haskeline-0.7.4.3: A command-line interface for user input, written in Haskell.

Safe HaskellNone
LanguageHaskell98

System.Console.Haskeline

Contents

Description

A rich user interface for line input in command-line programs. Haskeline is Unicode-aware and runs both on POSIX-compatible systems and on Windows.

Users may customize the interface with a ~/.haskeline file; see https://github.com/judah/haskeline/wiki/UserPreferences for more information.

An example use of this library for a simple read-eval-print loop (REPL) is the following:

import System.Console.Haskeline

main :: IO ()
main = runInputT defaultSettings loop
   where
       loop :: InputT IO ()
       loop = do
           minput <- getInputLine "% "
           case minput of
               Nothing -> return ()
               Just "quit" -> return ()
               Just input -> do outputStrLn $ "Input was: " ++ input
                                loop
Synopsis

Interactive sessions

The InputT monad transformer

data InputT m a Source #

A monad transformer which carries all of the state and settings relevant to a line-reading application.

Instances
MonadTrans InputT # 
Instance details

Defined in System.Console.Haskeline.InputT

Methods

lift :: Monad m => m a -> InputT m a Source #

Monad m => Monad (InputT m) # 
Instance details

Defined in System.Console.Haskeline.InputT

Methods

(>>=) :: InputT m a -> (a -> InputT m b) -> InputT m b Source #

(>>) :: InputT m a -> InputT m b -> InputT m b Source #

return :: a -> InputT m a Source #

fail :: String -> InputT m a Source #

Functor m => Functor (InputT m) # 
Instance details

Defined in System.Console.Haskeline.InputT

Methods

fmap :: (a -> b) -> InputT m a -> InputT m b Source #

(<$) :: a -> InputT m b -> InputT m a Source #

MonadFix m => MonadFix (InputT m) # 
Instance details

Defined in System.Console.Haskeline.InputT

Methods

mfix :: (a -> InputT m a) -> InputT m a Source #

Applicative m => Applicative (InputT m) # 
Instance details

Defined in System.Console.Haskeline.InputT

Methods

pure :: a -> InputT m a Source #

(<*>) :: InputT m (a -> b) -> InputT m a -> InputT m b Source #

liftA2 :: (a -> b -> c) -> InputT m a -> InputT m b -> InputT m c Source #

(*>) :: InputT m a -> InputT m b -> InputT m b Source #

(<*) :: InputT m a -> InputT m b -> InputT m a Source #

MonadIO m => MonadIO (InputT m) # 
Instance details

Defined in System.Console.Haskeline.InputT

Methods

liftIO :: IO a -> InputT m a Source #

MonadException m => MonadException (InputT m) # 
Instance details

Defined in System.Console.Haskeline.InputT

Methods

controlIO :: (RunIO (InputT m) -> IO (InputT m a)) -> InputT m a Source #

runInputT :: MonadException m => Settings m -> InputT m a -> m a Source #

Run a line-reading application. This function should suffice for most applications.

This function is equivalent to runInputTBehavior defaultBehavior. It uses terminal-style interaction if stdin is connected to a terminal and has echoing enabled. Otherwise (e.g., if stdin is a pipe), it uses file-style interaction.

If it uses terminal-style interaction, Prefs will be read from the user's ~/.haskeline file (if present). If it uses file-style interaction, Prefs are not relevant and will not be read.

haveTerminalUI :: Monad m => InputT m Bool Source #

Returns True if the current session uses terminal-style interaction. (See Behavior.)

mapInputT :: (forall b. m b -> m b) -> InputT m a -> InputT m a Source #

Map a user interaction by modifying the base monad computation.

Behaviors

data Behavior Source #

Haskeline has two ways of interacting with the user:

  • "Terminal-style" interaction provides an rich user interface by connecting to the user's terminal (which may be different than stdin or stdout).
  • "File-style" interaction treats the input as a simple stream of characters, for example when reading from a file or pipe. Input functions (e.g., getInputLine) print the prompt to stdout.

A Behavior is a method for deciding at run-time which type of interaction to use.

For most applications (e.g., a REPL), defaultBehavior should have the correct effect.

runInputTBehavior :: MonadException m => Behavior -> Settings m -> InputT m a -> m a Source #

Run a line-reading application according to the given behavior.

If it uses terminal-style interaction, Prefs will be read from the user's ~/.haskeline file (if present). If it uses file-style interaction, Prefs are not relevant and will not be read.

defaultBehavior :: Behavior Source #

Read input from stdin. Use terminal-style interaction if stdin is connected to a terminal and has echoing enabled. Otherwise (e.g., if stdin is a pipe), use file-style interaction.

This behavior should suffice for most applications.

useFileHandle :: Handle -> Behavior Source #

Use file-style interaction, reading input from the given Handle.

useFile :: FilePath -> Behavior Source #

Use file-style interaction, reading input from the given file.

preferTerm :: Behavior Source #

Use terminal-style interaction whenever possible, even if stdin and/or stdout are not terminals.

If it cannot open the user's terminal, use file-style interaction, reading input from stdin.

User interaction functions

Reading user input

The following functions read one line or character of input from the user.

When using terminal-style interaction, these functions return Nothing if the user pressed Ctrl-D when the input text was empty.

When using file-style interaction, these functions return Nothing if an EOF was encountered before any characters were read.

getInputLine Source #

Arguments

:: MonadException m 
=> String

The input prompt

-> InputT m (Maybe String) 

