HCL-1.5.1: High-level library for building command line interfaces.

Safe HaskellNone
LanguageHaskell98

System.Console.HCL

Contents

Description

This module provides a set of functions for building simple command-line interfaces. It allows interfaces which collect values (such as Integers, Dates, or other structured values), build lists of values, and use simple menus. It is not intended to build complex interfaces with full cursor control. It is oriented towards line-based interfaces.

Requests

The central concept of the library is the Request type, which embodies an interactive request for data. When requesting data, there is always the possibility of failure. That is, the user may enter a value that doesn't parse, or may want to quit the process. For this reason, the value stored by a request is IO ("Maybe a"), which shows there may not always be a value available. Request is a monad, and when a request fails, no subsequent requests are asked. Instead, the whole request chain is abandoned.

The function reqResp gives the most basic request possible, which is for a string. From this, other requests can be built. The library provides several:

  • reqInt - Requests Int values.
  • reqInteger - Requests Integer values.
  • reqChar - Requests a single character (without waiting for the user to press enter)
  • reqPassword - Like "reqResp", but doesn't echo the user's input to the console.
  • reqRead - Requests Read-able values.
  • reqList - Asks a request repeatedly and builds a list of the responses, which are returned when the user enters a failure value.
  • reqMenu - Given a list of items, asks the user to pick one of the items and returns it.
  • reqFail - Always results in failure. Useful in menus for creating a "quit" or "none" selection.

A number of request patterns are also exported by the module. These embody different control schemes that are useful when building command-line interfaces. These include:

  • reqIf - Takes a request which evaluates to a boolean and two requests representing "then" and "else" branches. The appropriate subsequent request is used, based on the value of the conditional request.
  • reqAgree - Takes a request and determines if the user answers yes or no. A default can also be provided.
  • reqForever - Takes a request and asks it over and over, until a failure value appears.
  • reqIterate - Takes a function which, given a value, produces a request. An initial Request value is also provided. The initial value is given to the function, and the value produced by the function is fed back into it. This continues until a failure occurs. This model is useful for shell-type applications which take a state, operate on it, and produce a new state, which is then fed back in.
  • reqCont - Takes a request and a "continuation" request. If the first request fails, the "continuation" request is run. This is useful for confirming if the user really wants to quit an application, or other escape mechanisms.

Running Requests

Requests can be run with two different functions:

  • execReq - Takes a request, runs it, and returns a meaningless value. This is most often used to run a request from 'main'.
  • runRequest - Runs a request and returns the raw IO ("Maybe a") value returned. This is useful for running a request and extracting the value returned out of it.

Prompting

In most req functions, except reqMenu and reqChoices, nothing is printed to the screen. Instead, a set of functions is provided which take a request and a string to use as a prompt. These functions include:

  • prompt - Displays a message and gets a response. If the message ends in a space, it is assumed that input should be typed on the same line. Otherwise, a newline is printed and input is then gathered.
  • prompt1 -- Simple way to ask for a response and provide a default.
  • promptAgree -- Simple way to ask for a yes/no response.

Simple Programs

Getting values combines prompting and requests. Here's a 'guess a number' game which probably isn't real fun (from examples\guess_num.hs):

guess_num_boring =
    do
      num <- prompt "Enter your guess between 1 - 100: " reqInt
      if num == 50
        then reqIO $ putStrLn "You win!"
        else reqIO $ putStrLn "Too bad!"

To run the program, type play_game guess_num_boring at the prompt. A better program might actually randomize the number, and tell you if you are low or high (again from examples\guess_num.hs):

guess_num_fun =
      do
        target <- reqIO $ getStdRandom (randomR (1::Integer,100))
        let guessed val =
              case compare target val of
                GT -> do { reqIO $ putStrLn "Too low!"; return False }
                LT -> do { reqIO $ putStrLn "Too high!"; return False }
                EQ -> do { reqIO $ putStrLn "You win!"; return True }
        reqUntil guessed (prompt "Enter a number between 1 and 100: " reqInteger)

play_game game = execReq game

