Copyright | (c) Evgeny Poberezkin |
---|---|
License | MIT |
Maintainer | evgeny@poberezkin.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe |
Language | Haskell2010 |
This module provides functions to instantly create interactive REPL,
similar to Prelude interact
but with line-by-line processing:
- stateless REPL from a single argument functions
- REPL with state from plain state function or with State monad
- REPL-fold from two-arguments functions, with the accumulator in the first argument
Each line you enter is read
into the argument type and sent to the function, with the result printed.
Synopsis
- class Repl a b
- repl :: Repl a b => (a -> b) -> IO ()
- repl' :: (Eq a, Read a, Show b) => a -> (a -> b) -> IO ()
- pRepl :: Repl a b => String -> (a -> b) -> IO ()
- pRepl' :: forall a b. (Eq a, Read a, Show b) => String -> a -> (a -> b) -> IO ()
- class ReplState a b s | b -> s
- replState :: ReplState a b s => (a -> b) -> s -> IO ()
- replState' :: (Eq a, Read a, Show b) => a -> (a -> State s b) -> s -> IO ()
- pReplState :: ReplState a b s => String -> (a -> b) -> s -> IO ()
- pReplState' :: forall a b s. (Eq a, Read a, Show b) => String -> a -> (a -> State s b) -> s -> IO ()
- replFold :: (Read a, Show b) => (b -> a -> b) -> b -> IO ()
- replFold' :: (Eq a, Read a, Show b) => a -> (b -> a -> b) -> b -> IO ()
- pReplFold :: (Read a, Show b) => String -> (b -> a -> b) -> b -> IO ()
- pReplFold' :: (Eq a, Read a, Show b) => String -> a -> (b -> a -> b) -> b -> IO ()
Stateless REPL
Repl
typeclass with polymorphic stateless function repl
to interactively
evaluate input lines and print responses (see below).
Instances
(Read a, Show b) => Repl a b Source # | Ctrl-D to exit |
Repl String String Source # |
|
(Read a, Show b) => Repl a (Maybe b) Source # | return |
Repl String (Maybe String) Source # | |
(Read a, Show b) => Repl a (Either String b) Source # | |
Repl String (Either String String) Source # | |
(Read a, Show b) => Repl [a] [b] Source # | 'stdin'/'stdout' values as lazy lists |
Repl [String] [String] Source # | 'stdin'/'stdout' |
repl :: Repl a b => (a -> b) -> IO () Source #
Function passed to repl
will be called with values from stdin
(String
s or Read
instances, one value at a time or as a lazy list
depending on the type of the function) and should return value
to be printed to stdout
(String
or Show
instance, possibly
wrapped in Maybe
or Either
, one value at a time or as a lazy list) .
Specific behaviour depends on function type (see instances above).
Examples:
Print square roots of the entered numbers:
repl (sqrt :: Double -> Double)
Reverse entered strings:
repl (reverse :: String -> String)
Prints both squares and square roots:
sqrSqrt :: [Double] -> [Double] sqrSqrt [] = [] sqrSqrt (x:xs) = x^2 : sqrt x : sqrSqrt xs repl sqrSqrt
REPL with state
class ReplState a b s | b -> s Source #
ReplState
typeclass with polymorphic stateful function replState
to interactively evaluate input lines and print responses (see below).
Instances
(Read a, Show b) => ReplState a (State s (Either String b)) s Source # | |
(Read a, Show b) => ReplState a (State s (Maybe b)) s Source # | return |
(Read a, Show b) => ReplState a (State s b) s Source # | Ctrl-D to exit |
(Read a, Show b) => ReplState a (s -> (b, s)) s Source # | plain state function with argument and result of any 'Read'/'Show' types |
Defined in System.IO.Interact | |
ReplState String (s -> (String, s)) s Source # | plain state function with |
ReplState String (State s (Either String String)) s Source # | |
ReplState String (State s (Maybe String)) s Source # | |
ReplState String (State s String) s Source # |
|
ReplState [String] (State s [String]) s Source # | 'stdin'/'stdout' |
:: ReplState a b s | |
=> (a -> b) | state function (type defined by the instances) |
-> s | initial state |
-> IO () |
Function passed to replState
will be called with values from stdin
and previous state (depending on type, via State monad or
as the first argument) and should return value to be printed to stdout
and the new state (either via State monad or as a tuple).
Specific behaviour depends on function type (see instances above).
Examples:
Prints sums of entered numbers:
adder :: Int -> State Int Int adder x = modify (+ x) >> get replState adder 0
or with plain state function
adder :: Int -> Int -> (Int, Int) adder x s = let s' = s + x in (s', s') replState adder 0
Above can be done with replFold
(see below):
replFold (+) 0
but replState is more flexible - state and output can be different types.
replState' :: (Eq a, Read a, Show b) => a -> (a -> State s b) -> s -> IO () Source #
Same as replState
with (a -> State s b)
function but the first
argument is the value that will cause replState'
to exit.
pReplState :: ReplState a b s => String -> (a -> b) -> s -> IO () Source #
replState
with prompt defined by the first argument
:: (Eq a, Read a, Show b) | |
=> String | prompt |
-> a | value to stop |
-> (a -> State s b) | state function |
-> s | initial state |
-> IO () |
replState'
with prompt
REPL-fold
replFold :: (Read a, Show b) => (b -> a -> b) -> b -> IO () Source #
replFold
combines the entered values with the accumulated value using
provided function and prints the resulting values.