ImperativeHaskell-1.1.1.0: A library for writing Imperative style haskell.

PortabilityGADTs, EmptyDataDecls, GeneralizedNewtypeDeriving, MultiParamTypeClasses, FlexibleInstances
Stabilityexperimental
MaintainerMatthew Mirman <mmirman@andrew.cmu.edu>
Safe HaskellNone

Control.Monad.Imperative.Internals

Description

A module which defines the monad for ImperativeHaskell, and some control operator to interact with MIO

Synopsis

Documentation

modifyOp :: ValTp k => (a -> b -> a) -> V Var r a -> V k r b -> MIO r ()Source

modifyOp makes a modification assignment operator out of a binary haskell function. The suggested use is to replicate functionality of assignments like -= or %= from C style languages.

if' :: ValTp b => V b r Bool -> MIO r () -> MIO r ()Source

if'(check) act only performs act if check evaluates to true it is specifically a value in its argument.

for' :: ValTp b => (MIO r irr1, V b r Bool, MIO r irr2) -> MIO r () -> MIO r ()Source

for'(init, check, incr) acts like its imperative for counterpart

while' :: ValTp b => V b r Bool -> MIO r () -> MIO r ()Source

while'(check) acts like its imperative while counterpart.

break' :: MIO a ()Source

break' exists the current loop. if called outside of a loop, rather than throwing a compilation error, it will simply return a runtime error.

continue' :: MIO a ()Source

continue' continues the current loop, passing over any control flow that is defined. if called outside of a loop, rather than throwing a compilation error, it will simply return a runtime error.

return' :: (Returnable b r, ValTp a) => V a b b -> MIO b rSource

return' can act as returnF or returnV depending on use if it does not work, it is likely that type inference could not figure out a sensible alternative.

returnV :: ValTp a => V a b b -> MIO b ()Source

returnV value acts like the imperative return, where if called, it will exit the current function and place the returned value into the current continuation. Note, this doesn't work as a last function call.

returnF :: ValTp a => V a b b -> MIO b bSource

returnF value acts like the imperative return, where if called, it will exit the current function and place the returned value into the current continuation. Note, this doesn't work inside of loops. Inside of loops, we need returnV

function :: MIO a a -> MIO b aSource

function foo takes an ImperativeMonad action and removes it from it's specific function context, specifically making it applicable in the body of other functions.

new :: a -> MIO r (V Var r a)Source

new constructs a new reference to the specified pure value

auto :: aSource

auto should just be used where the type can be automatically infered and we don't need an initial value Use caution, as it is simply an alternate name for undefined

data V b r a whereSource

Constructors

Lit :: a -> V Val r a 
C :: ValTp b => MIO r (V b r a) -> V Comp r a 

Instances

ValTp b => Assignable (V b) 
Eq a => Eq (V Val r a) 
Num a => Num (V Val r a) 
Show a => Show (V Val r a) 
IsString s => IsString (V Val r s) 

class ValTp b Source

Instances

data MIO r a Source

Instances

Assignable MIO 
Monad (MIO r) 
MonadIO (MIO r) 
MonadCont (MIO r) 

data Comp Source

Instances

data Val Source

Instances

ValTp Val 
Eq a => Eq (V Val r a) 
Num a => Num (V Val r a) 
Show a => Show (V Val r a) 
IsString s => IsString (V Val r s) 

data Var Source

Instances

(=:) :: Assignable valt => V Var r a -> valt r a -> MIO r ()Source

variable =: value executes value and writes it to the location pointed to by variable

(&) :: V Var r a -> V Var s aSource

(&)a gets a reference/pointer to the variable specified

val :: ValTp b => V b r a -> MIO r aSource