module Colourista.Pure
( formatWith
, red
, green
, blue
, yellow
, black
, white
, magenta
, cyan
, redBg
, greenBg
, blueBg
, yellowBg
, blackBg
, whiteBg
, magentaBg
, cyanBg
, bold
, italic
, underline
, doubleUnderline
, noUnderline
, indent
, reset
) where
import Data.ByteString (ByteString)
import Data.List.NonEmpty (NonEmpty (..))
import Data.Semigroup (Semigroup (..))
import Data.String (IsString (..))
import Data.Text (Text)
import System.Console.ANSI (Color (..), ColorIntensity (Vivid), ConsoleIntensity (BoldIntensity),
ConsoleLayer (Background, Foreground), SGR (..), Underlining (..),
setSGRCode)
formatWith
:: (IsString str, Semigroup str)
=> [str]
-> str
-> str
formatWith formatting str = case formatting of
[] -> str
x:xs -> sconcat (x :| xs) <> str <> reset
{-# SPECIALIZE formatWith :: [String] -> String -> String #-}
{-# SPECIALIZE formatWith :: [Text] -> Text -> Text #-}
{-# SPECIALIZE formatWith :: [ByteString] -> ByteString -> ByteString #-}
red :: IsString str => str
red = fromString $ setSGRCode [SetColor Foreground Vivid Red]
{-# SPECIALIZE red :: String #-}
{-# SPECIALIZE red :: Text #-}
{-# SPECIALIZE red :: ByteString #-}
green :: IsString str => str
green = fromString $ setSGRCode [SetColor Foreground Vivid Green]
{-# SPECIALIZE green :: String #-}
{-# SPECIALIZE green :: Text #-}
{-# SPECIALIZE green :: ByteString #-}
blue :: IsString str => str
blue = fromString $ setSGRCode [SetColor Foreground Vivid Blue]
{-# SPECIALIZE blue :: String #-}
{-# SPECIALIZE blue :: Text #-}
{-# SPECIALIZE blue :: ByteString #-}
yellow :: IsString str => str
yellow = fromString $ setSGRCode [SetColor Foreground Vivid Yellow]
{-# SPECIALIZE yellow :: String #-}
{-# SPECIALIZE yellow :: Text #-}
{-# SPECIALIZE yellow :: ByteString #-}
black :: IsString str => str
black = fromString $ setSGRCode [SetColor Foreground Vivid Black]
{-# SPECIALIZE black :: String #-}
{-# SPECIALIZE black :: Text #-}
{-# SPECIALIZE black :: ByteString #-}
white :: IsString str => str
white = fromString $ setSGRCode [SetColor Foreground Vivid White]
{-# SPECIALIZE white :: String #-}
{-# SPECIALIZE white :: Text #-}
{-# SPECIALIZE white :: ByteString #-}
magenta :: IsString str => str
magenta = fromString $ setSGRCode [SetColor Foreground Vivid Magenta]
{-# SPECIALIZE magenta :: String #-}
{-# SPECIALIZE magenta :: Text #-}
{-# SPECIALIZE magenta :: ByteString #-}
cyan :: IsString str => str
cyan = fromString $ setSGRCode [SetColor Foreground Vivid Cyan]
{-# SPECIALIZE cyan :: String #-}
{-# SPECIALIZE cyan :: Text #-}
{-# SPECIALIZE cyan :: ByteString #-}
redBg :: IsString str => str
redBg = fromString $ setSGRCode [SetColor Background Vivid Red]
{-# SPECIALIZE redBg :: String #-}
{-# SPECIALIZE redBg :: Text #-}
{-# SPECIALIZE redBg :: ByteString #-}
greenBg :: IsString str => str
greenBg = fromString $ setSGRCode [SetColor Background Vivid Green]
{-# SPECIALIZE greenBg :: String #-}
{-# SPECIALIZE greenBg :: Text #-}
{-# SPECIALIZE greenBg :: ByteString #-}
blueBg :: IsString str => str
blueBg = fromString $ setSGRCode [SetColor Background Vivid Blue]
{-# SPECIALIZE blueBg :: String #-}
{-# SPECIALIZE blueBg :: Text #-}
{-# SPECIALIZE blueBg :: ByteString #-}
yellowBg :: IsString str => str
yellowBg = fromString $ setSGRCode [SetColor Background Vivid Yellow]
{-# SPECIALIZE yellowBg :: String #-}
{-# SPECIALIZE yellowBg :: Text #-}
{-# SPECIALIZE yellowBg :: ByteString #-}
blackBg :: IsString str => str
blackBg = fromString $ setSGRCode [SetColor Background Vivid Black]
{-# SPECIALIZE blackBg :: String #-}
{-# SPECIALIZE blackBg :: Text #-}
{-# SPECIALIZE blackBg :: ByteString #-}
whiteBg :: IsString str => str
whiteBg = fromString $ setSGRCode [SetColor Background Vivid White]
{-# SPECIALIZE whiteBg :: String #-}
{-# SPECIALIZE whiteBg :: Text #-}
{-# SPECIALIZE whiteBg :: ByteString #-}
magentaBg :: IsString str => str
magentaBg = fromString $ setSGRCode [SetColor Background Vivid Magenta]
{-# SPECIALIZE magentaBg :: String #-}
{-# SPECIALIZE magentaBg :: Text #-}
{-# SPECIALIZE magentaBg :: ByteString #-}
cyanBg :: IsString str => str
cyanBg = fromString $ setSGRCode [SetColor Background Vivid Cyan]
{-# SPECIALIZE cyanBg :: String #-}
{-# SPECIALIZE cyanBg :: Text #-}
{-# SPECIALIZE cyanBg :: ByteString #-}
bold :: IsString str => str
bold = fromString $ setSGRCode [SetConsoleIntensity BoldIntensity]
{-# SPECIALIZE bold :: String #-}
{-# SPECIALIZE bold :: Text #-}
{-# SPECIALIZE bold :: ByteString #-}
italic :: IsString str => str
italic = fromString $ setSGRCode [SetItalicized True]
{-# SPECIALIZE italic :: String #-}
{-# SPECIALIZE italic :: Text #-}
{-# SPECIALIZE italic :: ByteString #-}
underline :: IsString str => str
underline = fromString $ setSGRCode [SetUnderlining SingleUnderline]
{-# SPECIALIZE underline :: String #-}
{-# SPECIALIZE underline :: Text #-}
{-# SPECIALIZE underline :: ByteString #-}
doubleUnderline :: IsString str => str
doubleUnderline = fromString $ setSGRCode [SetUnderlining DoubleUnderline]
{-# SPECIALIZE doubleUnderline :: String #-}
{-# SPECIALIZE doubleUnderline :: Text #-}
{-# SPECIALIZE doubleUnderline :: ByteString #-}
noUnderline :: IsString str => str
noUnderline = fromString $ setSGRCode [SetUnderlining NoUnderline]
{-# SPECIALIZE noUnderline :: String #-}
{-# SPECIALIZE noUnderline :: Text #-}
{-# SPECIALIZE noUnderline :: ByteString #-}
indent :: (IsString str, Semigroup str) => Int -> str
indent n
| n <= 0 = ""
| otherwise = stimes n " "
{-# SPECIALIZE indent :: Int -> String #-}
{-# SPECIALIZE indent :: Int -> Text #-}
{-# SPECIALIZE indent :: Int -> ByteString #-}
reset :: IsString str => str
reset = fromString $ setSGRCode [Reset]
{-# SPECIALIZE reset :: String #-}
{-# SPECIALIZE reset :: Text #-}
{-# SPECIALIZE reset :: ByteString #-}