{-| This module allows you to add colors to another style for Hable configuration. To add a single color to the whole table, it's the most simple to use 'colored8Config'. If you'd like to color vertical lines independently from horizontal lines, use 'colored8Charset' and don\'t forget to compose 'Colored8' to the 'hLineStyle' and 'vLineStyle' properties of your config appropriately. If you'd like to decide yourself how to act at the points of the table where vertical and horizontal lines are cutting across, use 'genColored8charset'. -} -------------------------------------------------------------------------------- module Hable.Style.Colored8 ( Color8(..) , Colored8(..) , colored8Config , colored8Charset , genColored8Charset , color8String ) where -------------------------------------------------------------------------------- import Hable.BoxChar import Hable.Config -------------------------------------------------------------------------------- -- | Add colors to a configuration. -- -- The first argument may be a foreground color. If it's 'Nothing', the -- foreground won't be modified. -- -- The second argument may be a background color. If it's 'Nothing', the -- background won't be modified. -- -- The third argument is the configuration to be colored. colored8Config :: Maybe Color8 -> Maybe Color8 -> Config style -> Config (Colored8 style) colored8Config fg bg conf = conf { charset = colored8Charset (charset conf) , hLineStyle = \m n -> fmap (Colored8 fg bg) (hLineStyle conf m n) , vLineStyle = \m n -> fmap (Colored8 fg bg) (vLineStyle conf m n) } -------------------------------------------------------------------------------- -- | Given a 'charset', returns another new one which supports colors through a -- 'Colored8' style. -- -- An example which circles the colors of the horizontal lines using 'mod' -- -- @ -- >>> putStr (hable defaultConfig { charset = colored8Charset (charset defaultConfig), vLineStyle = \_ _ -> Nothing, hLineStyle = \m n -> fmap (Colored8 (Just (toEnum (fromInteger ((n `mod` 6) + 1)))) Nothing) $ vLineStyle defaultConfig m n } exampleTable) -- @ -- -- Unfortunately, you wouldn't see the colors here, so there's a picture: -- -- <> colored8Charset :: (BoxChar style -> String) -> BoxChar (Colored8 style) -> String colored8Charset = genColored8Charset chooseColor where chooseColor _ _ _ (Colored8 vFg vBg _) = (vFg, vBg) -------------------------------------------------------------------------------- -- | A generalization of 'colored8Charset'. Instead of simply using choosing the -- vertical color components for 'Angled' box characters, you can pass your own -- function to decide which color to choose in this case. E.g. you could write a -- function which uses a completely different color. -- -- All in all, the first argument of 'genColored8charset' is a function. Its -- arguments are the same as the arguments of the 'Angled' constructor. genColored8Charset :: (HAxis -> Colored8 style -> VAxis -> Colored8 style -> (Maybe Color8, Maybe Color8)) -> (BoxChar style -> String) -> BoxChar (Colored8 style) -> String genColored8Charset _ chrst (Bar (Colored8 vFg vBg vStyle)) = color8String vFg vBg (chrst (Bar vStyle)) genColored8Charset _ chrst (Dash (Colored8 hFg hBg hStyle)) = color8String hFg hBg (chrst (Dash hStyle)) genColored8Charset chooseColor chrst angled@(Angled hAlign h@(Colored8 hFg hBg hStyle) vAlign v@(Colored8 vFg vBg vStyle)) = color8String fg bg (chrst (Angled hAlign hStyle vAlign vStyle)) where (fg, bg) = chooseColor hAlign h vAlign v -------------------------------------------------------------------------------- -- | Wraps a 'String' into the ANSI escape codes of the given fore- and -- background colors. color8String :: Maybe Color8 -> Maybe Color8 -> String -> String color8String fg bg string = concat [ insert 30 fg , insert 40 bg , string , "\ESC[0m" ] where insert n maybeXg = maybe "" (\xg -> "\ESC[" ++ show (fromEnum xg + n) ++ "m") maybeXg -------------------------------------------------------------------------------- -- | Represents the eight colors supported by most terminal emulators through -- ANSI escape codes. data Color8 = Black | Red | Green | Yellow | Blue | Magenta | Cyan | White deriving (Eq,Enum) -------------------------------------------------------------------------------- -- | A wrapper for any other style, adding an option of a fore- as well as a -- background color to it. For the color fields, 'Nothing' represents an -- unchanged\/unmodified\/unset color. data Colored8 style = Colored8 { foreground :: Maybe Color8 , background :: Maybe Color8 , colored8Style :: style }