Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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
- data Program τ α
- configure :: Version -> τ -> Config -> IO (Context τ)
- execute :: Program None α -> IO ()
- executeWith :: Context τ -> Program τ α -> IO ()
- terminate :: Int -> Program τ α
- getCommandLine :: Program τ Parameters
- queryCommandName :: Program τ Rope
- queryOptionFlag :: LongName -> Program τ Bool
- queryOptionValue :: LongName -> Program τ (Maybe Rope)
- queryOptionValue' :: Externalize ξ => LongName -> Program τ (Maybe ξ)
- queryArgument :: LongName -> Program τ Rope
- queryRemaining :: Program τ [Rope]
- queryEnvironmentValue :: LongName -> Program τ (Maybe Rope)
- queryEnvironmentValue' :: Externalize ξ => LongName -> Program τ (Maybe ξ)
- getProgramName :: Program τ Rope
- setProgramName :: Rope -> Program τ ()
- setVerbosityLevel :: Verbosity -> Program τ ()
- getConsoleWidth :: Program τ Int
- getApplicationState :: Program τ τ
- setApplicationState :: τ -> Program τ ()
- modifyApplicationState :: (τ -> Program τ τ) -> Program τ ()
- changeProgram :: υ -> Program υ α -> Program τ α
- outputEntire :: Handle -> Bytes -> Program τ ()
- inputEntire :: Handle -> Program τ Bytes
- sleepThread :: Rational -> Program τ ()
- resetTimer :: Program τ ()
- trap_ :: Program τ α -> Program τ ()
- catch :: Exception ε => Program τ α -> (ε -> Program τ α) -> Program τ α
- throw :: Exception ε => ε -> Program τ α
- try :: Exception ε => Program τ α -> Program τ (Either ε α)
- readProcess :: [Rope] -> Program τ (ExitCode, Rope, Rope)
- callProcess :: [Rope] -> Program τ ExitCode
- execProcess_ :: [Rope] -> Program τ ()
- data Context τ
- data None = None
- invalid :: HasCallStack => Program τ α
- data Boom = Boom
Documentation
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
. That is, they
don't return anything; I/O having already happened as side effects.IO
()
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
MonadFail (Program τ) Source # | |
Defined in Core.Program.Context | |
MonadIO (Program τ) Source # | |
Defined in Core.Program.Context | |
Applicative (Program τ) Source # | |
Functor (Program τ) Source # | |
Monad (Program τ) Source # | |
MonadCatch (Program τ) Source # | |
MonadMask (Program t) Source # | |
Defined in Core.Program.Context | |
MonadThrow (Program τ) Source # | |
Defined in Core.Program.Context | |
MonadUnliftIO (Program τ) Source # | |
Defined in Core.Program.Context | |
MonadReader (Context τ) (Program τ) Source # | |
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. This function does not return.
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 ofNothing
->return
()Just
quiet = case quiet ofValue
_ ->throw
NotQuiteRight -- complain that flag doesn't take valueEmpty
->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">>=
\caseNothing
->pure
"us-west-2" -- Oregon, not a bad defaultJust
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">>=
\caseNothing
->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
queryEnvironmentValue' :: Externalize ξ => LongName -> Program τ (Maybe ξ) Source #
Look to see if the user supplied the named environment variable and if so, return what its value was.
Like queryOptionValue'
above, this function attempts to parse the supplied
value as Just
the inferred type. This makes the assumption that the
requested environment variable is populated. If it is not set in the
environment, or is set to the empty string, then this function will return
Nothing
.
If the attempt to parse the supplied value fails an exception will be thrown.
Since: 0.6.2
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 #
getConsoleWidth :: Program τ Int Source #
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'
modifyApplicationState :: (τ -> Program τ τ) -> Program τ () Source #
Modify the user supplied top-level application state in a single atomic action
combining getting the value and replacing it. Following the pattern of other
modify
functions in the Haskell ecosystem, this takes a function which
allows you to take limited actions with the existing value, returning the new
value that should be stored.
modifyApplicationState
( settings{answer = a} ->pure
(settings { answer = a + 1 } ) )
While the function you need to supply is in Program
τ
and so able to do
general work if necessary, some care should be taken to return from the action
as quickly as possible; this call will be blocking other consumers of the
top-level application state until it returns.
Since: 0.6.9
changeProgram :: υ -> Program υ α -> Program τ α Source #
Sometimes you need to change the type of the application state from what is present at the top-level when the program starts.
While the original intent of providing an initial value of type τ
to
configure
was that your application state would be available at startup, an
alternative pattern is to form the application state as the first actions that
your program takes in the Program
τ
monad. This is especially common if you
are processing command-line options. In that case, you may find it useful to
initialize the program at type None
, say, and then change to the Program
υ
monad you intend to run through the actual program with once the full
settings object is available. You can do that using this function.
For example:
main ::IO
() main = do context <-configure
"1.0"None
(simpleConfig
...)executeWith
context program1 program1 ::Program
None
() program1 = do -- do things to form top-level application state let settings = Settings { ... }changeProgram
settings program2 program2 ::Program
Settings () program2 = do -- now carry on with application logic ...
This allows your code do do queryOptionValue
and the like in program1
and
then, once all the settings and initialization is complete, you can switch to
the actual type you intend to run at in program2
.
Since: 0.6.3
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
.
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
$ doresetTimer
...
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
$ dotrap_
(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.
A warning 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
Running processes
readProcess :: [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:
readProcess
["/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
)
Since: 0.6.4
callProcess :: [Rope] -> Program τ ExitCode Source #
Execute an external child process and wait for it to finish. 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.
The output of the child process (its stdout
) will go to the terminal console
independently of your parent process's output. If your Haskell program does
anything concurrently then anything it write
s will be
interleaved and probably make a mess of the child's output. So don't do that.
See the similar readProcess
for an action which executes an external program
but which returns its output.
If the thread invoking callProcess
receives an interrupting asynchronous
exception then it will terminate the child, waiting for it to exit.
(this wraps typed-process's runProcess
but follows
the naming convention of the underlying callProcess
code from
process.)
Since: 0.6.8
execProcess_ :: [Rope] -> Program τ () Source #
Execute a new external binary, replacing this Haskell program in memory and running the new binary in this program's place. The PID of the process does not change.
This function does not return.
As with readProcess
above, each of the arguments to the new process
must be supplied as individual values in the list. The first argument is the
name of the binary to be executed. The PATH
will be searched for the binary
if an absolute path is not given; an exception will be thrown if it is not
found.
(this wraps unix's executeFile
machinery, which results in an
execvp(3) standard library function call)
Since: 0.6.4
Internals
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
.
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.
invalid :: HasCallStack => Program τ α Source #
Illegal internal state resulting from what should be unreachable code or otherwise a programmer error.
A utility exception for those occasions when you just need to go "boom".
casecontainsKey
"James Bond" agents ofFalse
-> do evilPlanTrue
-> dowrite
"No Mr Bond, I expect you to die!"throw
Boom
Since: 0.3.2
Instances
Exception Boom Source # | |
Defined in Core.Program.Exceptions toException :: Boom -> SomeException # fromException :: SomeException -> Maybe Boom # displayException :: Boom -> String # | |
Show Boom Source # | |