cli-extras-0.2.0.0: Miscellaneous utilities for building and working with command line interfaces
Safe HaskellNone
LanguageHaskell2010

Cli.Extras

Description

|

Synopsis

Documentation

type CliThrow e m = MonadError e m Source #

newtype CliT e m a Source #

Constructors

CliT 

Fields

Instances

Instances details
MonadIO m => MonadError e (CliT e m) Source # 
Instance details

Defined in Cli.Extras.Types

Methods

throwError :: e -> CliT e m a #

catchError :: CliT e m a -> (e -> CliT e m a) -> CliT e m a #

Monad m => MonadLog Output (CliT e m) Source # 
Instance details

Defined in Cli.Extras.Types

Methods

logMessageFree :: (forall n. Monoid n => (Output -> n) -> n) -> CliT e m () #

Monad m => HasCliConfig e (CliT e m) Source # 
Instance details

Defined in Cli.Extras.Types

Methods

getCliConfig :: CliT e m (CliConfig e) Source #

MonadTrans (CliT e) Source # 
Instance details

Defined in Cli.Extras.Types

Methods

lift :: Monad m => m a -> CliT e m a #

Monad m => MonadReader (CliConfig e) (CliT e m) Source # 
Instance details

Defined in Cli.Extras.Types

Methods

ask :: CliT e m (CliConfig e) #

local :: (CliConfig e -> CliConfig e) -> CliT e m a -> CliT e m a #

reader :: (CliConfig e -> a) -> CliT e m a #

Monad m => Monad (CliT e m) Source # 
Instance details

Defined in Cli.Extras.Types

Methods

(>>=) :: CliT e m a -> (a -> CliT e m b) -> CliT e m b #

(>>) :: CliT e m a -> CliT e m b -> CliT e m b #

return :: a -> CliT e m a #

Functor m => Functor (CliT e m) Source # 
Instance details

Defined in Cli.Extras.Types

Methods

fmap :: (a -> b) -> CliT e m a -> CliT e m b #

(<$) :: a -> CliT e m b -> CliT e m a #

MonadFail m => MonadFail (CliT e m) Source # 
Instance details

Defined in Cli.Extras.Types

Methods

fail :: String -> CliT e m a #

Applicative m => Applicative (CliT e m) Source # 
Instance details

Defined in Cli.Extras.Types

Methods

pure :: a -> CliT e m a #

(<*>) :: CliT e m (a -> b) -> CliT e m a -> CliT e m b #

liftA2 :: (a -> b -> c) -> CliT e m a -> CliT e m b -> CliT e m c #

(*>) :: CliT e m a -> CliT e m b -> CliT e m b #

(<*) :: CliT e m a -> CliT e m b -> CliT e m a #

MonadIO m => MonadIO (CliT e m) Source # 
Instance details

Defined in Cli.Extras.Types

Methods

liftIO :: IO a -> CliT e m a #

MonadThrow m => MonadThrow (CliT e m) Source # 
Instance details

Defined in Cli.Extras.Types

Methods

throwM :: Exception e0 => e0 -> CliT e m a #

MonadCatch m => MonadCatch (CliT e m) Source # 
Instance details

Defined in Cli.Extras.Types

Methods

catch :: Exception e0 => CliT e m a -> (e0 -> CliT e m a) -> CliT e m a #

MonadMask m => MonadMask (CliT e m) Source # 
Instance details

Defined in Cli.Extras.Types

Methods

mask :: ((forall a. CliT e m a -> CliT e m a) -> CliT e m b) -> CliT e m b #

uninterruptibleMask :: ((forall a. CliT e m a -> CliT e m a) -> CliT e m b) -> CliT e m b #

generalBracket :: CliT e m a -> (a -> ExitCase b -> CliT e m c) -> (a -> CliT e m b) -> CliT e m (b, c) #

runCli :: MonadIO m => CliConfig e -> CliT e m a -> m a Source #

data CliConfig e Source #

Instances

Instances details
Monad m => MonadReader (CliConfig e) (CliT e m) Source # 
Instance details

