[Haskell-cafe] Trouble representing a set of flags
Stefan O'Rear
stefanor at cox.net
Mon Feb 5 22:26:02 EST 2007
I have a structure:
data Attr = Attr { fg :: !Color,
bg :: !Color,
bold :: !Bool,
blink :: !Bool,
rv :: !Bool,
halfBright :: !Bool,
underline :: !Bool
} deriving(Eq,Show,Ord)
newtype Color = Color Int deriving(Eq,Show,Ord)
but ghc is doing a phenominally bad job of unboxing it; so I'm trying
to do it manually using a bitfield:
-- |Data type representing character attributes.
newtype Attr = Attr Int deriving (Eq)
-- | Set the foreground color of an `Attr'.
setFG :: Color -> Attr -> Attr
setFG (Color c) (Attr a) = Attr ((a .&. 0xFFFFFF00) .|. c)
-- | Get the foreground color of an `Attr'.
getFG :: Attr -> Color
getFG (Attr a) = Color (a .&. 0xFF)
-- | Set the background color of an `Attr'.
setBG :: Color -> Attr -> Attr
setBG (Color c) (Attr a) = Attr ((a .&. 0xFFFF00FF) .|. (c `uncheckedShiftL` 8))
-- | Get the background color of an `Attr'.
getBG :: Attr -> Color
getBG (Attr a) = Color ((a .&. 0xFF00) `uncheckedShiftR` 8)
-- | Set bold attribute of an `Attr'.
setBold :: Attr -> Attr
setBold (Attr a) = Attr (a .|. 0x10000)
-- | Clear bold attribute of an `Attr'.
clearBold :: Attr -> Attr
clearBold (Attr a) = Attr (a .&. 0xFFFEFFFF)
-- | Examine bold attribute of an `Attr'.
isBold :: Attr -> Bool
isBold (Attr a) = (a .&. 0x10000) /= 0
Urk. this is NO FUN. How do I stop the copy&paste and still generate
fast code? Is there a better way?
(Also, GHC seems unable to unbox strict fields that are newtypes. Can
this be done, or should I abandon type safety and use type synonyms?)
(Yes, this is performance critical code, and I have profiler output to
back up this claim.)
(Should this be directed to glasgow-haskell-users@ ?)
More information about the Haskell-Cafe
mailing list