module Data.Bool8 (
   Bool8,
   false, true,
   toBool,
   fromBool,
   ) where

import Foreign.Storable (Storable, poke, peek, sizeOf, alignment)
import Foreign.Ptr (castPtr)

import Data.Functor ((<$>))
import Data.Word (Word8)


newtype Bool8 = Bool8 Word8
   deriving (Eq, Ord)

instance Show Bool8 where
   show (Bool8 0) = "Bool8.false"
   show _ = "Bool8.true"

instance Bounded Bool8 where
   minBound = false
   maxBound = true

instance Storable Bool8 where
   sizeOf _ = 1
   alignment _ = 1
   peek ptr = Bool8 <$> peek (castPtr ptr)
   poke ptr (Bool8 b) = poke (castPtr ptr) b

instance Enum Bool8 where
   fromEnum (Bool8 b) = fromIntegral b
   toEnum k = Bool8 $ if k==0 then 0 else 1

false, true :: Bool8
false = Bool8 0
true = Bool8 1

toBool :: Bool8 -> Bool
toBool (Bool8 b) = b/=0

fromBool :: Bool -> Bool8
fromBool b = if b then true else false