reflex-ghci-0.2.0.1: A GHCi widget library for use in reflex applications
Safe HaskellNone
LanguageHaskell2010

Reflex.Process.Repl

Description

  • Module: Reflex.Process.Repl
  • Description: Run repl-like processes in a reflex application.
Synopsis

Documentation

data Repl t Source #

Output of a repl session

Constructors

Repl 

Fields

data Cmd Source #

An individual command submitted to the repl, and its output

Constructors

Cmd 

Instances

Instances details
Eq Cmd Source # 
Instance details

Defined in Reflex.Process.Repl

Methods

(==) :: Cmd -> Cmd -> Bool Source #

(/=) :: Cmd -> Cmd -> Bool Source #

Ord Cmd Source # 
Instance details

Defined in Reflex.Process.Repl

Methods

compare :: Cmd -> Cmd -> Ordering Source #

(<) :: Cmd -> Cmd -> Bool Source #

(<=) :: Cmd -> Cmd -> Bool Source #

(>) :: Cmd -> Cmd -> Bool Source #

(>=) :: Cmd -> Cmd -> Bool Source #

max :: Cmd -> Cmd -> Cmd Source #

min :: Cmd -> Cmd -> Cmd Source #

Show Cmd Source # 
Instance details

Defined in Reflex.Process.Repl

data Accum Source #

An accumulator used to track and combine the repl's output streams

Constructors

Accum 

accumHandle :: (Int -> ByteString -> Bool) -> ByteString -> (Map Int Lines, Int, Lines) -> (Map Int Lines, Int, Lines) Source #

Accumulate a handle, grouping its output by prompts

accumHandles :: (Int -> ByteString -> Bool) -> These ByteString ByteString -> Accum -> Accum Source #

Accumulate the output of stdout and stderr, grouping the output lines of both by prompt

flushAccum :: Accum -> Accum Source #

Take all the pending output and consider it complete.

repl Source #

Arguments

:: forall t m. (Adjustable t m, MonadFix m, MonadHold t m, MonadIO (Performable m), MonadIO m, NotReady t m, PerformEvent t m, PostBuild t m, TriggerEvent t m) 
=> CreateProcess

Command to run to enter repl

-> Event t [Command]

Commands to send to the repl

-> (Int -> ByteString -> Bool)

Test for determining whether a line is the prompt we're waiting or

-> m (Repl t) 

Run a repl, feed it commands, and produce output grouped by those commands. The repl in question must be able to print its prompt on both stdout and stderr.

data Lines Source #

Accumulator for line-based output that keeps track of any dangling, unterminated line

Instances

Instances details
Eq Lines Source # 
Instance details

Defined in Reflex.Process.Repl

Methods

(==) :: Lines -> Lines -> Bool Source #

(/=) :: Lines -> Lines -> Bool Source #

Ord Lines Source # 
Instance details

Defined in Reflex.Process.Repl

Read Lines Source # 
Instance details

Defined in Reflex.Process.Repl

Show Lines Source # 
Instance details

Defined in Reflex.Process.Repl

Semigroup Lines Source # 
Instance details

Defined in Reflex.Process.Repl

Monoid Lines Source # 
Instance details

Defined in Reflex.Process.Repl

emptyLines :: Lines Source #

Empty output

addLines :: ByteString -> Lines -> Lines Source #

Add some raw output to a Lines. This will chop the raw output up into lines.

unLines :: Lines -> ByteString Source #

Convert a Lines back into a ByteString

lastWholeLine :: Lines -> Maybe ByteString Source #

Convenience accessor for the last whole line received by a Lines. Ignores any unterminated line that may follow.

splitLinesOn :: (ByteString -> Bool) -> Lines -> Maybe (Lines, Lines) Source #

Split lines into two. The sequence that satisfies the predicate is consumed and will not appear in either resulting Lines.

data Command Source #

A string that will be sent to the repl for evaluation. A newline will be appended to the end of the string. Commands should not themselves contain newlines.

unsafeCommand :: ByteString -> Command Source #

Constructs a Command without checking for newlines. If there are newlines in the input, things will not work properly.

command :: ByteString -> [Command] Source #

Convert a ByteString into a set of Commands. Any newlines found in the input are considered Command separators.

commands :: [ByteString] -> [Command] Source #

Convert a ByteString into a set of Commands. Any newlines found in the input are considered Command separators.

displayCommand :: Command -> ByteString Source #

Turn a command back into a ByteString.

sendCommands :: [Command] -> Maybe (SendPipe ByteString) Source #

Convert commands to a format that can be sent over stdin

testRepl :: IO () Source #

A headless repl test that runs ghci, executes some commands, and checks that the output is as expected.

mkTestCommands :: (PerformEvent t m, PostBuild t m, TriggerEvent t m, MonadIO (Performable m)) => m (Event t [Command]) Source #

Constructs some testing commands that are fed in on a timer

assertStdoutEq :: MonadIO m => String -> Maybe Cmd -> ByteString -> m Bool Source #

Check that stdout equals the given value

assertStderrEq :: MonadIO m => String -> Maybe Cmd -> ByteString -> m Bool Source #

Check that stderr equals the given value

assertStderr :: MonadIO m => String -> Maybe Cmd -> (Lines -> Bool) -> m Bool Source #

Test the contents of stderr

assertStdout :: MonadIO m => String -> Maybe Cmd -> (Lines -> Bool) -> m Bool Source #

Test the contents of stdout

assertHandleEq :: MonadIO m => (Cmd -> Lines) -> String -> Maybe Cmd -> ByteString -> m Bool Source #

Check that a handle equals the given value

assertHandle :: MonadIO m => (Cmd -> Lines) -> String -> Maybe Cmd -> (Lines -> Bool) -> m Bool Source #

Test the contents of a handle

assertCmd :: MonadIO m => String -> Maybe Cmd -> (Cmd -> Bool) -> m Bool Source #

Test that a repl command and its output satisfy the predicate