{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module RIO.PrettyPrint.DefaultStyles
( defaultStyles
) where
import Data.Array.IArray ( array )
import RIO
import RIO.PrettyPrint.Types ( Style (..), Styles )
import System.Console.ANSI.Codes
( Color (..), ColorIntensity (..), ConsoleIntensity (..)
, ConsoleLayer (..), SGR (..)
)
defaultStyles :: Styles
defaultStyles :: Styles
defaultStyles = forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
(i, i) -> [(i, e)] -> a i e
array (forall a. Bounded a => a
minBound, forall a. Bounded a => a
maxBound)
[ (Style
Error, (Text
"error", [ConsoleLayer -> ColorIntensity -> Color -> SGR
SetColor ConsoleLayer
Foreground ColorIntensity
Vivid Color
Red]))
, (Style
Warning, (Text
"warning", [ConsoleLayer -> ColorIntensity -> Color -> SGR
SetColor ConsoleLayer
Foreground ColorIntensity
Dull Color
Yellow]))
, (Style
Info, (Text
"info", [ConsoleLayer -> ColorIntensity -> Color -> SGR
SetColor ConsoleLayer
Foreground ColorIntensity
Dull Color
Blue]))
, (Style
Debug, (Text
"debug", [ConsoleLayer -> ColorIntensity -> Color -> SGR
SetColor ConsoleLayer
Foreground ColorIntensity
Dull Color
Green]))
, (Style
OtherLevel, (Text
"other-level", [ConsoleLayer -> ColorIntensity -> Color -> SGR
SetColor ConsoleLayer
Foreground ColorIntensity
Dull Color
Magenta]))
, (Style
Good, (Text
"good", [ConsoleLayer -> ColorIntensity -> Color -> SGR
SetColor ConsoleLayer
Foreground ColorIntensity
Vivid Color
Green]))
, (Style
Shell, (Text
"shell", [ConsoleLayer -> ColorIntensity -> Color -> SGR
SetColor ConsoleLayer
Foreground ColorIntensity
Vivid Color
Magenta]))
, (Style
File, (Text
"file", [ConsoleLayer -> ColorIntensity -> Color -> SGR
SetColor ConsoleLayer
Foreground ColorIntensity
Dull Color
Cyan]))
, (Style
Url, (Text
"url", [ConsoleLayer -> ColorIntensity -> Color -> SGR
SetColor ConsoleLayer
Foreground ColorIntensity
Dull Color
Cyan]))
, (Style
Dir, (Text
"dir", [ ConsoleIntensity -> SGR
SetConsoleIntensity ConsoleIntensity
BoldIntensity
, ConsoleLayer -> ColorIntensity -> Color -> SGR
SetColor ConsoleLayer
Foreground ColorIntensity
Vivid Color
Blue ]))
, (Style
Recommendation, (Text
"recommendation", [ ConsoleIntensity -> SGR
SetConsoleIntensity ConsoleIntensity
BoldIntensity
, ConsoleLayer -> ColorIntensity -> Color -> SGR
SetColor ConsoleLayer
Foreground ColorIntensity
Vivid Color
Green]))
, (Style
Current, (Text
"current", [ConsoleLayer -> ColorIntensity -> Color -> SGR
SetColor ConsoleLayer
Foreground ColorIntensity
Dull Color
Yellow]))
, (Style
Target, (Text
"target", [ConsoleLayer -> ColorIntensity -> Color -> SGR
SetColor ConsoleLayer
Foreground ColorIntensity
Vivid Color
Cyan]))
, (Style
Module, (Text
"module", [ConsoleLayer -> ColorIntensity -> Color -> SGR
SetColor ConsoleLayer
Foreground ColorIntensity
Vivid Color
Magenta]))
, (Style
PkgComponent, (Text
"package-component", [ConsoleLayer -> ColorIntensity -> Color -> SGR
SetColor ConsoleLayer
Foreground ColorIntensity
Vivid Color
Cyan]))
, (Style
Secondary, (Text
"secondary", [ConsoleLayer -> ColorIntensity -> Color -> SGR
SetColor ConsoleLayer
Foreground ColorIntensity
Vivid Color
Black]))
, (Style
Highlight, (Text
"highlight", [ConsoleLayer -> ColorIntensity -> Color -> SGR
SetColor ConsoleLayer
Foreground ColorIntensity
Vivid Color
Green]))
]