Reads one line of input. The final newline (if any) is removed. When using terminal-style interaction, this function provides a rich line-editing user interface.

If autoAddHistory == True and the line input is nonblank (i.e., is not all spaces), it will be automatically added to the history.

getInputLineWithInitial Source #

Arguments

:: MonadException m 
=> String

The input prompt

-> (String, String)

The initial value left and right of the cursor

-> InputT m (Maybe String) 

Reads one line of input and fills the insertion space with initial text. When using terminal-style interaction, this function provides a rich line-editing user interface with the added ability to give the user default values.

This function behaves in the exact same manner as getInputLine, except that it pre-populates the input area. The text that resides in the input area is given as a 2-tuple with two Strings. The string on the left of the tuple (obtained by calling fst) is what will appear to the left of the cursor and the string on the right (obtained by calling snd) is what will appear to the right of the cursor.

Some examples of calling of this function are:

getInputLineWithInitial "prompt> " ("left", "") -- The cursor starts at the end of the line.
getInputLineWithInitial "prompt> " ("left ", "right") -- The cursor starts before the second word.

getInputChar Source #

Arguments

:: MonadException m 
=> String

The input prompt

-> InputT m (Maybe Char) 

Reads one character of input. Ignores non-printable characters.

When using terminal-style interaction, the character will be read without waiting for a newline.

When using file-style interaction, a newline will be read if it is immediately available after the input character.

getPassword Source #

Arguments

:: MonadException m 
=> Maybe Char

A masking character; e.g., Just '*'

-> String 
-> InputT m (Maybe String) 

Reads one line of input, without displaying the input while it is being typed. When using terminal-style interaction, the masking character (if given) will replace each typed character.

When using file-style interaction, this function turns off echoing while reading the line of input.

Note that if Haskeline is built against a version of the Win32 library earlier than 2.5, getPassword will incorrectly echo back input on MinTTY consoles (such as Cygwin or MSYS).

Outputting text

The following functions enable cross-platform output of text that may contain Unicode characters.

outputStr :: MonadIO m => String -> InputT m () Source #

Write a Unicode string to the user's standard output.

outputStrLn :: MonadIO m => String -> InputT m () Source #

Write a string to the user's standard output, followed by a newline.

getExternalPrint :: MonadException m => InputT m (String -> IO ()) Source #

Return a printing function, which in terminal-style interactions is thread-safe and may be run concurrently with user input without affecting the prompt.

Customization

Settings

data Settings m Source #

Application-specific customizations to the user interface.

Constructors

Settings 

Fields

defaultSettings :: MonadIO m => Settings m Source #

A useful default. In particular:

defaultSettings = Settings {
          complete = completeFilename,
          historyFile = Nothing,
          autoAddHistory = True
          }

setComplete :: CompletionFunc m -> Settings m -> Settings m Source #

Because complete is the only field of Settings depending on m, the expression defaultSettings {completionFunc = f} leads to a type error from being too general. This function works around that issue, and may become unnecessary if another field depending on m is added.

User preferences

data Prefs Source #

Prefs allow the user to customize the terminal-style line-editing interface. They are read by default from ~/.haskeline; to override that behavior, use readPrefs and runInputTWithPrefs.

Each line of a .haskeline file defines one field of the Prefs datatype; field names are case-insensitive and unparseable lines are ignored. For example:

editMode: Vi
completionType: MenuCompletion
maxhistorysize: Just 40
Instances
Show Prefs # 
Instance details

Defined in System.Console.Haskeline.Prefs

readPrefs :: FilePath -> IO Prefs Source #

Read Prefs from a given file. If there is an error reading the file, the defaultPrefs will be returned.

defaultPrefs :: Prefs Source #

The default preferences which may be overwritten in the .haskeline file.

runInputTWithPrefs :: MonadException m => Prefs -> Settings m -> InputT m a -> m a Source #

Run a line-reading application. Uses defaultBehavior to determine the interaction behavior.

runInputTBehaviorWithPrefs :: MonadException m => Behavior -> Prefs -> Settings m -> InputT m a -> m a Source #

Run a line-reading application.

History

The InputT monad transformer provides direct, low-level access to the user's line history state.

However, for most applications, it should suffice to just use the autoAddHistory and historyFile flags.

getHistory :: MonadIO m => InputT m History Source #

Get the current line input history.

putHistory :: MonadIO m => History -> InputT m () Source #

Set the line input history.

modifyHistory :: MonadIO m => (History -> History) -> InputT m () Source #

Change the current line input history.

Ctrl-C handling

withInterrupt :: MonadException m => InputT m a -> InputT m a Source #

If Ctrl-C is pressed during the given action, throw an exception of type Interrupt. For example:

tryAction :: InputT IO ()
tryAction = handle (\Interrupt -> outputStrLn "Cancelled.")
               $ withInterrupt $ someLongAction

The action can handle the interrupt itself; a new Interrupt exception will be thrown every time Ctrl-C is pressed.

tryAction :: InputT IO ()
tryAction = withInterrupt loop
    where loop = handle (\Interrupt -> outputStrLn "Cancelled; try again." >> loop)
                   someLongAction

This behavior differs from GHC's built-in Ctrl-C handling, which may immediately terminate the program after the second time that the user presses Ctrl-C.

handleInterrupt :: MonadException m => m a -> m a -> m a Source #

Catch and handle an exception of type Interrupt.

handleInterrupt f = handle $ \Interrupt -> f

Additional submodules