Defined in Cli.Extras.Types

Methods

ask :: CliT e m (CliConfig e) #

local :: (CliConfig e -> CliConfig e) -> CliT e m a -> CliT e m a #

reader :: (CliConfig e -> a) -> CliT e m a #

class Monad m => HasCliConfig e m | m -> e Source #

Minimal complete definition

getCliConfig

Instances

Instances details
Monad m => HasCliConfig e (CliT e m) Source # 
Instance details

Defined in Cli.Extras.Types

Methods

getCliConfig :: CliT e m (CliConfig e) Source #

HasCliConfig e m => HasCliConfig e (ExceptT e m) Source # 
Instance details

Defined in Cli.Extras.Types

HasCliConfig e m => HasCliConfig e (StateT s m) Source # 
Instance details

Defined in Cli.Extras.Types

(Monoid w, HasCliConfig e m) => HasCliConfig e (WriterT w m) Source # 
Instance details

Defined in Cli.Extras.Types

HasCliConfig e m => HasCliConfig e (ReaderT r m) Source # 
Instance details

Defined in Cli.Extras.Types

data Output Source #

Instances

Instances details
Eq Output Source # 
Instance details

Defined in Cli.Extras.Types

Methods

(==) :: Output -> Output -> Bool #

(/=) :: Output -> Output -> Bool #

Ord Output Source # 
Instance details

Defined in Cli.Extras.Types

Show Output Source # 
Instance details

Defined in Cli.Extras.Types

Monad m => MonadLog Output (CliT e m) Source # 
Instance details

Defined in Cli.Extras.Types

Methods

logMessageFree :: (forall n. Monoid n => (Output -> n) -> n) -> CliT e m () #

Monad m => MonadLog Output (DieT e m) Source # 
Instance details

Defined in Cli.Extras.Types

Methods

logMessageFree :: (forall n. Monoid n => (Output -> n) -> n) -> DieT e m () #

withSpinner :: (MonadIO m, MonadMask m, CliLog m, HasCliConfig e m) => Text -> m a -> m a Source #

Run an action with a CLI spinner.

withSpinnerNoTrail :: (MonadIO m, MonadMask m, CliLog m, HasCliConfig e m) => Text -> m a -> m a Source #

A spinner that leaves no trail after a successful run.

Use if you wish the spinner to be ephemerally visible to the user.

