{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Text.Pretty.Simple.Internal.Color
  where
#if __GLASGOW_HASKELL__ < 710
import Control.Applicative
#endif
import Data.Typeable (Typeable)
import GHC.Generics (Generic)
import Prettyprinter.Render.Terminal
  (AnsiStyle, Intensity(Dull,Vivid), Color(..))
import qualified Prettyprinter.Render.Terminal as Ansi
data ColorOptions = ColorOptions
  { ColorOptions -> Style
colorQuote :: Style
  
  , ColorOptions -> Style
colorString :: Style
  
  , ColorOptions -> Style
colorError :: Style
  
  , ColorOptions -> Style
colorNum :: Style
  
  , ColorOptions -> [Style]
colorRainbowParens :: [Style]
  
  
  
  } deriving (ColorOptions -> ColorOptions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ColorOptions -> ColorOptions -> Bool
$c/= :: ColorOptions -> ColorOptions -> Bool
== :: ColorOptions -> ColorOptions -> Bool
$c== :: ColorOptions -> ColorOptions -> Bool
Eq, forall x. Rep ColorOptions x -> ColorOptions
forall x. ColorOptions -> Rep ColorOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ColorOptions x -> ColorOptions
$cfrom :: forall x. ColorOptions -> Rep ColorOptions x
Generic, Int -> ColorOptions -> ShowS
[ColorOptions] -> ShowS
ColorOptions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ColorOptions] -> ShowS
$cshowList :: [ColorOptions] -> ShowS
show :: ColorOptions -> String
$cshow :: ColorOptions -> String
showsPrec :: Int -> ColorOptions -> ShowS
$cshowsPrec :: Int -> ColorOptions -> ShowS
Show, Typeable)
defaultColorOptionsDarkBg :: ColorOptions
defaultColorOptionsDarkBg :: ColorOptions
defaultColorOptionsDarkBg =
  ColorOptions
  { colorQuote :: Style
colorQuote = Intensity -> Color -> Style
colorBold Intensity
Vivid Color
White
  , colorString :: Style
colorString = Intensity -> Color -> Style
colorBold Intensity
Vivid Color
Blue
  , colorError :: Style
colorError = Intensity -> Color -> Style
colorBold Intensity
Vivid Color
Red
  , colorNum :: Style
colorNum = Intensity -> Color -> Style
colorBold Intensity
Vivid Color
Green
  , colorRainbowParens :: [Style]
colorRainbowParens =
    [ Intensity -> Color -> Style
colorBold Intensity
Vivid Color
Magenta
    , Intensity -> Color -> Style
colorBold Intensity
Vivid Color
Cyan
    , Intensity -> Color -> Style
colorBold Intensity
Vivid Color
Yellow
    , Intensity -> Color -> Style
color Intensity
Dull Color
Magenta
    , Intensity -> Color -> Style
color Intensity
Dull Color
Cyan
    , Intensity -> Color -> Style
color Intensity
Dull Color
Yellow
    , Intensity -> Color -> Style
colorBold Intensity
Dull Color
Magenta
    , Intensity -> Color -> Style
colorBold Intensity
Dull Color
Cyan
    , Intensity -> Color -> Style
colorBold Intensity
Dull Color
Yellow
    , Intensity -> Color -> Style
color Intensity
Vivid Color
Magenta
    , Intensity -> Color -> Style
color Intensity
Vivid Color
Cyan
    , Intensity -> Color -> Style
color Intensity
Vivid Color
Yellow
    ]
  }
