{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Cli.Extras.Logging
( AsUnstructuredError (..)
, newCliConfig
, mkDefaultCliConfig
, runCli
, verboseLogLevel
, isOverwrite
, getSeverity
, getLogLevel
, setLogLevel
, putLog
, putLogRaw
, failWith
, withExitFailMessage
, writeLog
, allowUserToMakeLoggingVerbose
, getChars
, handleLog
) where
import Control.Concurrent (forkIO, killThread, threadDelay)
import Control.Concurrent.MVar (modifyMVar_, newMVar)
import Control.Lens (Prism', review)
import Control.Monad (unless, void, when)
import Control.Monad.Catch (MonadCatch, MonadMask, bracket, catch, throwM)
import Control.Monad.Except (runExceptT, throwError)
import Control.Monad.IO.Class (liftIO)
import Control.Monad.Log (Severity (..), WithSeverity (..), logMessage, runLoggingT)
import Control.Monad.Loops (iterateUntil)
import Control.Monad.Reader (MonadIO, ReaderT (..))
import Data.IORef (atomicModifyIORef', newIORef, readIORef, writeIORef)
import Data.List (isInfixOf)
import Data.Semigroup ((<>))
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.IO as T
import GHC.IO.Encoding.Types
import System.Console.ANSI (Color (Red, Yellow), ColorIntensity (Vivid),
ConsoleIntensity (FaintIntensity), ConsoleLayer (Foreground),
SGR (SetColor, SetConsoleIntensity), clearLine)
import System.Environment
import System.Exit (ExitCode (..))
import System.IO
import qualified Cli.Extras.TerminalString as TS
import Cli.Extras.Theme
import Cli.Extras.Types
putLog :: CliLog m => Severity -> Text -> m ()
putLog sev = logMessage . Output_Log . WithSeverity sev
putLog' :: CliConfig -> Severity -> Text -> IO ()
putLog' conf sev t = runLoggingT (putLog sev t) (handleLog conf)
mkDefaultCliConfig :: [String] -> IO CliConfig
mkDefaultCliConfig cliArgs = do
let logLevel = if any (`elem` ["-v", "--verbose"]) cliArgs then Debug else Notice
notInteractive <- not <$> isInteractiveTerm
cliConf <- newCliConfig logLevel notInteractive notInteractive
return cliConf
where
isInteractiveTerm = do
isTerm <- hIsTerminalDevice stdout
let inShellCompletion = isInfixOf "completion" $ unwords cliArgs
termEnv <- lookupEnv "TERM"
let isDumb = termEnv == Just "dumb"
return $ isTerm && not inShellCompletion && not isDumb
newCliConfig
:: Severity
-> Bool
-> Bool
-> IO (CliConfig)
newCliConfig sev noColor noSpinner = do
level <- newIORef sev
lock <- newMVar False
tipDisplayed <- newIORef False
stack <- newIORef ([], [])
textEncoding <- hGetEncoding stdout
let theme = if maybe False supportsUnicode textEncoding
then unicodeTheme
else noUnicodeTheme
return $ CliConfig level noColor noSpinner lock tipDisplayed stack theme
runCli :: MonadIO m => CliConfig -> CliT e m a -> m (Either e a)
runCli c =
runExceptT
. flip runLoggingT (handleLog c)
. flip runReaderT c
. unCliT
verboseLogLevel :: Severity
verboseLogLevel = Debug
isOverwrite :: Output -> Bool
isOverwrite = \case
Output_Overwrite _ -> True
_ -> False
getSeverity :: Output -> Maybe Severity
getSeverity = \case
Output_Log (WithSeverity sev _) -> Just sev
Output_LogRaw (WithSeverity sev _) -> Just sev
_ -> Nothing
getLogLevel :: (MonadIO m, HasCliConfig m) => m Severity
getLogLevel = getLogLevel' =<< getCliConfig
getLogLevel' :: MonadIO m => CliConfig -> m Severity
getLogLevel' = liftIO . readIORef . _cliConfig_logLevel
setLogLevel :: (MonadIO m, HasCliConfig m) => Severity -> m ()
setLogLevel sev = do
conf <- getCliConfig
setLogLevel' conf sev
setLogLevel' :: MonadIO m => CliConfig -> Severity -> m ()
setLogLevel' conf sev = liftIO $ writeIORef (_cliConfig_logLevel conf) sev
handleLog :: MonadIO m => CliConfig -> Output -> m ()
handleLog conf output = do
level <- getLogLevel' conf
liftIO $ modifyMVar_ (_cliConfig_lock conf) $ \wasOverwriting -> do
let noColor = _cliConfig_noColor conf
case getSeverity output of
Nothing -> handleLog' noColor output
Just sev -> if sev > level
then return wasOverwriting
else do
when wasOverwriting $
void $ handleLog' noColor Output_ClearLine
handleLog' noColor output
handleLog' :: MonadIO m => Bool -> Output -> m Bool
handleLog' noColor output = do
case output of
Output_Log m -> liftIO $ do
writeLog True noColor m
Output_LogRaw m -> liftIO $ do
writeLog False noColor m
hFlush stdout
Output_Write ts -> liftIO $ do
T.putStrLn $ TS.render (not noColor) Nothing ts
hFlush stdout
Output_Overwrite ts -> liftIO $ do
width <- TS.getTerminalWidth
T.putStr $ "\r" <> TS.render (not noColor) width ts
hFlush stdout
Output_ClearLine -> liftIO $ do
putStr "\r"
clearLine
hFlush stdout
return $ isOverwrite output
putLogRaw :: CliLog m => Severity -> Text -> m ()
putLogRaw sev = logMessage . Output_LogRaw . WithSeverity sev
class AsUnstructuredError e where
asUnstructuredError :: Prism' e Text
instance AsUnstructuredError Text where
asUnstructuredError = id
failWith :: (CliThrow e m, AsUnstructuredError e) => Text -> m a
failWith = throwError . review asUnstructuredError
withExitFailMessage :: (CliLog m, MonadCatch m) => Text -> m a -> m a
withExitFailMessage msg f = f `catch` \(e :: ExitCode) -> do
case e of
ExitFailure _ -> putLog Alert msg
ExitSuccess -> pure ()
throwM e
writeLog :: (MonadIO m, MonadMask m) => Bool -> Bool -> WithSeverity Text -> m ()
writeLog withNewLine noColor (WithSeverity severity s) = if T.null s then pure () else write
where
write
| noColor && severity <= Warning = liftIO $ putFn $ T.pack (show severity) <> ": " <> s
| not noColor && severity <= Error = TS.putStrWithSGR errorColors h withNewLine s
| not noColor && severity <= Warning = TS.putStrWithSGR warningColors h withNewLine s
| not noColor && severity >= Debug = TS.putStrWithSGR debugColors h withNewLine s
| otherwise = liftIO $ putFn s
putFn = if withNewLine then T.hPutStrLn h else T.hPutStr h
h = if severity <= Error then stderr else stdout
errorColors = [SetColor Foreground Vivid Red]
warningColors = [SetColor Foreground Vivid Yellow]
debugColors = [SetConsoleIntensity FaintIntensity]
allowUserToMakeLoggingVerbose
:: CliConfig
-> String
-> IO ()
allowUserToMakeLoggingVerbose conf keyCode = do
let unlessVerbose f = do
l <- getLogLevel' conf
unless (l == verboseLogLevel) f
showTip = liftIO $ forkIO $ unlessVerbose $ do
liftIO $ threadDelay $ 10*1000000
tipDisplayed <- liftIO $ atomicModifyIORef' (_cliConfig_tipDisplayed conf) $ (,) True
unless tipDisplayed $ unlessVerbose $ do
putLog' conf Notice "Tip: Press Ctrl+e to display full output"
bracket showTip (liftIO . killThread) $ \_ -> do
unlessVerbose $ do
hSetBuffering stdin NoBuffering
_ <- iterateUntil (== keyCode) getChars
putLog' conf Warning "Ctrl+e pressed; making output verbose (-v)"
setLogLevel' conf verboseLogLevel
getChars :: IO String
getChars = reverse <$> f mempty
where
f xs = do
x <- getChar
hReady stdin >>= \case
True -> f (x:xs)
False -> return (x:xs)
supportsUnicode :: TextEncoding -> Bool
supportsUnicode enc = any ((textEncodingName enc ==) . textEncodingName)
[ utf8
, utf8_bom
, utf16
, utf16be
, utf16le
, utf32
, utf32be
, utf32le
]