{-# LANGUAGE CPP,FlexibleInstances #-} module Byte(Byte,Short,Unpack(..),bools2bytes,join8,join16,ord,byte) where import Data.Word import Utils2(Split,pieces) #ifndef __PFE__ import Data.Bits join8 :: Word8->Word8->Word16 join8 w1 w2 = shiftL (fromIntegral w1) 8 .|. fromIntegral w2 join16 :: Word16->Word16->Word32 join16 w1 w2 = shiftL (fromIntegral w1) 16 .|. fromIntegral w2 #endif type Byte = Word8 -- ^ 8 bits, range 0..255 only type Short = Word16 -- ^ 16 bits, range 0..65535 only bools2bytes :: [Bool] -> [Byte] bools2bytes = map packByte . pieces 8 where packByte bits = sum $ zipWith ((*).bit) bits be_bitvalue bit False = 0 bit True = 1 be_bitvalue = [128,64,32,16,8,4,2,1] class Split bs => Unpack bs where unpack :: bs -> [Byte] instance Unpack [Byte] where unpack = id ord c = fromIntegral (fromEnum c) byte x = ord x :: Byte