The 'no trail' property automatically carries over to sub-spinners (in that they won't leave a trail either).

withSpinner' Source #

Arguments

:: (MonadIO m, MonadMask m, CliLog m, HasCliConfig e m) 
=> Text 
-> Maybe (a -> Text)

Leave an optional trail with the given message creator

-> m a 
-> m a 

Advanced version that controls the display and content of the trail message.

class AsUnstructuredError e where Source #

Indicates unstructured errors form one variant (or conceptual projection) of the error type.

Shouldn't really use this, but who has time to clean up that much!

Instances

Instances details
AsUnstructuredError Text Source # 
Instance details

Defined in Cli.Extras.Logging

newCliConfig Source #

Arguments

:: Severity

The initial log level. Messages below this severity will not be logged, unless the log level is subsequently altered using setLogLevel.

-> Bool

Should ANSI terminal formatting be disabled?

-> Bool

Should spinners be disabled?

-> (e -> (Text, ExitCode))

How to display errors, and compute the ExitCode corresponding to each error.

-> IO (CliConfig e) 

Create a new CliConfig, initialized with the provided values.

putLog :: CliLog m => Severity -> Text -> m () Source #

Log a message to the console.

The message is guaranteed to be logged uninterrupted, even if there are ongoing spinners.

failWith :: (CliThrow e m, AsUnstructuredError e) => Text -> m a Source #

Like `putLog Alert` but also abrupts the program.

errorToWarning :: (HasCliConfig e m, CliLog m) => e -> m () Source #

Log an error as though it were a warning, in a non-fatal way.

withExitFailMessage :: (CliLog m, MonadCatch m) => Text -> m a -> m a Source #

Intercept ExitFailure exceptions and log the given alert before exiting.

This is useful when you want to provide contextual information to a deeper failure.

data Severity #

Classes of severity for log messages. These have been chosen to match syslog severity levels

Constructors

Emergency

System is unusable. By syslog convention, this level should not be used by applications.

Alert

Should be corrected immediately.

Critical

Critical conditions.

Error

Error conditions.

Warning

May indicate that an error will occur if action is not taken.

Notice

Events that are unusual, but not error conditions.

Informational

Normal operational messages that require no action.

Debug

Information useful to developers for debugging the application.

Instances

Instances details
Bounded Severity 
Instance details

Defined in Control.Monad.Log

Enum Severity 
Instance details

Defined in Control.Monad.Log

Eq Severity 
Instance details

Defined in Control.Monad.Log

Ord Severity 
Instance details

Defined in Control.Monad.Log

Read Severity 
Instance details

Defined in Control.Monad.Log

Show Severity 
Instance details

Defined in Control.Monad.Log

Pretty Severity 
Instance details

Defined in Control.Monad.Log

Methods

pretty :: Severity -> Doc ann #

prettyList :: [Severity] -> Doc ann #

class AsProcessFailure e where Source #

Indicates arbitrary process failures form one variant (or conceptual projection) of the error type.

Instances

Instances details
AsProcessFailure ProcessFailure Source # 
Instance details

Defined in Cli.Extras.Process

callCommand :: (MonadIO m, CliLog m) => String -> m () Source #

Like callCommand, but logging (with Debug severity) the process which was started.

callProcess :: (MonadIO m, CliLog m) => String -> [String] -> m () Source #

Like callProcess, but logging (with Debug severity) the process which was started.

callProcessAndLogOutput Source #

Arguments

:: (MonadIO m, CliLog m, CliThrow e m, AsProcessFailure e, MonadMask m) 
=> (Severity, Severity)

This tuple controls the severity of each output stream. Its fst is the severity of stdout; snd is the severity of stderr.

-> ProcessSpec 
-> m () 

Like readProcess, but such that each of the child processes' standard output streams (stdout and stderr) is logged, with the corresponding severity.

Usually, this function is called as callProcessAndLogOutput (Debug, Error). If the child process is known to print diagnostic or informative messages to stderr, it is advisable to call callProcessAndLogOutput with a non-Error severity for stderr, for example callProcessAndLogOutput (Debug, Debug).

createProcess :: (MonadIO m, CliLog m) => ProcessSpec -> m (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) Source #

Like createProcess, but logging (with Debug severity) the process which was started.

createProcess_ :: (MonadIO m, CliLog m) => String -> ProcessSpec -> m (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) Source #

Like createProcess_, but logging (with Debug severity) the process which was started.

throwExitCode :: (CliThrow e m, AsProcessFailure e) => ProcessSpec -> ExitCode -> m () Source #

Aborts the computation (using throwError) when given a non-ExitSuccess ExitCode.

readProcessAndLogOutput Source #

Arguments

:: (MonadIO m, CliLog m, CliThrow e m, AsProcessFailure e, MonadFail m) 
=> (Severity, Severity)

This tuple controls the severity of each output stream. Its fst is the severity of stdout; snd is the severity of stderr.

-> ProcessSpec 
-> m Text 

Like readProcess, but such that each of the child processes' standard output streams (stdout and stderr) is logged, with the corresponding severity.

Usually, this function is called as readProcessAndLogOutput (Debug, Error). If the child process is known to print diagnostic or informative messages to stderr, it is advisable to call readProcessAndLogOutput with a non-Error severity for stderr, for example readProcessAndLogOutput (Debug, Debug).

reconstructCommand :: CmdSpec -> Text Source #

Pretty print a CmdSpec

runProcess_ :: (MonadIO m, CliLog m, CliThrow e m, MonadMask m, AsProcessFailure e) => ProcessSpec -> m () Source #

Runs a process to completion, aborting the computation (using throwExitCode) in case of a non-ExitSuccess exit status.