core-program-0.5.1.0: Opinionated Haskell Interoperability
Safe HaskellNone
LanguageHaskell2010

Core.Program.Execute

Description

Embelish a Haskell command-line program with useful behaviours.

Runtime

Sets number of capabilities (heavy-weight operating system threads used by the GHC runtime to run Haskell green threads) to the number of CPU cores available (for some reason the default is 1 capability only, which is a bit silly on a multicore system).

Install signal handlers to properly terminate the program performing cleanup as necessary.

Encoding is set to UTF-8, working around confusing bugs that sometimes occur when applications are running in Docker containers.

Logging and output

The Program monad provides functions for both normal output and debug logging. A common annoyance when building command line tools and daemons is getting program output to stdout and debug messages interleaved, made even worse when error messages written to stderr land in the same console. To avoid this, when all output is sent through a single channel. This includes both normal output and log messages.

Exceptions

Ideally your code should handle (and not leak) exceptions, as is good practice anywhere in the Haskell ecosystem. As a measure of last resort however, if an exception is thrown (and not caught) by your program it will be caught at the outer execute entrypoint, logged for debugging, and then your program will exit.

Customizing the execution context

The execute function will run your Program in a basic Context initialized with appropriate defaults. Most settings can be changed at runtime, but to specify the allowed command-line options and expected arguments you can initialize your program using configure and then run with executeWith.

Synopsis

Documentation

data Program τ α Source #

The type of a top-level program.

You would use this by writing:

module Main where

import Core.Program

main :: IO ()
main = execute program

and defining a program that is the top level of your application:

program :: Program None ()

Such actions are combinable; you can sequence them (using bind in do-notation) or run them in parallel, but basically you should need one such object at the top of your application.

Type variables

A Program has a user-supplied application state and a return type.

The first type variable, τ, is your application's state. This is an object that will be threaded through the computation and made available to your code in the Program monad. While this is a common requirement of the outer code layer in large programs, it is often not necessary in small programs or when starting new projects. You can mark that there is no top-level application state required using None and easily change it later if your needs evolve.

The return type, α, is usually unit as this effectively being called directly from main and Haskell programs have type IO (). That is, they don't return anything; I/O having already happened as side effects.

Programs in separate modules

One of the quirks of Haskell is that it is difficult to refer to code in the Main module when you've got a number of programs kicking around in a project each with a main function. One way of dealing with this is to put your top-level Program actions in a separate modules so you can refer to them from test suites and example snippets.

Interoperating with the rest of the Haskell ecosystem

The Program monad is a wrapper over IO; at any point when you need to move to another package's entry point, just use liftIO. It's re-exported by Core.System.Base for your convenience. Later, you might be interested in unlifting back to Program; see Core.Program.Unlift.

Instances

Instances details
Monad (Program τ) Source # 
Instance details

Defined in Core.Program.Context

Methods

(>>=) :: Program τ a -> (a -> Program τ b) -> Program τ b #

(>>) :: Program τ a -> Program τ b -> Program τ b #

return :: a -> Program τ a #

Functor (Program τ) Source # 
Instance details

Defined in Core.Program.Context

Methods

fmap :: (a -> b) -> Program τ a -> Program τ b #

(<$) :: a -> Program τ b -> Program τ a #

MonadFail (Program τ) Source # 
Instance details

Defined in Core.Program.Context

Methods

fail :: String -> Program τ a #

Applicative (Program τ) Source # 
Instance details

Defined in Core.Program.Context

Methods

pure :: a -> Program τ a #

(<*>) :: Program τ (a -> b) -> Program τ a -> Program τ b #

liftA2 :: (a -> b -> c) -> Program τ a -> Program τ b -> Program τ c #

(*>) :: Program τ a -> Program τ b -> Program τ b #

(<*) :: Program τ a -> Program τ b -> Program τ a #

MonadIO (Program τ) Source # 
Instance details

Defined in Core.Program.Context

Methods

liftIO :: IO a -> Program τ a #

MonadThrow (Program τ) Source # 
Instance details

Defined in Core.Program.Context

Methods

throwM :: Exception e => e -> Program τ a #

MonadCatch (Program τ) Source # 
Instance details

Defined in Core.Program.Context

Methods

catch :: Exception e => Program τ a -> (e -> Program τ a) -> Program τ a #

MonadMask (Program t) Source # 
Instance details

Defined in Core.Program.Context

Methods

mask :: ((forall a. Program t a -> Program t a) -> Program t b) -> Program t b #

