module System.Console.Terminfo.Color(
                    termColors,
                    Color(..),
                    
                    withForegroundColor,
                    withBackgroundColor,
                    
                    setForegroundColor,
                    setBackgroundColor,
                    
                    restoreDefaultColors
                    ) where
import System.Console.Terminfo.Base
import Control.Monad (mplus)
termColors :: Capability Int
termColors = tiGetNum "colors"
data Color = Black | Red | Green | Yellow | Blue | Magenta | Cyan
            | White | ColorNumber Int
colorIntA, colorInt :: Color -> Int
colorIntA c = case c of
    Black -> 0
    Red -> 1
    Green -> 2
    Yellow -> 3
    Blue -> 4
    Magenta -> 5
    Cyan -> 6
    White -> 7
    ColorNumber n -> n
colorInt c = case c of
    Black -> 0
    Blue -> 1
    Green -> 2
    Cyan -> 3
    Red -> 4
    Magenta -> 5
    Yellow -> 6
    White -> 7
    ColorNumber n -> n
withForegroundColor :: TermStr s => Capability (Color -> s -> s)
withForegroundColor = withColorCmd setForegroundColor
withBackgroundColor :: TermStr s => Capability (Color -> s -> s)
withBackgroundColor = withColorCmd setBackgroundColor
withColorCmd :: TermStr s => Capability (a -> s)
            -> Capability (a -> s -> s)
withColorCmd getSet = do
    set <- getSet
    restore <- restoreDefaultColors
    return $ \c t -> set c <#> t <#> restore
setForegroundColor :: TermStr s => Capability (Color -> s)
setForegroundColor = setaf `mplus` setf
    where
        setaf = fmap (. colorIntA) $ tiGetOutput1 "setaf"
        setf = fmap (. colorInt) $ tiGetOutput1 "setf"
setBackgroundColor :: TermStr s => Capability (Color -> s)
setBackgroundColor = setab `mplus` setb
    where
        setab = fmap (. colorIntA) $ tiGetOutput1 "setab"
        setb = fmap (. colorInt) $ tiGetOutput1 "setb"
  
restoreDefaultColors :: TermStr s => Capability s 
restoreDefaultColors = tiGetOutput1 "op"