To run the program, type play_game guess_num_fun at the prompt. Several features of this program are worth pointing out:

  • reqIO - This function is used to lift IO operations into the Request type.
  • reqUntil - This function takes a condition and a request, and runs the request until the condition is satisfied. The conditional has the type (a -> Request b), which allows the conditional to produce output, or base its decision on other requests. Naturally, the second argument has the type (Request a), which means the result of the request can be passed to the condition. Other functions which wrap up input patterns are reqFoldl, reqList, reqCont, and others.

Combining Requests

The functions in this library are designed to allow more complex Request values to be built from them. For example, imagine you are coding for a tax form submission and have a data type like this (from examples\taxpayer.hs):

 data Taxpayer = Taxpayer { name :: String, age :: Int, ssn :: String }
  deriving (Read, Show)

Because Taxpayer derives Read, a simple way of collecting a Taxpayer value from the user would be:

reqTaxpayer :: Request Taxpayer
reqTaxpayer = prompt "Please enter tax payer information: " (reqRead reqResp)

Of course, this isn't very friendly:

*Main> getTaxpayer reqTaxpayer
Please enter tax payer information: Taxpayer {name="John", age = 30, ssn = "" }
You entered: Taxpayer {name = "John", age = 30, ssn = ""}

Typing Taxpayer { name = "John" ... } each time is pretty tedious. A better solution builds the value from simpler pieces:

reqTaxpayerEasy :: Request Taxpayer
reqTaxpayerEasy =
  do
    name <- prompt "Please enter the tax payer's name: " reqResp
    age <- prompt "Please enter their age: " reqInt
    ssn <- prompt "What is their SSN/ASN: " reqResp
    return (Taxpayer name age ssn)

Now, when tax payer info must be entered a nice set of prompts is displayed:

*Main> getTaxpayer reqTaxpayerEasy
Please enter the tax payer's name: Bob
Please enter their age: 50
Please enter their SSN/ASN: 111-11-1111
You entered: Taxpayer {name = "Bob", age = 50, ssn = "111-11-1111"}

Validation

HCL provides the reqWhile and reqUntil functions which help ensure values entered are correct. For example, in the above, we could validate SSN's fairly easily like so (again, from example\tax_payer.hs):

reqSSN :: Request String -> Request String
reqSSN req =
  do
    -- very simple validation
    let
      matchSSN = matchRegex (mkRegex "^...-..-....$")
      invalidSSN ssn = return $ isNothing (matchSSN ssn)
    ssn <- reqWhile invalidSSN req
    return ssn

In the above, reqWhile repeatedly uses invalidSSN to determine if the value entered matches the (very simple) regular expression provided. When it does, the SSN entered is returned. Until then, the request is asked over and over. One subtlety to note is that a request to get the actual value is passed in to the function as req. This allows the function reqTaxpayerValidate to pass it's own prompt and request into reqSSN:

reqTaxpayerValidate :: Request Taxpayer
reqTaxpayerValidate =
  do
    name <- prompt "Please enter the tax payer's name: " reqResp
    age <- prompt "Please enter their age: " reqInt
    ssn <- reqSSN (prompt "What is their SSN/ASN: " reqResp)
    return (Taxpayer name age ssn)

Running reqTaxpayerValidate from the prompt then gives:

*Main> getTaxpayer reqTaxpayerValidate
Please enter the tax payer's name: Bob
Please enter their age: 20
What is their SSN/ASN: 324=12=1231
What is their SSN/ASN: 324-12-1211
You entered: Taxpayer {name = "Bob", age = 20, ssn = "324-12-1211"}

Dealing with Failure

A fundamental assumption of the Request type is that requests can fail. The user can enter no input or provide bad input. The discussion of validation above is a bit disingenuous because it does not mention what happens when the user just types a newline at the prompt. In all cases, the request chain ends and the program exits.

