Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
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
- data InputT m a
- runInputT :: (MonadIO m, MonadMask m) => Settings m -> InputT m a -> m a
- haveTerminalUI :: Monad m => InputT m Bool
- mapInputT :: (forall b. m b -> m b) -> InputT m a -> InputT m a
- data Behavior
- runInputTBehavior :: (MonadIO m, MonadMask m) => Behavior -> Settings m -> InputT m a -> m a
- defaultBehavior :: Behavior
- useFileHandle :: Handle -> Behavior
- useFile :: FilePath -> Behavior
- preferTerm :: Behavior
- getInputLine :: (MonadIO m, MonadMask m) => String -> InputT m (Maybe String)
- getInputLineWithInitial :: (MonadIO m, MonadMask m) => String -> (String, String) -> InputT m (Maybe String)
- getInputChar :: (MonadIO m, MonadMask m) => String -> InputT m (Maybe Char)
- getPassword :: (MonadIO m, MonadMask m) => Maybe Char -> String -> InputT m (Maybe String)
- waitForAnyKey :: (MonadIO m, MonadMask m) => String -> InputT m Bool
- outputStr :: MonadIO m => String -> InputT m ()
- outputStrLn :: MonadIO m => String -> InputT m ()
- getExternalPrint :: MonadIO m => InputT m (String -> IO ())
- data Settings m = Settings {}
- defaultSettings :: MonadIO m => Settings m
- setComplete :: CompletionFunc m -> Settings m -> Settings m
- data Prefs
- readPrefs :: FilePath -> IO Prefs
- defaultPrefs :: Prefs
- runInputTWithPrefs :: (MonadIO m, MonadMask m) => Prefs -> Settings m -> InputT m a -> m a
- runInputTBehaviorWithPrefs :: (MonadIO m, MonadMask m) => Behavior -> Prefs -> Settings m -> InputT m a -> m a
- withRunInBase :: Monad m => ((forall a. InputT m a -> m a) -> m b) -> InputT m b
- getHistory :: MonadIO m => InputT m History
- putHistory :: MonadIO m => History -> InputT m ()
- modifyHistory :: MonadIO m => (History -> History) -> InputT m ()
- withInterrupt :: (MonadIO m, MonadMask m) => InputT m a -> InputT m a
- data Interrupt = Interrupt
- handleInterrupt :: MonadMask m => m a -> m a -> m a
- module System.Console.Haskeline.Completion
Interactive sessions
The InputT monad transformer
A monad transformer which carries all of the state and settings relevant to a line-reading application.
Instances
MonadTrans InputT Source # | |
Defined in System.Console.Haskeline.InputT | |
MonadFail m => MonadFail (InputT m) Source # | |
Defined in System.Console.Haskeline.InputT | |
MonadFix m => MonadFix (InputT m) Source # | |
Defined in System.Console.Haskeline.InputT | |
MonadIO m => MonadIO (InputT m) Source # | |
Defined in System.Console.Haskeline.InputT | |
Applicative m => Applicative (InputT m) Source # | |
Functor m => Functor (InputT m) Source # | |
Monad m => Monad (InputT m) Source # | |
MonadCatch m => MonadCatch (InputT m) Source # | |
MonadMask m => MonadMask (InputT m) Source # | |
Defined in System.Console.Haskeline.InputT | |
MonadThrow m => MonadThrow (InputT m) Source # | |
Defined in System.Console.Haskeline.InputT |
runInputT :: (MonadIO m, MonadMask 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
. It
uses terminal-style interaction if runInputTBehavior
defaultBehavior
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.
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
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
orstdout
). - "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 tostdout
.
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 :: (MonadIO m, MonadMask m) => Behavior -> Settings m -> InputT m a -> m a Source #
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.
User interaction functions
Reading user input
The following functions read one line or character of input from the user.
They return Nothing
if they encounter the end of input. More specifically:
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
and the line input is nonblank (i.e., is not all
spaces), it will be automatically added to the history.autoAddHistory
== True
getInputLineWithInitial Source #
:: (MonadIO m, MonadMask 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 String
s. 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.
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.
:: (MonadIO m, MonadMask m) | |
=> Maybe Char | A masking character; e.g., |
-> 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).
Waits for one key to be pressed, then returns. Ignores the value of the specific key.
Returns True
if it successfully accepted one key. Returns False
if it encountered the end of input; i.e., an EOF
in file-style interaction,
or a Ctrl-D
in terminal-style interaction.
When using file-style interaction, consumes a single character from the input which may be non-printable.
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 :: MonadIO 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
Application-specific customizations to the user interface.
Settings | |
|
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 #
User preferences
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
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 :: (MonadIO m, MonadMask m) => Prefs -> Settings m -> InputT m a -> m a Source #
Run a line-reading application. Uses defaultBehavior
to determine the
interaction behavior.
runInputTBehaviorWithPrefs :: (MonadIO m, MonadMask m) => Behavior -> Prefs -> Settings m -> InputT m a -> m a Source #
Run a line-reading application.
withRunInBase :: Monad m => ((forall a. InputT m a -> m a) -> m b) -> InputT m b Source #
Run an action in the underlying monad, as per lift
, passing it a runner
function which restores the current InputT
context. This can be used in
the event that we have some function that takes an action in the underlying
monad as an argument (such as lift
, hoist
, forkIO
, etc) and we want
to compose it with actions in InputT
.
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.
modifyHistory :: MonadIO m => (History -> History) -> InputT m () Source #
Change the current line input history.
Ctrl-C handling
withInterrupt :: (MonadIO m, MonadMask 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.
Instances
Exception Interrupt Source # | |
Defined in System.Console.Haskeline.Term toException :: Interrupt -> SomeException # fromException :: SomeException -> Maybe Interrupt # displayException :: Interrupt -> String # | |
Show Interrupt Source # | |
Eq Interrupt Source # | |
handleInterrupt :: MonadMask m => m a -> m a -> m a Source #
Catch and handle an exception of type Interrupt
.
handleInterrupt f = handle $ \Interrupt -> f