System.Console.Haskeline
Contents
- data InputT m a
- runInputT :: MonadException m => Settings m -> InputT m a -> m a
- runInputTWithPrefs :: MonadException m => Prefs -> Settings m -> InputT m a -> m a
- getInputLine :: forall m. MonadException m => String -> InputT m (Maybe String)
- outputStr :: forall m. MonadIO m => String -> InputT m ()
- outputStrLn :: MonadIO m => String -> InputT m ()
- data Settings m = Settings {}
- defaultSettings :: MonadIO m => Settings m
- setComplete :: CompletionFunc m -> Settings m -> Settings m
- data Interrupt = Interrupt
- handleInterrupt :: MonadException m => m a -> m a -> m a
- module System.Console.Haskeline.Completion
- module System.Console.Haskeline.Prefs
- module System.Console.Haskeline.MonadException
Main functions
An example use of this library for a simple read-eval-print loop is the following.
import System.Console.Haskeline
import Control.Monad.Trans
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
A monad transformer which carries all of the state and settings relevant to a line-reading application.
Instances
| MonadTrans InputT | |
| Monad m => MonadState History (InputT m) | |
| Monad m => MonadReader Prefs (InputT m) | |
| Monad m => Monad (InputT m) | |
| MonadIO m => MonadIO (InputT m) | |
| MonadException m => MonadException (InputT m) | |
| Monad m => MonadReader (RunTerm (InputCmdT m)) (InputT m) | |
| Monad m => MonadReader (Settings m) (InputT m) |
runInputT :: MonadException m => Settings m -> InputT m a -> m aSource
Run a line-reading application, reading user Prefs from
~/.haskeline
runInputTWithPrefs :: MonadException m => Prefs -> Settings m -> InputT m a -> m aSource
Arguments
| :: forall m . MonadException m | |
| => String | The input prompt |
| -> InputT m (Maybe String) |
Read one line of input from the user, with a rich line-editing
user interface. Returns Nothing if the user presses Ctrl-D when the input
text is empty. Otherwise, it returns the input line with the final newline
removed.
If stdin is not connected to a terminal (for example, piped from
another process), then this function is equivalent to getLine, except that
it returns Nothing if an EOF is encountered before any characters are
read.
If signal handling is enabled in the Settings, then getInputLine will
throw an Interrupt exception when the user presses Ctrl-C.
outputStr :: forall m. MonadIO m => String -> InputT m ()Source
Write a string to the console output. Allows cross-platform display of Unicode characters.
outputStrLn :: MonadIO m => String -> InputT m ()Source
Write a string to the console output, followed by a newline. Allows cross-platform display of Unicode characters.
Settings
Application-specific customizations to the user interface.
Constructors
| Settings | |
Fields
| |
defaultSettings :: MonadIO m => Settings mSource
A useful default. In particular:
defaultSettings = Settings {
complete = completeFilename,
historyFile = Nothing,
handleSigINT = False
}
setComplete :: CompletionFunc m -> Settings m -> Settings mSource
Ctrl-C handling
Arguments
| :: MonadException m | |
| => m a | Handler to run if Ctrl-C is pressed |
| -> m a | Computation to run |
| -> m a |
Catch and handle an exception of type Interrupt.