interact-0.2.0.0: instantly create REPL from any function

Copyright(c) Evgeny Poberezkin
LicenseMIT
Maintainerevgeny@poberezkin.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe
LanguageHaskell2010

System.IO.Interact

Contents

Description

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

Stateless REPL

class Repl a b Source #

Repl typeclass with polymorphic stateless function repl to interactively evaluate input lines and print responses (see below).

Minimal complete definition

pRepl

Instances
(Read a, Show b) => Repl a b Source #

Ctrl-D to exit

Instance details

Defined in System.IO.Interact

Methods

repl :: (a -> b) -> IO () Source #

pRepl :: String -> (a -> b) -> IO () Source #

Repl String String Source #

Strings do not use 'read'/'show'

Instance details

Defined in System.IO.Interact

Methods

repl :: (String -> String) -> IO () Source #

pRepl :: String -> (String -> String) -> IO () Source #

(Read a, Show b) => Repl a (Maybe b) Source #

return Nothing to exit

Instance details

Defined in System.IO.Interact

Methods

repl :: (a -> Maybe b) -> IO () Source #

pRepl :: String -> (a -> Maybe b) -> IO () Source #

Repl String (Maybe String) Source # 
Instance details

Defined in System.IO.Interact

Methods

repl :: (String -> Maybe String) -> IO () Source #

pRepl :: String -> (String -> Maybe String) -> IO () Source #

(Read a, Show b) => Repl a (Either String b) Source #

return Left to exit, string in Left is printed

Instance details

Defined in System.IO.Interact

Methods

repl :: (a -> Either String b) -> IO () Source #

pRepl :: String -> (a -> Either String b) -> IO () Source #

Repl String (Either String String) Source # 
Instance details

Defined in System.IO.Interact

(Read a, Show b) => Repl [a] [b] Source #

'stdin'/'stdout' values as lazy lists

Instance details

Defined in System.IO.Interact

Methods

repl :: ([a] -> [b]) -> IO () Source #

pRepl :: String -> ([a] -> [b]) -> IO () Source #

Repl [String] [String] Source #

'stdin'/'stdout' Strings as lazy lists

Instance details

Defined in System.IO.Interact

Methods

repl :: ([String] -> [String]) -> IO () Source #

pRepl :: String -> ([String] -> [String]) -> IO () Source #

repl :: Repl a b => (a -> b) -> IO () Source #

Function passed to repl will be called with values from stdin (Strings 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' :: (Eq a, Read a, Show b) => a -> (a -> b) -> IO () Source #

Same as repl with (a -> b) function but the first argument is the value that will cause repl' to exit.

pRepl :: Repl a b => String -> (a -> b) -> IO () Source #

pRepl is repl with prompt

Example:

pRepl ">" (sqrt :: Double -> Double)

pRepl' Source #

Arguments

:: (Eq a, Read a, Show b) 
=> String

prompt

-> a

value to stop

-> (a -> b)

function to transform the input

-> IO () 

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).

Minimal complete definition

pReplState

Instances
(Read a, Show b) => ReplState a (State s (Either String b)) s Source #

return Left to exit, string in Left is printed

Instance details

Defined in System.IO.Interact

Methods

replState :: (a -> State s (Either String b)) -> s -> IO () Source #

pReplState :: String -> (a -> State s (Either String b)) -> s -> IO () Source #

(Read a, Show b) => ReplState a (State s (Maybe b)) s Source #

return Nothing to exit

Instance details

Defined in System.IO.Interact

Methods

replState :: (a -> State s (Maybe b)) -> s -> IO () Source #

pReplState :: String -> (a -> State s (Maybe b)) -> s -> IO () Source #

(Read a, Show b) => ReplState a (State s b) s Source #

Ctrl-D to exit

Instance details

Defined in System.IO.Interact

Methods

replState :: (a -> State s b) -> s -> IO () Source #

pReplState :: String -> (a -> State s b) -> s -> IO () Source #

(Read a, Show b) => ReplState a (s -> (b, s)) s Source #

plain state function with argument and result of any 'Read'/'Show' types

Instance details

Defined in System.IO.Interact

Methods

replState :: (a -> s -> (b, s)) -> s -> IO () Source #

pReplState :: String -> (a -> s -> (b, s)) -> s -> IO () Source #

ReplState String (s -> (String, s)) s Source #

plain state function with Strings as argument and result

Instance details

Defined in System.IO.Interact

Methods

replState :: (String -> s -> (String, s)) -> s -> IO () Source #

pReplState :: String -> (String -> s -> (String, s)) -> s -> IO () Source #

ReplState String (State s (Either String String)) s Source # 
Instance details

Defined in System.IO.Interact

Methods

replState :: (String -> State s (Either String String)) -> s -> IO () Source #

pReplState :: String -> (String -> State s (Either String String)) -> s -> IO () Source #

ReplState String (State s (Maybe String)) s Source # 
Instance details

Defined in System.IO.Interact

Methods

replState :: (String -> State s (Maybe String)) -> s -> IO () Source #

pReplState :: String -> (String -> State s (Maybe String)) -> s -> IO () Source #

ReplState String (State s String) s Source #

Strings do not use 'read'/'show'

Instance details

Defined in System.IO.Interact

Methods

replState :: (String -> State s String) -> s -> IO () Source #

pReplState :: String -> (String -> State s String) -> s -> IO () Source #

ReplState [String] (State s [String]) s Source #

'stdin'/'stdout' Strings as lazy lists

Instance details

Defined in System.IO.Interact

Methods

replState :: ([String] -> State s [String]) -> s -> IO () Source #

pReplState :: String -> ([String] -> State s [String]) -> s -> IO () Source #

replState Source #

Arguments

:: 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

pReplState' Source #

Arguments

:: (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.

replFold' :: (Eq a, Read a, Show b) => a -> (b -> a -> b) -> b -> IO () Source #

Same as replFold but the first argument is the value that will cause replFold' to exit.

pReplFold :: (Read a, Show b) => String -> (b -> a -> b) -> b -> IO () Source #

replFold with prompt

pReplFold' Source #

Arguments

:: (Eq a, Read a, Show b) 
=> String

prompt

-> a

value to stop

-> (b -> a -> b)

folding function

-> b

initial value

-> IO () 

replFold' with prompt