Shellac-0.9: A framework for creating shell envinronmentsContentsIndex
System.Console.Shell
Contents
Shell Descriptions
Executing Shells
Creating Shell Commands
Subshells
Printing Help Messages
Generating text output
Auxiliary Types
Description

This module implements a framework for creating read-eval-print style command shells. Shells are created by declaratively defining evaluation functions and "shell commands". Input is read using a plugable backend. The shell framework handles command history and word completion if the backend supports it.

The basic idea is for creating a shell is:

  1. Create a list of shell commands and an evaluation function
  2. Create a shell description (using mkShellDescription)
  3. Set up the initial shell state
  4. Run the shell (using runShell)
Synopsis
data ShellDescription st = ShDesc {
shellCommands :: [ShellCommand st]
commandStyle :: CommandStyle
evaluateFunc :: (String -> Sh st ())
greetingText :: (Maybe String)
wordBreakChars :: [Char]
beforePrompt :: (Sh st ())
prompt :: (st -> IO String)
secondaryPrompt :: (Maybe (st -> IO String))
exceptionHandler :: (Exception -> Sh st ())
defaultCompletions :: (Maybe (st -> String -> IO [String]))
historyFile :: (Maybe FilePath)
maxHistoryEntries :: Int
historyEnabled :: Bool
}
initialShellDescription :: ShellDescription st
mkShellDescription :: [ShellCommand st] -> (String -> Sh st ()) -> ShellDescription st
defaultExceptionHandler :: Exception -> Sh st ()
runShell :: ShellDescription st -> ShellBackend bst -> st -> IO st
exitCommand :: String -> ShellCommand st
helpCommand :: String -> ShellCommand st
toggle :: String -> String -> (st -> Bool) -> (Bool -> st -> st) -> ShellCommand st
cmd :: CommandFunction f st => String -> f -> String -> ShellCommand st
class CommandFunction f st | f -> st
newtype File = File String
newtype Username = Username String
newtype Completable compl = Completable String
class Completion compl st | compl -> st where
complete :: compl -> st -> String -> IO [String]
completableLabel :: compl -> String
type ShellCommand st = ShellDescription st -> (String, CommandParser st, Doc, Doc)
type Subshell st st' = (st -> IO st', st' -> IO st, st' -> IO (ShellDescription st'))
simpleSubshell :: (st -> IO st') -> ShellDescription st' -> IO (Subshell st st')
showShellHelp :: ShellDescription st -> String
showCmdHelp :: ShellDescription st -> String -> String
shellPutStr :: String -> Sh st ()
shellPutStrLn :: String -> Sh st ()
shellPutInfo :: String -> Sh st ()
shellPutInfoLn :: String -> Sh st ()
shellPutErr :: String -> Sh st ()
shellPutErrLn :: String -> Sh st ()
data CommandStyle
= OnlyCommands
| CharPrefixCommands Char
| SingleCharCommands
data ShellSpecial st
= ShellExit
| ShellHelp (Maybe String)
| ShellNothing
| ShellContinueLine String
| forall st' . ExecSubshell (Subshell st st')
type OutputCommand = BackendOutput -> IO ()
type CommandResult st = (st, Maybe (ShellSpecial st))
Shell Descriptions
data ShellDescription st
A record type which describes the attributes of a shell.
Constructors
ShDesc
shellCommands :: [ShellCommand st]Commands for this shell
commandStyle :: CommandStyleThe style of shell commands
evaluateFunc :: (String -> Sh st ())The evaluation function for this shell
greetingText :: (Maybe String)Text to print when the shell starts
wordBreakChars :: [Char]The characters upon which the backend will break words
beforePrompt :: (Sh st ())A shell action to run before each prompt is printed
prompt :: (st -> IO String)A command to generate the prompt to print
secondaryPrompt :: (Maybe (st -> IO String))A command to generate the secondary prompt. The secondary prompt is used for multi-line input. If not set, the regular prompt is used instead.
exceptionHandler :: (Exception -> Sh st ())A function called when an exception occurs
defaultCompletions :: (Maybe (st -> String -> IO [String]))If set, this function provides completions when NOT in the context of a shell command
historyFile :: (Maybe FilePath)If set, this provides the path to a file to contain a history of entered shell commands
maxHistoryEntries :: IntThe maximum number of history entries to maintain
historyEnabled :: BoolIf true, the history mechanism of the backend (if any) will be used; false will disable history features.
initialShellDescription :: ShellDescription st
A basic shell description with sane initial values
mkShellDescription :: [ShellCommand st] -> (String -> Sh st ()) -> ShellDescription st
Creates a simple shell description from a list of shell commmands and an evalation function.
defaultExceptionHandler :: Exception -> Sh st ()
The default shell exception handler. It simply prints the exception and returns the shell state unchanged. (However, it specificaly ignores the thread killed exception, because that is used to implement execution canceling)
Executing Shells
runShell :: ShellDescription st -> ShellBackend bst -> st -> IO st
Run a shell. Given a shell description, a shell backend to use and an initial state this function runs the shell until it exits, and then returns the final state.
Creating Shell Commands
exitCommand
:: Stringthe name of the command
-> ShellCommand st
Creates a shell command which will exit the shell.
helpCommand
:: Stringthe name of the command
-> ShellCommand st
Creates a command which will print the shell help message.
toggle
:: Stringcommand name
-> Stringhelp message
-> (st -> Bool)getter
-> (Bool -> st -> st)setter
-> ShellCommand st
Creates a command to toggle a boolean value
cmd
:: CommandFunction f st
=> Stringthe name of the command
-> fthe command function. See CommandFunction for restrictions on the type of this function.
-> Stringthe help string for this command
-> ShellCommand st
Creates a user defined shell commmand. This relies on the typeclass machenery defined by CommandFunction.
class CommandFunction f st | f -> st

This class is used in the cmd function to automaticly generate the command parsers and command syntax strings for user defined commands. The type of 'f' is restricted to have a restricted set of monomorphic arguments (Int, Integer, Float, Double, String, File, Username, and Completable) and the head type must be Sh st ()

  f :: Int -> File -> Sh MyShellState ()
  g :: Double -> Sh st ()
  h :: Sh SomeShellState ()

are all legal types, whereas:

  bad1 :: a -> Sh (MyShellState a) ()
  bad2 :: [Int] -> Sh MyShellState ()
  bad3 :: Bool -> MyShellState

are not.

show/hide Instances
newtype File
Represents a command argument which is a filename
Constructors
File String
show/hide Instances
newtype Username
Represents a command argument which is a username
Constructors
Username String
show/hide Instances
newtype Completable compl
Represents a command argument which is an arbitrary completable item. The type argument determines the instance of Completion which is used to create completions for this command argument.
Constructors
Completable String
show/hide Instances
(CommandFunction r st, Completion compl st) => CommandFunction (Completable compl -> r) st
class Completion compl st | compl -> st where
A typeclass representing user definable completion functions.
Methods
complete :: compl -> st -> String -> IO [String]
Actually generates the list of possible completions, given the current shell state and a string representing the beginning of the word.
completableLabel :: compl -> String
generates a label for the argument for use in the help displays.
type ShellCommand st = ShellDescription st -> (String, CommandParser st, Doc, Doc)
The type of a shell command. The shell description is passed in, and the tuple consists of (command name,command parser,command syntax document,help message document)
Subshells
type Subshell st st' = (st -> IO st', st' -> IO st, st' -> IO (ShellDescription st'))

The type of subshells. The tuple consists of:

  1. A function to generate the initial subshell state from the outer shell state
  2. A function to generate the outer shell state from the final subshell state
  3. A function to generate the shell description from the inital subshell state
simpleSubshell
:: (st -> IO st')A function to generate the initial subshell state from the outer shell state
-> ShellDescription st'A shell description for the subshell
-> IO (Subshell st st')
Creates a simple subshell from a state mapping function and a shell description.
Printing Help Messages
showShellHelp :: ShellDescription st -> String
Prints the help message for this shell, which lists all avaliable commands with their syntax and a short informative message about each.
showCmdHelp :: ShellDescription st -> String -> String
Print the help message for a particular shell command
Generating text output
shellPutStr :: String -> Sh st ()
Prints a regular output string with a line terminator
shellPutStrLn :: String -> Sh st ()
Prints regular output with a line terminator
shellPutInfo :: String -> Sh st ()
Prints an informational output string
shellPutInfoLn :: String -> Sh st ()
Prints an informational output string with a line terminator
shellPutErr :: String -> Sh st ()
Prints an error output string
shellPutErrLn :: String -> Sh st ()
Prints and error output string with a line terminator
Auxiliary Types
data CommandStyle
Datatype describing the style of shell commands. This determines how shell input is parsed.
Constructors
OnlyCommandsIndicates that all input is to be interpreted as shell commands; no input will be passed to the evaluation function.
CharPrefixCommands CharIndicates that commands are prefixed with a particular character Colon ':' is the default charcter (a la GHCi).
SingleCharCommandsCommands consisit of a single character
data ShellSpecial st
Special commands for the shell framework.
Constructors
ShellExitCauses the shell to exit
ShellHelp (Maybe String)Causes the shell to print an informative message. If a command name is specified, only information about that command will be displayed
ShellNothingInstructs the shell to do nothing; redisplay the prompt and continue
ShellContinueLine StringAsk the shell to continue accepting input on another line, which should be appended to the given string
forall st' . ExecSubshell (Subshell st st')Causes the shell to execute a subshell
type OutputCommand = BackendOutput -> IO ()
The type of commands which produce output on the shell console.
type CommandResult st = (st, Maybe (ShellSpecial st))
The type of results from shell commands. They are a modified shell state and possibly a shell "special" action to execute.
Produced by Haddock version 0.8