module System.Console.ANSI.Codes
    (
      
      module System.Console.ANSI.Types
      
    , cursorUpCode, cursorDownCode, cursorForwardCode, cursorBackwardCode
      
    , cursorUpLineCode, cursorDownLineCode
      
    , setCursorColumnCode, setCursorPositionCode
      
    , clearFromCursorToScreenEndCode, clearFromCursorToScreenBeginningCode
    , clearScreenCode, clearFromCursorToLineEndCode
    , clearFromCursorToLineBeginningCode, clearLineCode
      
    , scrollPageUpCode, scrollPageDownCode
      
    , setSGRCode
      
    , hideCursorCode, showCursorCode
      
      
      
      
      
      
      
    , setTitleCode
      
    , colorToCode, csi, sgrToCode
    ) where
import Data.Colour.SRGB (toSRGB24, RGB (..))
import Data.List (intersperse)
import System.Console.ANSI.Types
csi :: [Int]  
    -> String 
    -> String
csi args code = "\ESC[" ++ concat (intersperse ";" (map show args)) ++ code
colorToCode :: Color -> Int
colorToCode color = case color of
    Black   -> 0
    Red     -> 1
    Green   -> 2
    Yellow  -> 3
    Blue    -> 4
    Magenta -> 5
    Cyan    -> 6
    White   -> 7
sgrToCode :: SGR 
          -> [Int]
sgrToCode sgr = case sgr of
    Reset -> [0]
    SetConsoleIntensity intensity -> case intensity of
        BoldIntensity   -> [1]
        FaintIntensity  -> [2]
        NormalIntensity -> [22]
    SetItalicized True  -> [3]
    SetItalicized False -> [23]
    SetUnderlining underlining -> case underlining of
        SingleUnderline -> [4]
        DoubleUnderline -> [21]
        NoUnderline     -> [24]
    SetBlinkSpeed blink_speed -> case blink_speed of
        SlowBlink   -> [5]
        RapidBlink  -> [6]
        NoBlink     -> [25]
    SetVisible False -> [8]
    SetVisible True  -> [28]
    SetSwapForegroundBackground True  -> [7]
    SetSwapForegroundBackground False -> [27]
    SetColor Foreground Dull color  -> [30 + colorToCode color]
    SetColor Foreground Vivid color -> [90 + colorToCode color]
    SetColor Background Dull color  -> [40 + colorToCode color]
    SetColor Background Vivid color -> [100 + colorToCode color]
    SetRGBColor Foreground color -> [38, 2] ++ toRGB color
    SetRGBColor Background color -> [48, 2] ++ toRGB color
  where
    toRGB color = let RGB r g b = toSRGB24 color
                  in  map fromIntegral [r, g, b]
cursorUpCode, cursorDownCode, cursorForwardCode, cursorBackwardCode :: Int 
                                                                    -> String
cursorUpCode n = csi [n] "A"
cursorDownCode n = csi [n] "B"
cursorForwardCode n = csi [n] "C"
cursorBackwardCode n = csi [n] "D"
cursorDownLineCode, cursorUpLineCode :: Int 
                                     -> String
cursorDownLineCode n = csi [n] "E"
cursorUpLineCode n = csi [n] "F"
setCursorColumnCode :: Int 
                    -> String
setCursorColumnCode n = csi [n + 1] "G"
setCursorPositionCode :: Int 
                      -> Int 
                      -> String
setCursorPositionCode n m = csi [n + 1, m + 1] "H"
clearFromCursorToScreenEndCode, clearFromCursorToScreenBeginningCode, clearScreenCode :: String
clearFromCursorToLineEndCode, clearFromCursorToLineBeginningCode, clearLineCode :: String
clearFromCursorToScreenEndCode = csi [0] "J"
clearFromCursorToScreenBeginningCode = csi [1] "J"
clearScreenCode = csi [2] "J"
clearFromCursorToLineEndCode = csi [0] "K"
clearFromCursorToLineBeginningCode = csi [1] "K"
clearLineCode = csi [2] "K"
scrollPageUpCode, scrollPageDownCode :: Int 
                                     -> String
scrollPageUpCode n = csi [n] "S"
scrollPageDownCode n = csi [n] "T"
setSGRCode :: [SGR] 
                    
                    
                    
           -> String
setSGRCode sgrs = csi (concatMap sgrToCode sgrs) "m"
hideCursorCode, showCursorCode :: String
hideCursorCode = csi [] "?25l"
showCursorCode = csi [] "?25h"
setTitleCode :: String 
             -> String
setTitleCode title = "\ESC]0;" ++ filter (/= '\007') title ++ "\007"