1
1
mirror of https://github.com/nmattia/niv.git synced 2024-11-29 09:42:35 +03:00

Cleanup logger

This commit is contained in:
Nicolas Mattia 2019-11-30 15:58:37 +01:00
parent 26438c14a8
commit c0cc366f0f
2 changed files with 41 additions and 17 deletions

View File

@ -1,8 +1,10 @@
{-# LANGUAGE OverloadedStrings #-}
module Data.Text.Extended where module Data.Text.Extended where
import Niv.Logger
import System.Exit (exitFailure) import System.Exit (exitFailure)
import qualified Data.Text as T import qualified Data.Text as T
import qualified Data.Text.IO as T
tshow :: Show a => a -> T.Text tshow :: Show a => a -> T.Text
tshow = T.pack . show tshow = T.pack . show
@ -10,5 +12,5 @@ tshow = T.pack . show
-- not quite the perfect place for this -- not quite the perfect place for this
abort :: T.Text -> IO a abort :: T.Text -> IO a
abort msg = do abort msg = do
T.putStrLn msg tsay $ T.unwords [ tbold $ tred "FATAL:", msg ]
exitFailure exitFailure

View File

@ -3,7 +3,17 @@
{-# LANGUAGE LambdaCase #-} {-# LANGUAGE LambdaCase #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Niv.Logger where module Niv.Logger
( job
, tsay
, say
, green, tgreen
, red, tred
, blue, tblue
, yellow, tyellow
, bold, tbold
, faint, tfaint
) where
import Control.Monad import Control.Monad
import Data.Profunctor import Data.Profunctor
@ -13,6 +23,9 @@ import qualified Data.Text as T
import UnliftIO import UnliftIO
import qualified System.Console.ANSI as ANSI import qualified System.Console.ANSI as ANSI
type S = String -> String
type T = T.Text -> T.Text
-- XXX: this assumes as single thread -- XXX: this assumes as single thread
job :: String -> IO () -> IO () job :: String -> IO () -> IO ()
job str act = do job str act = do
@ -45,51 +58,60 @@ say :: String -> IO ()
say msg = do say msg = do
stackSize <- jobStackSize stackSize <- jobStackSize
let indent = replicate (stackSize * 2) ' ' let indent = replicate (stackSize * 2) ' '
putStrLn $ indent <> msg putStrLn $ unlines $ (indent <>) <$> lines msg
green :: String -> String green :: S
green str = green str =
ANSI.setSGRCode [ANSI.SetConsoleIntensity ANSI.BoldIntensity] <> ANSI.setSGRCode [ANSI.SetConsoleIntensity ANSI.BoldIntensity] <>
ANSI.setSGRCode [ANSI.SetColor ANSI.Foreground ANSI.Vivid ANSI.Green] <> ANSI.setSGRCode [ANSI.SetColor ANSI.Foreground ANSI.Vivid ANSI.Green] <>
str <> ANSI.setSGRCode [ANSI.Reset] str <> ANSI.setSGRCode [ANSI.Reset]
yellow :: String -> String tgreen :: T
tgreen = t green
yellow :: S
yellow str = yellow str =
ANSI.setSGRCode [ANSI.SetConsoleIntensity ANSI.BoldIntensity] <> ANSI.setSGRCode [ANSI.SetConsoleIntensity ANSI.BoldIntensity] <>
ANSI.setSGRCode [ANSI.SetColor ANSI.Foreground ANSI.Vivid ANSI.Yellow] <> ANSI.setSGRCode [ANSI.SetColor ANSI.Foreground ANSI.Vivid ANSI.Yellow] <>
str <> ANSI.setSGRCode [ANSI.Reset] str <> ANSI.setSGRCode [ANSI.Reset]
tyellow :: T.Text -> T.Text tyellow :: T
tyellow = dimap T.unpack T.pack yellow tyellow = t yellow
blue :: String -> String blue :: S
blue str = blue str =
ANSI.setSGRCode [ANSI.SetConsoleIntensity ANSI.BoldIntensity] <> ANSI.setSGRCode [ANSI.SetConsoleIntensity ANSI.BoldIntensity] <>
ANSI.setSGRCode [ANSI.SetColor ANSI.Foreground ANSI.Vivid ANSI.Blue] <> ANSI.setSGRCode [ANSI.SetColor ANSI.Foreground ANSI.Vivid ANSI.Blue] <>
str <> ANSI.setSGRCode [ANSI.Reset] str <> ANSI.setSGRCode [ANSI.Reset]
tblue :: T.Text -> T.Text tblue :: T
tblue = dimap T.unpack T.pack blue tblue = t blue
red :: String -> String red :: S
red str = red str =
ANSI.setSGRCode [ANSI.SetColor ANSI.Foreground ANSI.Vivid ANSI.Red] <> ANSI.setSGRCode [ANSI.SetColor ANSI.Foreground ANSI.Vivid ANSI.Red] <>
str <> ANSI.setSGRCode [ANSI.Reset] str <> ANSI.setSGRCode [ANSI.Reset]
tbold :: T.Text -> T.Text tred :: T
tbold = dimap T.unpack T.pack bold tred = t red
bold :: String -> String bold :: S
bold str = bold str =
ANSI.setSGRCode [ANSI.SetConsoleIntensity ANSI.BoldIntensity] <> ANSI.setSGRCode [ANSI.SetConsoleIntensity ANSI.BoldIntensity] <>
ANSI.setSGRCode [ANSI.SetColor ANSI.Foreground ANSI.Vivid ANSI.White] <> ANSI.setSGRCode [ANSI.SetColor ANSI.Foreground ANSI.Vivid ANSI.White] <>
str <> ANSI.setSGRCode [ANSI.Reset] str <> ANSI.setSGRCode [ANSI.Reset]
tfaint :: T.Text -> T.Text tbold :: T
tfaint = dimap T.unpack T.pack faint tbold = t bold
faint :: String -> String faint :: String -> String
faint str = faint str =
ANSI.setSGRCode [ANSI.SetConsoleIntensity ANSI.FaintIntensity] <> ANSI.setSGRCode [ANSI.SetConsoleIntensity ANSI.FaintIntensity] <>
ANSI.setSGRCode [ANSI.SetColor ANSI.Foreground ANSI.Vivid ANSI.White] <> ANSI.setSGRCode [ANSI.SetColor ANSI.Foreground ANSI.Vivid ANSI.White] <>
str <> ANSI.setSGRCode [ANSI.Reset] str <> ANSI.setSGRCode [ANSI.Reset]
tfaint :: T
tfaint = t faint
t :: (String -> String) -> T.Text -> T.Text
t = dimap T.unpack T.pack