module System.Logger.Backend.ColorOption
( ColorOption(..)
, readColorOption
, colorOptionText
, defaultColorOption
, pColorOption
, pColorOption_
, useColor
) where
#ifndef MIN_VERSION_base
#define MIN_VERSION_base(x,y,z) 1
#endif
import Configuration.Utils
import Control.DeepSeq
import Control.Monad.Except
import qualified Data.CaseInsensitive as CI
#if ! MIN_VERSION_base(4,8,0)
import Data.Monoid
#endif
import Data.Monoid.Unicode
import Data.String
import qualified Data.Text as T
import Data.Typeable
import GHC.Generics
import qualified Options.Applicative as O
import Prelude.Unicode
import qualified System.Console.ANSI as A
import System.IO (Handle)
data ColorOption
= ColorAuto
| ColorFalse
| ColorTrue
deriving (Show, Read, Eq, Ord, Enum, Bounded, Typeable, Generic)
instance NFData ColorOption
readColorOption
∷ (Monad m, Eq a, Show a, CI.FoldCase a, IsString a, IsString e, Monoid e, MonadError e m)
⇒ a
→ m ColorOption
readColorOption x = case CI.mk x of
"auto" → return ColorAuto
"false" → return ColorFalse
"true" → return ColorTrue
e → throwError $ "unexpected color option value: "
⊕ fromString (show e)
⊕ ", expected \"auto\", \"false\", or \"true\""
colorOptionText
∷ IsString a
⇒ ColorOption
→ a
colorOptionText ColorAuto = "auto"
colorOptionText ColorFalse = "false"
colorOptionText ColorTrue = "true"
defaultColorOption ∷ ColorOption
defaultColorOption = ColorAuto
instance ToJSON ColorOption where
toJSON = String ∘ colorOptionText
instance FromJSON ColorOption where
parseJSON = withText "ColorOption" $ either fail return ∘ readColorOption
pColorOption ∷ O.Parser ColorOption
pColorOption = pColorOption_ ""
pColorOption_
∷ T.Text
→ O.Parser ColorOption
pColorOption_ prefix = option (eitherReader readColorOption)
× long (T.unpack prefix ⊕ "color")
⊕ short 'c'
⊕ help "whether to use ANSI terminal colors in the output"
useColor
∷ ColorOption
→ Handle
→ IO Bool
useColor ColorFalse _ = return False
useColor ColorTrue _ = return True
useColor ColorAuto handle = A.hSupportsANSI handle