core-program-0.2.5.0: Opinionated Haskell Interoperability

Safe HaskellNone
LanguageHaskell2010

Core.Program.Execute

Contents

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. So you're best off putting your top-level Program actions in a separate modules so you can refer to them from test suites and example snippets.

Instances
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 #

fail :: String -> 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 #

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 #

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 lookupOptionFlag, lookupOptionValue, and lookupArgument functions below (which are just wrappers around a code block like the example shown here).

lookupOptionFlag :: LongName -> Parameters -> Maybe Bool Source #

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

lookupOptionValue :: LongName -> Parameters -> Maybe String Source #

Look to see if the user supplied a valued option and if so, what its value was.

lookupArgument :: LongName -> Parameters -> Maybe String Source #

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

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 event 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 wrteR 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.

    state <- getApplicationState

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

Update the user supplied top-level application state.

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

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

Useful actions

output :: 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.

    output h b

Do not use this to output to stdout as that would bypass the mechanism used by the write*, event, 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).

input :: Handle -> Program τ Bytes Source #

Read the (entire) contents of the specified Handle.

Concurrency

data Thread α Source #

A thread for concurrent computation. Haskell uses green threads: small lines of work that are scheduled down onto actual execution contexts, set by default by this library to be one per core. They are incredibly lightweight, and you are encouraged to use them freely. Haskell provides a rich ecosystem of tools to do work concurrently and to communicate safely between threads

(this wraps async's Async)

fork :: Program τ α -> Program τ (Thread α) Source #

Fork a thread. The child thread will run in the same Context as the calling Program, including sharing the user-defined application state type.

(this wraps async's async which in turn wraps base's forkIO)

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

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

    sleep 1.5

(this wraps base's threadDelay)

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
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
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.