module Graphics.Vty.Attributes ( module Graphics.Vty.Attributes
, module Graphics.Vty.Attributes.Color
, module Graphics.Vty.Attributes.Color240
)
where
import Graphics.Vty.Attributes.Color
import Graphics.Vty.Attributes.Color240
import Data.Bits
import Data.Monoid
import Data.Word
data Attr = Attr
{ attr_style :: !(MaybeDefault Style)
, attr_fore_color :: !(MaybeDefault Color)
, attr_back_color :: !(MaybeDefault Color)
} deriving ( Eq, Show )
instance Monoid Attr where
mempty = Attr mempty mempty mempty
mappend attr_0 attr_1 =
Attr ( attr_style attr_0 `mappend` attr_style attr_1 )
( attr_fore_color attr_0 `mappend` attr_fore_color attr_1 )
( attr_back_color attr_0 `mappend` attr_back_color attr_1 )
data FixedAttr = FixedAttr
{ fixed_style :: !Style
, fixed_fore_color :: !(Maybe Color)
, fixed_back_color :: !(Maybe Color)
} deriving ( Eq, Show )
data MaybeDefault v where
Default :: MaybeDefault v
KeepCurrent :: MaybeDefault v
SetTo :: forall v . ( Eq v, Show v ) => !v -> MaybeDefault v
deriving instance Eq v => Eq (MaybeDefault v)
deriving instance Eq v => Show (MaybeDefault v)
instance Eq v => Monoid ( MaybeDefault v ) where
mempty = KeepCurrent
mappend Default Default = Default
mappend Default KeepCurrent = Default
mappend Default ( SetTo v ) = SetTo v
mappend KeepCurrent Default = Default
mappend KeepCurrent KeepCurrent = KeepCurrent
mappend KeepCurrent ( SetTo v ) = SetTo v
mappend ( SetTo _v ) Default = Default
mappend ( SetTo v ) KeepCurrent = SetTo v
mappend ( SetTo _ ) ( SetTo v ) = SetTo v
black, red, green, yellow, blue, magenta, cyan, white :: Color
black = ISOColor 0
red = ISOColor 1
green = ISOColor 2
yellow = ISOColor 3
blue = ISOColor 4
magenta= ISOColor 5
cyan = ISOColor 6
white = ISOColor 7
bright_black, bright_red, bright_green, bright_yellow :: Color
bright_blue, bright_magenta, bright_cyan, bright_white :: Color
bright_black = ISOColor 8
bright_red = ISOColor 9
bright_green = ISOColor 10
bright_yellow = ISOColor 11
bright_blue = ISOColor 12
bright_magenta= ISOColor 13
bright_cyan = ISOColor 14
bright_white = ISOColor 15
type Style = Word8
standout, underline, reverse_video, blink, dim, bold :: Style
standout = 0x01
underline = 0x02
reverse_video = 0x04
blink = 0x08
dim = 0x10
bold = 0x20
default_style_mask :: Style
default_style_mask = 0x00
style_mask :: Attr -> Word8
style_mask attr
= case attr_style attr of
Default -> 0
KeepCurrent -> 0
SetTo v -> v
has_style :: Style -> Style -> Bool
has_style s bit_mask = ( s .&. bit_mask ) /= 0
with_fore_color :: Attr -> Color -> Attr
with_fore_color attr c = attr { attr_fore_color = SetTo c }
with_back_color :: Attr -> Color -> Attr
with_back_color attr c = attr { attr_back_color = SetTo c }
with_style :: Attr -> Style -> Attr
with_style attr style_flag = attr { attr_style = SetTo $ style_mask attr .|. style_flag }
def_attr :: Attr
def_attr = Attr Default Default Default
current_attr :: Attr
current_attr = Attr KeepCurrent KeepCurrent KeepCurrent