------------------------------------------------------------------------------- --- $Id: Bit.hs#1 2009/10/01 10:31:09 REDMOND\\satnams $ ------------------------------------------------------------------------------- module Lava.Bit where ------------------------------------------------------------------------------- data Bit = One | Zero deriving Eq ------------------------------------------------------------------------------- instance Show Bit where showsPrec _ Zero = showString "0" showsPrec _ One = showString "1" ------------------------------------------------------------------------------- instance Num Bit where fromInteger 0 = Zero fromInteger 1 = One (+) = undefined (*) = undefined abs = undefined signum = undefined ------------------------------------------------------------------------------- fromBit :: Bit -> Bool fromBit Zero = False fromBit One = True ------------------------------------------------------------------------------- toBit :: Bool -> Bit toBit False = Zero toBit True = One ------------------------------------------------------------------------------- unaryBoolToBit :: (Bool -> Bool) -> (Bit -> Bit) unaryBoolToBit f bit = toBit (f (fromBit bit)) ------------------------------------------------------------------------------- binaryBoolToBit :: (Bool -> Bool -> Bool) -> (Bit -> Bit -> Bit) binaryBoolToBit f bit1 bit2 = toBit (f (fromBit bit1) (fromBit bit2)) ------------------------------------------------------------------------------- f3BoolToBit :: (Bool -> Bool -> Bool -> Bool) -> (Bit -> Bit -> Bit -> Bit) f3BoolToBit f bit1 bit2 bit3 = toBit (f (fromBit bit1) (fromBit bit2)(fromBit bit3)) ------------------------------------------------------------------------------- f4BoolToBit :: (Bool -> Bool -> Bool -> Bool -> Bool) -> (Bit -> Bit -> Bit -> Bit -> Bit) f4BoolToBit f bit1 bit2 bit3 bit4 = toBit (f (fromBit bit1) (fromBit bit2)(fromBit bit3) (fromBit bit4)) -------------------------------------------------------------------------------