| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
System.Console.Repline
Description
Repline exposes an additional monad transformer on top of Haskeline called HaskelineT. It simplifies several
aspects of composing Haskeline with State and Exception monads in modern versions of mtl.
type Repl a = HaskelineT IO a
The evaluator evalRepl evaluates a HaskelineT monad transformer by constructing a shell with several
custom functions and evaluating it inside of IO:
- Commands: Handled on ordinary input.
- Completions: Handled when tab key is pressed.
- Options: Handled when a command prefixed by a colon is entered.
- Banner: Text Displayed at initialization.
- Initializer: Run at initialization.
A simple evaluation function might simply echo the output back to the screen.
-- Evaluation : handle each line user inputs cmd :: String -> Repl () cmd input = liftIO $ print input
Several tab completion options are available, the most common is the WordCompleter which completes on single
words separated by spaces from a list of matches. The internal logic can be whatever is required and can also
access a StateT instance to query application state.
-- Tab Completion: return a completion for partial words entered completer :: Monad m => WordCompleter m completer n = do let names = ["kirk", "spock", "mccoy"] return $ filter (isPrefixOf n) names
Input which is prefixed by a colon (commands like ":type" and ":help") queries an association list of
functions which map to custom logic. The function takes a space-separated list of augments in it's first
argument. If the entire line is desired then the unwords function can be used to concatenate.
-- Commands help :: [String] -> Repl () help args = liftIO $ print $ "Help: " ++ show args say :: [String] -> Repl () say args = do _ <- liftIO $ system $ "cowsay" ++ " " ++ (unwords args) return ()
Now we need only map these functions to their commands.
options :: [(String, [String] -> Repl ())]
options = [
("help", help) -- :help
, ("say", say) -- :say
]The banner function is simply an IO action that is called at the start of the shell.
ini :: Repl () ini = liftIO $ putStrLn "Welcome!"
Putting it all together we have a little shell.
main :: IO () main = evalRepl ">>> " cmd options (Word completer) ini
Putting this in a file we can test out our cow-trek shell.
$ runhaskell Main.hs
Welcome!
>>> <TAB>
kirk spock mccoy
>>> k<TAB>
kirk
>>> spam
"spam"
>>> :say Hello Haskell
_______________
< Hello Haskell >
---------------
\ ^__^
\ (oo)\_______
(__)\ )\/\
||----w |
|| ||See https://github.com/sdiehl/repline for more examples.
- data HaskelineT m a
- runHaskelineT :: MonadException m => Settings m -> HaskelineT m a -> m a
- type Cmd m = [String] -> m ()
- type Options m = [(String, Cmd m)]
- type WordCompleter m = String -> m [String]
- type LineCompleter m = String -> String -> m [Completion]
- data CompleterStyle m
- = Word (WordCompleter m)
- | Word0 (WordCompleter m)
- | Cursor (LineCompleter m)
- | File
- | Prefix (CompletionFunc m) [(String, CompletionFunc m)]
- type Command m = String -> m ()
- type CompletionFunc m = (String, String) -> m (String, [Completion])
- wordCompleter :: Monad m => WordCompleter m -> CompletionFunc m
- listCompleter :: Monad m => [String] -> CompletionFunc m
- fileCompleter :: MonadIO m => CompletionFunc m
- listWordCompleter :: Monad m => [String] -> WordCompleter m
- runMatcher :: Monad m => [(String, CompletionFunc m)] -> CompletionFunc m -> CompletionFunc m
- evalRepl :: MonadException m => String -> Command (HaskelineT m) -> Options (HaskelineT m) -> CompleterStyle m -> HaskelineT m a -> m ()
- abort :: MonadIO m => HaskelineT m a
- tryAction :: MonadException m => HaskelineT m a -> HaskelineT m a
- trimComplete :: String -> Completion -> Completion
Documentation
data HaskelineT m a Source #
Instances
| MonadTrans HaskelineT Source # | |
| MonadState s m => MonadState s (HaskelineT m) Source # | |
| Monad m => Monad (HaskelineT m) Source # | |
| Functor m => Functor (HaskelineT m) Source # | |
| Applicative m => Applicative (HaskelineT m) Source # | |
| MonadIO m => MonadIO (HaskelineT m) Source # | |
| MonadException m => MonadException (HaskelineT m) Source # | |
runHaskelineT :: MonadException m => Settings m -> HaskelineT m a -> m a Source #
type WordCompleter m = String -> m [String] Source #
type LineCompleter m = String -> String -> m [Completion] Source #
data CompleterStyle m Source #
Constructors
| Word (WordCompleter m) | Completion function takes single word. |
| Word0 (WordCompleter m) | Completion function takes single word ( no space ). |
| Cursor (LineCompleter m) | Completion function takes tuple of full line. |
| File | Completion function completes files in CWD. |
| Prefix (CompletionFunc m) [(String, CompletionFunc m)] | Conditional tab completion based on prefix. |
type CompletionFunc m = (String, String) -> m (String, [Completion]) #
wordCompleter :: Monad m => WordCompleter m -> CompletionFunc m Source #
listCompleter :: Monad m => [String] -> CompletionFunc m Source #
fileCompleter :: MonadIO m => CompletionFunc m Source #
listWordCompleter :: Monad m => [String] -> WordCompleter m Source #
runMatcher :: Monad m => [(String, CompletionFunc m)] -> CompletionFunc m -> CompletionFunc m Source #
Arguments
| :: MonadException m | |
| => String | Banner |
| -> Command (HaskelineT m) | Command function |
| -> Options (HaskelineT m) | Options list and commands |
| -> CompleterStyle m | Tab completion function |
| -> HaskelineT m a | Initializer |
| -> m () |
Evaluate the REPL logic into a MonadException context.
abort :: MonadIO m => HaskelineT m a Source #
Abort the current REPL loop, and continue.
tryAction :: MonadException m => HaskelineT m a -> HaskelineT m a Source #
Wrap a HasklineT action so that if an interrupt is thrown the shell continues as normal.
trimComplete :: String -> Completion -> Completion Source #