{-# LANGUAGE CPP #-}
module Colourista.IO
(
redMessage
, greenMessage
, blueMessage
, yellowMessage
, blackMessage
, whiteMessage
, magentaMessage
, cyanMessage
, successMessage
, infoMessage
, skipMessage
, warningMessage
, errorMessage
, boldMessage
, italicMessage
, formattedMessage
) where
#if __GLASGOW_HASKELL__ < 804
import Data.Semigroup (Semigroup (..))
#endif
import Data.Text (Text)
import qualified Data.Text.IO as TIO
import qualified Colourista.Pure as Colourista
redMessage :: Text -> IO ()
redMessage :: Text -> IO ()
redMessage = [Text] -> Text -> IO ()
formattedMessage [Text
forall str. IsString str => str
Colourista.red]
{-# INLINE redMessage #-}
greenMessage :: Text -> IO ()
greenMessage :: Text -> IO ()
greenMessage = [Text] -> Text -> IO ()
formattedMessage [Text
forall str. IsString str => str
Colourista.green]
{-# INLINE greenMessage #-}
blueMessage :: Text -> IO ()
blueMessage :: Text -> IO ()
blueMessage = [Text] -> Text -> IO ()
formattedMessage [Text
forall str. IsString str => str
Colourista.blue]
{-# INLINE blueMessage #-}
yellowMessage :: Text -> IO ()
yellowMessage :: Text -> IO ()
yellowMessage = [Text] -> Text -> IO ()
formattedMessage [Text
forall str. IsString str => str
Colourista.yellow]
{-# INLINE yellowMessage #-}
blackMessage :: Text -> IO ()
blackMessage :: Text -> IO ()
blackMessage = [Text] -> Text -> IO ()
formattedMessage [Text
forall str. IsString str => str
Colourista.black]
{-# INLINE blackMessage #-}
whiteMessage :: Text -> IO ()
whiteMessage :: Text -> IO ()
whiteMessage = [Text] -> Text -> IO ()
formattedMessage [Text
forall str. IsString str => str
Colourista.white]
{-# INLINE whiteMessage #-}
magentaMessage :: Text -> IO ()
magentaMessage :: Text -> IO ()
magentaMessage = [Text] -> Text -> IO ()
formattedMessage [Text
forall str. IsString str => str
Colourista.magenta]
{-# INLINE magentaMessage #-}
cyanMessage :: Text -> IO ()
cyanMessage :: Text -> IO ()
cyanMessage = [Text] -> Text -> IO ()
formattedMessage [Text
forall str. IsString str => str
Colourista.cyan]
{-# INLINE cyanMessage #-}
successMessage :: Text -> IO ()
successMessage :: Text -> IO ()
successMessage Text
t = Text -> IO ()
greenMessage (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$ Text
" ✔ " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
t
{-# INLINE successMessage #-}
infoMessage :: Text -> IO ()
infoMessage :: Text -> IO ()
infoMessage Text
t = Text -> IO ()
blueMessage (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$ Text
" ⓘ " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
t
{-# INLINE infoMessage #-}
skipMessage :: Text -> IO ()
skipMessage :: Text -> IO ()
skipMessage Text
t = Text -> IO ()
cyanMessage (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$ Text
" ▶ " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
t
{-# INLINE skipMessage #-}
warningMessage :: Text -> IO ()
warningMessage :: Text -> IO ()
warningMessage Text
t = Text -> IO ()
yellowMessage (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$ Text
" ⚠ " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
t
{-# INLINE warningMessage #-}
errorMessage :: Text -> IO ()
errorMessage :: Text -> IO ()
errorMessage Text
t = Text -> IO ()
redMessage (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$ Text
" \128721 " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
t
{-# INLINE errorMessage #-}
boldMessage :: Text -> IO ()
boldMessage :: Text -> IO ()
boldMessage = [Text] -> Text -> IO ()
formattedMessage [Text
forall str. IsString str => str
Colourista.bold]
{-# INLINE boldMessage #-}
italicMessage :: Text -> IO ()
italicMessage :: Text -> IO ()
italicMessage = [Text] -> Text -> IO ()
formattedMessage [Text
forall str. IsString str => str
Colourista.italic]
{-# INLINE italicMessage #-}
formattedMessage :: [Text] -> Text -> IO ()
formattedMessage :: [Text] -> Text -> IO ()
formattedMessage [Text]
formatting = Text -> IO ()
TIO.putStrLn (Text -> IO ()) -> (Text -> Text) -> Text -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Text -> Text
forall str. (IsString str, Semigroup str) => [str] -> str -> str
Colourista.formatWith [Text]
formatting
{-# INLINE formattedMessage #-}