defaultColorOptionsLightBg :: ColorOptions
defaultColorOptionsLightBg :: ColorOptions
defaultColorOptionsLightBg =
  ColorOptions
  { colorQuote :: Style
colorQuote = Intensity -> Color -> Style
colorBold Intensity
Vivid Color
Black
  , colorString :: Style
colorString = Intensity -> Color -> Style
colorBold Intensity
Vivid Color
Blue
  , colorError :: Style
colorError = Intensity -> Color -> Style
colorBold Intensity
Vivid Color
Red
  , colorNum :: Style
colorNum = Intensity -> Color -> Style
colorBold Intensity
Vivid Color
Green
  , colorRainbowParens :: [Style]
colorRainbowParens =
    [ Intensity -> Color -> Style
colorBold Intensity
Vivid Color
Magenta
    , Intensity -> Color -> Style
colorBold Intensity
Vivid Color
Cyan
    , Intensity -> Color -> Style
color Intensity
Dull Color
Magenta
    , Intensity -> Color -> Style
color Intensity
Dull Color
Cyan
    , Intensity -> Color -> Style
colorBold Intensity
Dull Color
Magenta
    , Intensity -> Color -> Style
colorBold Intensity
Dull Color
Cyan
    , Intensity -> Color -> Style
color Intensity
Vivid Color
Magenta
    , Intensity -> Color -> Style
color Intensity
Vivid Color
Cyan
    ]
  }
colorNull :: Style
colorNull :: Style
colorNull = Style
  { styleColor :: Maybe (Color, Intensity)
styleColor = forall a. Maybe a
Nothing
  , styleBold :: Bool
styleBold = Bool
False
  , styleItalic :: Bool
styleItalic = Bool
False
  , styleUnderlined :: Bool
styleUnderlined = Bool
False
  }
data Style = Style
  { Style -> Maybe (Color, Intensity)
styleColor :: Maybe (Color, Intensity)
  , Style -> Bool
styleBold :: Bool
  , Style -> Bool
styleItalic :: Bool
  , Style -> Bool
styleUnderlined :: Bool
  }
  deriving (Style -> Style -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Style -> Style -> Bool
$c/= :: Style -> Style -> Bool
== :: Style -> Style -> Bool
$c== :: Style -> Style -> Bool
Eq, forall x. Rep Style x -> Style
forall x. Style -> Rep Style x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Style x -> Style
$cfrom :: forall x. Style -> Rep Style x
Generic, Int -> Style -> ShowS
[Style] -> ShowS
Style -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Style] -> ShowS
$cshowList :: [Style] -> ShowS
show :: Style -> String
$cshow :: Style -> String
showsPrec :: Int -> Style -> ShowS
$cshowsPrec :: Int -> Style -> ShowS
Show, Typeable)
color :: Intensity -> Color -> Style
color :: Intensity -> Color -> Style
color Intensity
i Color
c = Style
colorNull {styleColor :: Maybe (Color, Intensity)
styleColor = forall a. a -> Maybe a
Just (Color
c, Intensity
i)}
colorBold :: Intensity -> Color -> Style
colorBold :: Intensity -> Color -> Style
colorBold Intensity
i Color
c = (Intensity -> Color -> Style
color Intensity
i Color
c) {styleBold :: Bool
styleBold = Bool
True}
convertStyle :: Style -> AnsiStyle
convertStyle :: Style -> AnsiStyle
convertStyle Style {Bool
Maybe (Color, Intensity)
styleUnderlined :: Bool
styleItalic :: Bool
styleBold :: Bool
styleColor :: Maybe (Color, Intensity)
styleUnderlined :: Style -> Bool
styleItalic :: Style -> Bool
styleBold :: Style -> Bool
styleColor :: Style -> Maybe (Color, Intensity)
..} =
  forall a. Monoid a => [a] -> a
mconcat
    [ forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. Monoid a => a
mempty (forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry forall a b. (a -> b) -> a -> b
$ forall a b c. (a -> b -> c) -> b -> a -> c
flip Intensity -> Color -> AnsiStyle
col) Maybe (Color, Intensity)
styleColor
    , if Bool
styleBold then AnsiStyle
Ansi.bold else forall a. Monoid a => a
mempty
    , if Bool
styleItalic then AnsiStyle
Ansi.italicized else forall a. Monoid a => a
mempty
    , if Bool
styleUnderlined then AnsiStyle
Ansi.underlined else forall a. Monoid a => a
mempty
    ]
  where
    col :: Intensity -> Color -> AnsiStyle
col = \case
      Intensity
Vivid -> Color -> AnsiStyle
Ansi.color
      Intensity
Dull -> Color -> AnsiStyle
Ansi.colorDull