uninterruptibleMask :: ((forall a. Program t a -> Program t a) -> Program t b) -> Program t b #

generalBracket :: Program t a -> (a -> ExitCase b -> Program t c) -> (a -> Program t b) -> Program t (b, c) #

MonadReader (Context τ) (Program τ) Source # 
Instance details

Defined in Core.Program.Context

Methods

ask :: Program τ (Context τ) #

local :: (Context τ -> Context τ) -> Program τ a -> Program τ a #

reader :: (Context τ -> a) -> Program τ a #

Running programs

configure :: Version -> τ -> Config -> IO (Context τ) Source #

Initialize the programs's execution context. This takes care of various administrative actions, including setting up output channels, parsing command-line arguments (according to the supplied configuration), and putting in place various semaphores for internal program communication. See Core.Program.Arguments for details.

This is also where you specify the initial {blank, empty, default) value for the top-level user-defined application state, if you have one. Specify None if you aren't using this feature.

execute :: Program None α -> IO () Source #

Embelish a program with useful behaviours. See module header Core.Program.Execute for a detailed description. Internally this function calls configure with an appropriate default when initializing.

executeWith :: Context τ -> Program τ α -> IO () Source #

Embelish a program with useful behaviours, supplying a configuration for command-line options & argument parsing and an initial value for the top-level application state, if appropriate.

Exiting a program

terminate :: Int -> Program τ α Source #

Safely exit the program with the supplied exit code. Current output and debug queues will be flushed, and then the process will terminate.

Accessing program context

getCommandLine :: Program τ Parameters Source #

Retrieve the values of parameters parsed from options and arguments supplied by the user on the command-line.

The command-line parameters are returned in a Map, mapping from from the option or argument name to the supplied value. You can query this map directly:

program = do
    params <- getCommandLine
    let result = lookupKeyValue "silence" (paramterValuesFrom params)
    case result of
        Nothing -> return ()
        Just quiet = case quiet of
            Value _ -> throw NotQuiteRight                 -- complain that flag doesn't take value
            Empty   -> write "You should be quiet now"   -- much better
    ...

which is pattern matching to answer "was this option specified by the user?" or "what was the value of this [mandatory] argument?", and then "if so, did the parameter have a value?"

This is available should you need to differentiate between a Value and an Empty ParameterValue, but for many cases as a convenience you can use the queryOptionFlag, queryOptionValue, and queryArgument functions below.

queryCommandName :: Program τ Rope Source #

Retreive the sub-command mode selected by the user. This assumes your program was set up to take sub-commands via complexConfig.

    mode <- queryCommandName

Since: 0.3.5

queryOptionFlag :: LongName -> Program τ Bool Source #

Returns True if the option is present, and False if it is not.

program = do
    overwrite <- queryOptionFlag "overwrite"
    ...

Since: 0.3.5

queryOptionValue :: LongName -> Program τ (Maybe Rope) Source #

Look to see if the user supplied a valued option and if so, what its value was. Use of the LambdaCase extension makes accessing the option (and specifying a default if it is absent) reasonably nice:

program = do
    region <- queryOptionValue "region" >>= \case
        Nothing -> pure "us-west-2" -- Oregon, not a bad default
        Just value -> pure value

If you require something other than the text value as entered by the user you'll need to do something to parse the returned value and convert it to an appropriate type See queryOptionValue' for an alternative that does this automatically in many common cases, i.e. for options that take numberic values.

Since: 0.3.5

queryOptionValue' :: Externalize ξ => LongName -> Program τ (Maybe ξ) Source #

Look to see if the user supplied a valued option and if so, what its value was. This covers the common case of wanting to read a numeric argument from an option:

program = do
    count <- queryOptionValue' "count" >>= \case
        Nothing -> pure (0 :: Int)
        Just value -> pure value
    ...

The return type of this function has the same semantics as queryOptionValue: if the option is absent you get Nothing back (and in the example above we specify a default in that case) and Just if a value is present. Unlike the original function, however, here we assume success in reading the value! If the value is unable to be parsed into the nominated Haskell type using parseExternal then an exception with an appropriate error message will be thrown­—which is what you want if the user specifies something that can't be parsed.

Note that the return type is polymorphic so you'll need to ensure the concrete type you actually want is specified either via type inference or by adding a type annotation somewhere.

Since: 0.5.1

queryArgument :: LongName -> Program τ Rope Source #

Arguments are mandatory, so by the time your program is running a value has already been identified. This retreives the value for that parameter.

program = do
    file <- queryArgument "filename"
    ...

Since: 0.2.7

