Safe Haskell | None |
---|---|
Language | Haskell2010 |
This libraries provides a polysemy effect that provides interactive command line usage.
Synopsis
- data Readline (m :: * -> *) a where
- GetInputLine :: String -> Readline m (Maybe String)
- GetInputLineWithInitial :: String -> (String, String) -> Readline m (Maybe String)
- GetInputChar :: String -> Readline m (Maybe Char)
- GetPassword :: Maybe Char -> String -> Readline m (Maybe String)
- WaitForAnyKey :: String -> Readline m Bool
- OutputStr :: String -> Readline m ()
- getInputLine :: forall r. MemberWithError Readline r => String -> Sem r (Maybe String)
- getInputLineWithInitial :: forall r. MemberWithError Readline r => String -> (String, String) -> Sem r (Maybe String)
- getInputChar :: forall r. MemberWithError Readline r => String -> Sem r (Maybe Char)
- getPassword :: forall r. MemberWithError Readline r => Maybe Char -> String -> Sem r (Maybe String)
- waitForAnyKey :: forall r. MemberWithError Readline r => String -> Sem r Bool
- outputStr :: forall r. MemberWithError Readline r => String -> Sem r ()
- outputStrLn :: Member Readline r => String -> Sem r ()
- runReadline :: forall m r a. (MonadIO m, MonadMask m, Member (Embed m) r) => Settings m -> Sem (Readline ': r) a -> Sem r a
- runReadlineFinal :: forall m r a. (MonadIO m, MonadMask m, Member (Final (InputT m)) r) => Sem (Readline ': r) a -> Sem r a
- interpretReadlineAsInputT :: forall m r a. (MonadIO m, MonadMask m, Member (Embed (InputT m)) r) => Sem (Readline ': r) a -> Sem r a
- data Settings (m :: Type -> Type) = Settings {}
- defaultSettings :: forall (m :: Type -> Type). MonadIO m => Settings m
- runInputT :: (MonadIO m, MonadMask m) => Settings m -> InputT m a -> m a
Effect and Actions
data Readline (m :: * -> *) a where Source #
For documentation on actions see haskeline's functions with the same name and similar type signatures.
GetInputLine :: String -> Readline m (Maybe String) | |
GetInputLineWithInitial :: String -> (String, String) -> Readline m (Maybe String) | |
GetInputChar :: String -> Readline m (Maybe Char) | |
GetPassword :: Maybe Char -> String -> Readline m (Maybe String) | |
WaitForAnyKey :: String -> Readline m Bool | |
OutputStr :: String -> Readline m () |
getInputLine :: forall r. MemberWithError Readline r => String -> Sem r (Maybe String) Source #
getInputLineWithInitial :: forall r. MemberWithError Readline r => String -> (String, String) -> Sem r (Maybe String) Source #
getInputChar :: forall r. MemberWithError Readline r => String -> Sem r (Maybe Char) Source #
getPassword :: forall r. MemberWithError Readline r => Maybe Char -> String -> Sem r (Maybe String) Source #
waitForAnyKey :: forall r. MemberWithError Readline r => String -> Sem r Bool Source #
Interpreters
runReadline :: forall m r a. (MonadIO m, MonadMask m, Member (Embed m) r) => Settings m -> Sem (Readline ': r) a -> Sem r a Source #
The simplest way to run a Readline effect. Immediately eliminates the
resulting InputT
. There is one problem with this approach however.
Internal details of polysemy cause runInputT
to be run once per effect
call (e.g. getInputLine "> " >> getInputLine "> "
will result in two calls
to runInputT
), and the History state of consecutive runs is not
preserved unless there is a history file. If you want history for your repl
there are therefore two recommended approaches:
- Provide a history file in the settings you specify. e.g.
runReadline (
. This is the easiest approach but technically suboptimal because the history file will be read between every different primitive effect call.defaultSettings
{historyFile = Just ".repl_history"}) - Use
interpretReadlineAsInputT
orrunReadlineFinal
and keep theInputT
around until after usingrunFinal
to escape polysemy land. This way state can be preserved between effect calls. For an example using this seeexamples/Echo.hs
.
runReadlineFinal :: forall m r a. (MonadIO m, MonadMask m, Member (Final (InputT m)) r) => Sem (Readline ': r) a -> Sem r a Source #
Interpreter for the somewhat common case of wanting to keep InputT around
until after runFinal
to ensure that state is preserved between subsequent
effects.
interpretReadlineAsInputT :: forall m r a. (MonadIO m, MonadMask m, Member (Embed (InputT m)) r) => Sem (Readline ': r) a -> Sem r a Source #
Interpret in terms of an embedded InputT
stack.
Re-exports from haskeline
data Settings (m :: Type -> Type) #
Application-specific customizations to the user interface.
Settings | |
|
Instances
(MonadIO m, MonadMask m) => CommandMonad (InputCmdT m) | |
Defined in System.Console.Haskeline.InputT runCompletion :: (String, String) -> InputCmdT m (String, [Completion]) |
defaultSettings :: forall (m :: Type -> Type). MonadIO m => Settings m #
A useful default. In particular:
defaultSettings = Settings { complete = completeFilename, historyFile = Nothing, autoAddHistory = True }
runInputT :: (MonadIO m, MonadMask m) => Settings m -> InputT m a -> m a #
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.