This is due to the behavior of the Request monad - as soon as one request fails, the rest fail. The library provides several functions for dealing with this:

  • reqDefault - Allows a default value to be supplied, which will be returned if the user provides no input or bad input.
  • required - Repeatedly asks a request until the user provides input. "Failure" values will not occur.
  • reqCont - Takes two request arguments. If the first fails, the second is used. Useful for providing a "continuation" to a request chain.
  • reqWhich - Indicates if a request failed or not, through the use of the Either type. There is no direct way to determine if a request failed (that is, if it evaluates to Nothing, the entire chain fails and you won't see it). This function allows some visibility into if a specific request succeeded or not.

One use for reqCont is to confirm if the user really wants to quit a program. In the guess-a-number game, hitting Enter at a prompt stops the game. This can be avoided by changing how the guess a number game is launched:

guess_num_cont =
    reqCont guess_num_fun confirm
  where
    confirm =
      reqIf (promptAgree "Are you sure you want to quit? " (Just False) reqResp)
        reqFail
        guess_num_cont

Above, reqCont will run guess_num_fun until it returns a Just value. If Nothing is returned, then reqConfirm is run. If the user does not wish to quit, reqConfirm will run guess_num_confirm again. Otherwise, reqFail is run, which causes the request to fail and thus the program to exit. Notice that the confirmation behavior was added by just adding another layer to the request chain. The guess_num_fun function was used to provide gameplay - guess_num_confirm just added a layer to control when the game ends.

However, because this pattern is fairly common, HCL provides the reqConfirm function, which acts just like the reqCont pattern above. That is, it takes a request to run and a request which returns a Bool. If the initial request fails, the confirmation request is run. If that request results in True, the failure is allowed to propagate. Otherwise, the initial request is run again. The function guess_num_confirm gives an example of its usage:

guess_num_confirm =
    reqConfirm confirm guess_num_fun 
  where
    confirm = promptAgree "Are you sure you want to quit? " (Just False) reqResp

Making Menus

Several functions are used to build simple, hierarchical menus. A menu is defined as a list of pairs, where the first element is the label and the second a value to return. Usually, that value is a Request. In some cases it is not. There are two functions used for building menus:

  • reqChoices - A low-level means to build menus. It does not expect the second item in the pair to be a request, and is thus very general.
  • reqMenu - Expects the list given to be a pair of a string and another request. When an item is selected, that request is run and the value is returned.
  • reqSubMenu - Inserts a menu into a menu. When the item for the submenu is selected, the submenu will display its choices. When the user wishes to exit (by providing a failure value), the previously displayed menu will display again.
  • reqMenuItem - Constructs an indvidual menu item.
  • reqMenuEnd - Indicates the end of a list of menu items.
  • reqMenuExit - A specialized menu item which will cause the menu request to fail. That means we return to the previous menu or exit the request chain altogether, depending on how the menus are structured.

reqMenu and reqSubMenu work together to build hierarchical menus in which the user can automatically navigate "up" by just hitting return. For example, imagine a simple menu-driven PIM:

*Main> pim
1. Manage contacts
2. Manage calendar
? 1
1. Add a contact
2. Remove a contact
? <-- User hits return here, returns to main menu
1. Manage contacts
2. Manage calendar
?

Setting this up is fairly straightforward (from examples\pim.hs):

pim = execReq $ reqConfirm confirm topMenu 
  where
    confirm = promptAgree "Are you sure you want to quit?" (Just False) reqResp
    
topMenu =
  reqMenu $
  -- Insert a submenu defined elsewhere
  reqSubMenu topMenu "Manage contacts" manageContactsMenu $
  -- Insert a sub menu directly
  reqSubMenu topMenu "Manage calendar"
    (reqMenuItem "Add an event" notImpl $
      ...
      reqMenuExit "Return to previous menu"
      reqMenuEnd) $
  ...
  -- End the menu definition
  reqMenuEnd
  
-- Defines a partial menu
manageContactsMenu =
  reqMenuItem "Add a contact" notImpl $
  ...
  reqMenuExit "Return to previous menu"
  reqMenuEnd

notImpl = reqIO $ putStrLn "This function is not implemented."

reqMenu begins the process of definining a menu. reqMenuItem is used to build a menu item, and when combined with ($) as above can be used to define a list of menu items "in-line". reqSubMenu takes the menu to return to as its first argument (in the case above, topMenu), a label to name the menu item, and a request which will become the submenu. As seen above, submenus can be inserted directly (e.g. "Manage calendar"), or they can be defined independently (e.g. "Manage contacts"). reqMenuExit allows the submenu to return to control to its calling menu. Finally, reqMenuEnd can be used to end an "in-line" menu definition.

Just Plain Cool

Some of the other functions included are just cool to use:

  • reqIterate - This take a function which maps a value to a request and a request. The request is evaluated and the results passed to the function. The result of that function is passed back into the function again. reqIterate is useful for applications that manipulate some sort of environment by repeatedly passing the modified environment back into themselves. An example of this is shown in examples\shell.hs where the shell function is repeatedly called from main using reqIterate. The hangman game in hangman\hangman.hs also uses this when the playRound function is repeatedly called from main.
  • reqFoldl - Like foldl, but for requests. The accumulating function takes values of type a (which come from the request given) and type b (the accumulating value) and produces a Request of type b. If and when the initial request fails, whatever accumulated value that was built is returned.
  • reqList - Takes a request and repeatedly runs it, building a list of the results. When the request fails, the list is returned.
  • makeReq - Not really so cool, but allows you to construct your own Request values. Values created with makeReq can be extracted with runRequest. However, they will come back with the type (IO ("Maybe a"), where the value is always a Just value.

Examples

Several examples are included with the library, including a hangman game you can play:

  • examples\guess_num.hs - Demonstrates various ways of implementing a "guess a number" game.
  • examples\pim.hs - Shows how to build simple menus.
  • examples\shell.hs - Shows how to use reqIterate to build a simple shell.
  • examples\tax_payer.hs - Demonstrates how to construct requests for specific structured data types from simpler requests.
  • hangman\hangman.hs - Implements the hangman game. An executable is installed when you install the library - just run hangman at the command line.
Synopsis

Request type and related functions

data Request a Source #

The Request data type represents a value requested interactively. The request may have failed or been no response, in which case the request fails. Otherwise, the request holds the response given.

Instances
Monad Request Source #

Request behavior as a Monad covers failure - when a request results in Nothing, all bind operations fail afterwards. Thus, when one request fails, all subsequent requests automatically fail.

Instance details

Defined in System.Console.HCL

Methods

(>>=) :: Request a -> (a -> Request b) -> Request b #

(>>) :: Request a -> Request b -> Request b #

return :: a -> Request a #

fail :: String -> Request a #

Functor Request Source #

Because we have defined Request as Applicative, we must also define it as Functor.

Instance details

Defined in System.Console.HCL

Methods

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

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

Applicative Request Source #

Because we have defined Request as Monad, we must also define it as Applicative.

Instance details

Defined in System.Console.HCL

Methods

pure :: a -> Request a #

(<*>) :: Request (a -> b) -> Request a -> Request b #

liftA2 :: (a -> b -> c) -> Request a -> Request b -> Request c #

(*>) :: Request a -> Request b -> Request b #

(<*) :: Request a -> Request b -> Request a #

MonadIO Request Source #

Allow the Request type to use IO operations.

Instance details

Defined in System.Console.HCL

Methods

liftIO :: IO a -> Request a #

Show a => Show (Request a) Source #

Show for requests.

Instance details

Defined in System.Console.HCL

Methods

showsPrec :: Int -> Request a -> ShowS #

show :: Request a -> String #

showList :: [Request a] -> ShowS #

Arbitrary a => Arbitrary (Request a) Source #

Creates a request which will return a random value or Nothing. The request returns the same value every time it is evaluated.

Instance details

Defined in System.Console.HCL

Methods

arbitrary :: Gen (Request a) #

shrink :: Request a -> [Request a] #

runRequest Source #

Arguments

:: Request a

The request to evaluate.

-> IO (Maybe a)

Result of the request.

Extracts the value from a given request.

execReq Source #

Arguments

:: Request a

Request to run.

-> IO ()

No meaningful value is returned.

Runs a request, throws away the result, and returns an IO type (rather than a Request). Useful when a request should just be run and we don't care about the result. Generally used at the top level to evaluate a request in main.

reqIO Source #

Arguments

:: IO a

IO action to perform

-> Request a

Result of the IO action, as a Request.

Allows IO operations in the Request type. Same as liftIO in MonadIO class (in Control.Monad.Trans module)

makeReq Source #

Arguments

:: a

The value to turn into a Request.

-> Request a

The value as a Request.

Takes a value and makes it into a request. Should not be an IO (Maybe a) type value, unless multiply nested values is desired.

Request building blocks

reqResp :: Request String Source #

The basic request - get a string from the user. If a newline or all whitespace is entered, the request is assumed to be a failure.

reqInteger :: Request Integer Source #

Gets an Integer from the user. If the value entered cannot be converted, the request fails.

reqInt :: Request Int Source #

Gets an Int from the user. If the value entered cannot be converted, the request fails.

reqRead Source #

Arguments

:: Read a 
=> Request String

A request that returns a string (generally reqResp), which will then be parsed.

-> Request a

The value parsed.

Uses reads to process a request. If the value cannot be parsed, fails. Otherwise, returns the value parsed.

reqChar :: Request Char Source #

reqChar requests a single character. Unlike other Requests, it does not wait for the user to hit enter; it simply returns the first keystroke.

reqPassword :: Request String Source #

reqPassword works like reqResp except that it does not echo the user's input to standard output.

Functions lifted into Requests

andReq Source #

Arguments

:: Request Bool

Left boolean value.

-> Request Bool

Right boolean value.

-> Request Bool

Result value.

&& operator for requests (with failure). Behaves similarly, including "short-circuit" behavior. If either condition fails, the entire Request fails.

orReq Source #

Arguments

:: Request Bool

Left boolean value.

-> Request Bool

Right boolean value.

-> Request Bool

Result value.

|| operator for requests (with failure). Behaves similarly, including "short-circuit" behavior. If either condition fails, the entire Request fails.

notReq Source #

Arguments

:: Request Bool

Request to evaluate.

-> Request Bool

Result value.

not operator for requests.

reqIf Source #

Arguments

:: Request Bool

The test to apply

-> Request a

Request to evaluate if test is true.

-> Request a

Request to evaluate if test if false.

-> Request a

Result.

If statement for requests.

reqConst Source #

Arguments

:: a

Value to make into a request.

-> Request a

Result.

Takes a value and makes it into a request.

reqLift Source #

Arguments

:: (a -> b)

Function to lift.

-> Request a

Argument to function.

-> Request b

Result.

Lifts a one-argument function into Request types.

reqLift2 Source #

Arguments

:: (a -> b -> c)

Function to lift.

-> Request a

First argument to function.

-> Request b

Second argument to function.

-> Request c

Result.

Lifts a two argument function into Request types. The arguments to the function are evaluated in order, from left to right, since the Request monad imposes sequencing.

reqMaybe Source #

Arguments

:: Request a

Request to evaluate.

-> Request b

Default value.

-> (a -> Request b)

Function to map b to Request a.

-> Request b

Result.

Like the maybe function, but for requests. Given a request value, a default value,and a function that maps b to Request a, this function either returns the default if the request value is nothing, or it applies the function given to the value of the request and returns it.

Request patterns

reqAgree Source #

Arguments

:: Maybe Bool

Default value (if any).

-> Request String

Request which gets a string (usually reqResp).

-> Request Bool

Result.

Returns true if the user answer y or Y. Allows a default to be specified, and allows failure if no default is given.

reqFail :: Request a Source #

Automatic failure. Useful in menus to quit or return to the previous menu.

required Source #

Arguments

:: Request a

Request to evaluate.

-> Request a

Result.

Takes a request and guarantees a value will be returned. That is, the request is repeated until a valid (i.e. not Nothing) response is returned.

reqUntil Source #

Arguments

:: (a -> Request Bool)

Condition to test.

-> Request a

Request value to evaluate according to test.

-> Request a

Result.

Runs the request until the condition given is satisfied, then returns the result.

reqWhile :: (a -> Request Bool) -> Request a -> Request a Source #

Runs the request while the condition given holds, then returns the result. Good for verification.

reqDefault Source #

Arguments

:: Request a

Request to evaluate.

-> a

Default value.

-> Request a

Result.

Requests a response from user. If Nothing is returned, assumes default and returns that.

reqForever Source #

Arguments

:: Request a

Request to ask forever.

-> Request a

Result.

reqChoices Source #

Arguments

:: [(String, a)]

List of choices and labels which will be selected from.

-> Request Int

Request which gets the selection from the user.

-> Request a

Result of selection.

Given a list of items and programs to run, displays a menu of the items and runs the selected program. Very low level - usually reqMenu is used instead. If the user selects an invalid choice, failure occurs.

reqIterate Source #

Arguments

:: (a -> Request a)

Iterative function which transforms a to Request a.

-> a

Initial value used.

-> Request a

Result of evaulation.

Takes an initial value and function which produces a request from that value. Applies the function to the initial value and then recurses. Useful for functions which operate off their own output (e.g. a shell maintaining an environment).

reqCont Source #

Arguments

:: Request a

First request to evaluate.

-> Request a

Continuation request which is evaluated if first fails.

-> Request a

Result.

Takes a request and a "continuation" request. If the first request results in Nothing, run the second request. In either case, return the result of the successful request.

reqConfirm Source #

Arguments

:: Request Bool

When evaluated, determines if the failure is allowed to proceed or not.

-> Request a

The request to run and to watch for failure

-> Request a

Result of the request (if it did not fail).

Executes the request given and, if a failure value occurs, executes the Bool request given (usually some sort of prompt asking if they want to quit). If the answer is True, the failure value propagates. Otherwise, the initial request is run again.

reqWhich Source #

Arguments

:: Request a

Request to evaluate.

-> Request (Either () a)

Result.

reqFoldl Source #

Arguments

:: (a -> b -> Request b)

Accumulating function.

-> b

Initial value.

-> Request a

Request to evaluate.

-> Request b

Result.

Give a function from a -> b, an initial value, and a Request for a, builds a Request for b. When (Request a) fails, then the function returns whatever (Request b) has been built.

reqList Source #

Arguments

:: Request a

Request to evaluate.

-> Request [a]

Result.

Given a request, builds a list of response. When the user enters Nothing, the list building ends

Menus

reqMenu Source #

Arguments

:: [(String, Request a)]

List of request choices and labels.

-> Request a

Result.

Takes a list of strings and requests and forms a menu out of them. Menus can built using reqMenuItem, reqSubMenu, reqMenuExit, and reqMenuEnd.

reqMenuItem :: String -> Request a -> [(String, Request a)] -> [(String, Request a)] Source #

Used to add an individual entry to a menu that is being built.

reqMenuEnd :: [(String, Request a)] Source #

Ends a list of menu item definitions.

reqSubMenu Source #

Arguments

:: Request a

The menu to return to.

-> String

The label of the submenu (in the current menu)

-> [(String, Request a)]

The submenu itself

-> [(String, Request a)]

The existing menu into which this submenu will be inserted.

-> [(String, Request a)]

The menu item built and returned.

Creates a submenu within a menu. When the submenu exits, control returns to the item specified.

reqMenuExit :: String -> [(String, Request a)] -> [(String, Request a)] Source #

Causes the program to exit from the current menu.

Prompting

prompt Source #

Arguments

:: String

Message to display.

-> Request a

Request which gathers input

-> Request a

Result.

Prints a message and makes a request. If the message ends in a space, it is assumed that the user should enter values on the same line. Otherwise, a new line is printed and the reqeust is evaulated.

prompt1 Source #

Arguments

:: Show a 
=> String

Message to display. Follows conventions of prompt.

-> Request a

Request to evaluate.

-> a

Default value to use if necessary.

-> Request a

Result.

Deprecated name for prompt1.

Displays a message prompt and a default choice in a common way. If the user doesn't provide a choice or enters bad data, the default value provided is returned. Otherwise, the value entered is returned.

promptAgree Source #

Arguments

:: String

Message to display. Follows conventions of prompt.

-> Maybe Bool

Default value, if any.

-> Request String

Request which gets a string (usually reqResp).

-> Request Bool

Result.

Prints a message, displays defaults (if any), and turns a Request String into a Request Bool. If a default value is provided, it will be returned if the user enters nothing or an invalid response.