queryRemaining :: Program τ [Rope] Source #

In other applications, you want to gather up the remaining arguments on the command-line. You need to have specified Remaining in the configuration.

program = do
    files <- queryRemaining
    ...

Since: 0.3.5

queryEnvironmentValue :: LongName -> Program τ (Maybe Rope) Source #

Look to see if the user supplied the named environment variable and if so, return what its value was.

Since: 0.3.5

getProgramName :: Program τ Rope Source #

Get the program name as invoked from the command-line (or as overridden by setProgramName).

setProgramName :: Rope -> Program τ () Source #

Override the program name used for logging, etc. At least, that was the idea. Nothing makes use of this at the moment. :/

setVerbosityLevel :: Verbosity -> Program τ () Source #

Change the verbosity level of the program's logging output. This changes whether info and the debug family of functions emit to the logging stream; they do not affect writeing to the terminal on the standard output stream.

getConsoleWidth :: Program τ Int Source #

Retreive the current terminal's width, in characters.

If you are outputting an object with a Render instance then you may not need this; you can instead use writeR which is aware of the width of your terminal and will reflow (in as much as the underlying type's Render instance lets it).

getApplicationState :: Program τ τ Source #

Get the user supplied application state as originally supplied to configure and modified subsequntly by replacement with setApplicationState.

    settings <- getApplicationState

setApplicationState :: τ -> Program τ () Source #

Update the user supplied top-level application state.

    let settings' = settings { answer = 42 }
    setApplicationState settings'

Useful actions

outputEntire :: Handle -> Bytes -> Program τ () Source #

Write the supplied Bytes to the given Handle. Note that in contrast to write we don't output a trailing newline.

    outputEntire h b

Do not use this to output to stdout as that would bypass the mechanism used by the write*, info, and debug* functions to sequence output correctly. If you wish to write to the terminal use:

    write (intoRope b)

(which is not unsafe, but will lead to unexpected results if the binary blob you pass in is other than UTF-8 text).

inputEntire :: Handle -> Program τ Bytes Source #

Read the (entire) contents of the specified Handle.

execProcess :: [Rope] -> Program τ (ExitCode, Rope, Rope) Source #

Execute an external child process and wait for its output and result. The command is specified first and and subsequent arguments as elements of the list. This helper then logs the command being executed to the debug output, which can be useful when you're trying to find out what exactly what program is being invoked.

Keep in mind that this isn't invoking a shell; arguments and their values have to be enumerated separately:

    execProcess ["/usr/bin/ssh", "-l", "admin", "203.0.113.42", "\'remote command here\'"]

having to write out the individual options and arguments and deal with escaping is a bit of an annoyance but that's execvp(3) for you.

The return tuple is the exit code from the child process, its entire stdout and its entire stderr, if any. Note that this is not a streaming interface, so if you're doing something that returns huge amounts of output you'll want to use something like io-streams instead.

(this wraps typed-process's readProcess)

sleepThread :: Rational -> Program τ () Source #

Pause the current thread for the given number of seconds. For example, to delay a second and a half, do:

    sleepThread 1.5

(this wraps base's threadDelay)

resetTimer :: Program τ () Source #

Reset the start time (used to calculate durations shown in event- and debug-level logging) held in the Context to zero. This is useful if you want to see the elapsed time taken by a specific worker rather than seeing log entries relative to the program start time which is the default.

If you want to start time held on your main program thread to maintain a count of the total elapsed program time, then fork a new thread for your worker and reset the timer there.

    forkThread $ do
        resetTimer
        ...

then times output in the log messages will be relative to that call to resetTimer, not the program start.

Since: 0.2.7

trap_ :: Program τ α -> Program τ () Source #

Trap any exceptions coming out of the given Program action, and discard them. The one and only time you want this is inside an endless loop:

    forever $ do
        trap_
            ( bracket
                obtainResource
                releaseResource
                useResource
            )

This function really will swollow expcetions, which means that you'd better have handled any synchronous checked errors already with a catch and/or have released resources with bracket or finally as shown above.

An info level message will be sent to the log channel indicating that an uncaught exception was trapped along with a debug level message showing the exception text, if any.

Since: 0.2.11

Exception handling

catch :: Exception ε => Program τ α -> (ε -> Program τ α) -> Program τ α Source #

Catch an exception.

Some care must be taken. Remember that even though it is constrained by the Exception typeclass, ε does not stand for "any" exception type; is has a concrete type when it gets to being used in your code. Things are fairly straight-forward if you know exactly the exception you are looking for:

    catch
        action
        (\(e :: FirstWorldProblem) -> do
            ...
        )

but more awkward when you don't.

If you just need to catch all exceptions, the pattern for that is as follows:

    catch
        action
        (\(e :: SomeException) -> do
            ...
        )

The SomeException type is the root type of all exceptions; or rather, all types that have an instance of Exception can be converted into this root type. Thus you can catch all synchronous exceptions but you can't tell which type of exception it was originally; you rely on the Show instance (which is the default that displayException falls back to) to display a message which will hopefully be of enough utility to figure out what the problem is. In fairness it usually is. (This all seems a bit of a deficiency in the underlying exception machinery but it's what we have)

This catch function will not catch asynchonous exceptions. If you need to do that, see the more comprehensive exception handling facilities offered by safe-exceptions, which in turn builds on exceptions and base). Note that Program implements MonadCatch so you can use the full power available there if required.

Since: 0.5.0

throw :: Exception ε => ε -> Program τ α Source #

Throw an exception.

This will be thrown as a normal synchronous exception that can be caught with catch or try above.

Don't try and use this from pure code! A common temptation is to be in the middle of a computation, hit a problem, and think "oh, that's bad. I guess I'll throw an exception!". You can't. Surface the problem back to the I/O level code that Program τ monad provides, and then you can throw an exception if appropriate.

When you do throw an exception, we recommend you go to some trouble to make sure that the string or otherwise descriptive message is unique in your codebase. If you do so then when the problem arises you will be able to quickly search for that string and find the place where the exception arose from, even without the benefit of stack traces. For example,

    throw (SomeoneWrongOnInternet "Ashley thinks there are more than three Star Wars movies")

which will get you a nice crash message as your world falls down around you:

22:54:39Z (00.002) SomeoneWrongOnInternet "Ashley thinks there are more than three Star Wars movies"
$

but if you're in a hurry and don't want to define a local exception type to use,

    throw Boom

will work.

(experienced users will note that Program implements MonadThrow and as such this is just a wrapper around calling safe-exceptions's throw function)

Since: 0.5.0

try :: Exception ε => Program τ α -> Program τ (Either ε α) Source #

Catch an exception. Instead of handling an exception in a supplied function, however, return from executing the sub-program with the outcome in an Either, with the exception being on the Left side if one is thrown. If the sub-program completes normally its result is in the Right side.

(this is a wrapper around calling safe-exceptions's try function, which in turn wraps exceptions's try, which...)

Since: 0.5.0

Internals

data Context τ Source #

Internal context for a running program. You access this via actions in the Program monad. The principal item here is the user-supplied top-level application data of type τ which can be retrieved with getApplicationState and updated with setApplicationState.

Instances

Instances details
Functor Context Source # 
Instance details

Defined in Core.Program.Context

Methods

fmap :: (a -> b) -> Context a -> Context b #

(<$) :: a -> Context b -> Context a #

MonadReader (Context τ) (Program τ) Source # 
Instance details

Defined in Core.Program.Context

Methods

ask :: Program τ (Context τ) #

local :: (Context τ -> Context τ) -> Program τ a -> Program τ a #

reader :: (Context τ -> a) -> Program τ a #

data None Source #

A Program with no user-supplied state to be threaded throughout the computation.

The Core.Program.Execute framework makes your top-level application state available at the outer level of your process. While this is a feature that most substantial programs rely on, it is not needed for many simple tasks or when first starting out what will become a larger project.

This is effectively the unit type, but this alias is here to clearly signal a user-data type is not a part of the program semantics.

Constructors

None 

Instances

Instances details
Eq None Source # 
Instance details

Defined in Core.Program.Context

Methods

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

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

Show None Source # 
Instance details

Defined in Core.Program.Context

Methods

showsPrec :: Int -> None -> ShowS #

show :: None -> String #

showList :: [None] -> ShowS #

invalid :: Program τ α Source #

Illegal internal state resulting from what should be unreachable code or otherwise a programmer error.

data Boom Source #

A utility exception for those occasions when you just need to go "boom".

    case containsKey "James Bond" agents of
        False -> do
            evilPlan
        True ->  do
            write "No Mr Bond, I expect you to die!"
            throw Boom

Since: 0.3.2

Constructors

Boom 

Instances

Instances details
Show Boom Source # 
Instance details

Defined in Core.Program.Exceptions

Methods

showsPrec :: Int -> Boom -> ShowS #

show :: Boom -> String #

showList :: [Boom] -> ShowS #

Exception Boom Source # 
Instance details

Defined in Core.Program.Exceptions