ImperativeHaskell-2.0.0.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 :: (HasValue r (V TyVar r) i, HasValue r (V k r) i) => (a -> b -> a) -> V TyVar r a -> V k r b -> MIO i 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' :: (HasValue r (V b r) i, HasValue r valt i) => V b r Bool -> valt () -> MIO i r ()Source

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

for' :: (CState i, HasValue r (V b r) i, HasValue r valt TyInLoop) => (MIO i r irr1, V b r Bool, MIO i r irr2) -> valt () -> MIO i r ()Source

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

while' :: (HasValue r (V b r) i, HasValue r (V b r) TyInLoop, HasValue r valt TyInLoop, CState i) => V b r Bool -> valt () -> MIO i r ()Source

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

break' :: MIO TyInLoop r ()Source

break' exists the current loop.

continue' :: MIO TyInLoop r ()Source

continue' continues the current loop, passing over any control flow that is defined.

defer' :: HasValue r valt TyInFunc => valt a -> MIO i r ()Source

defer' executes the given action (or value) before the function returns.

function :: MIO TyInFunc a a -> MIO i 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 :: HasValue r (V TyVar r) i => a -> MIO i r (V TyVar 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

runImperative :: MIO TyInFunc a a -> IO aSource

runImperative takes an MIO action as returned by a function, and lifts it into IO.

io :: IO a -> MIO TyInFunc r aSource

io action takes a haskell IO action and makes it useable from within the MIO monad.

data V b r a whereSource

Constructors

Lit :: a -> V TyVal r a 
C :: MIO i r (V b r a) -> V (TyComp i b) r a 

Instances

HasValue r (V b r) a => HasValue r (V (TyComp a b) r) a 
HasValue r (V TyVal r) i 
HasValue r (V TyVar r) i 
Eq a => Eq (V TyVal r a) 
Num a => Num (V TyVal r a) 
Show a => Show (V TyVal r a) 
IsString s => IsString (V TyVal r s) 

data MIO i r a Source

Instances

HasValue r (MIO i r) i 
Monad (MIO i r) 
MonadIO (MIO i r) 
MonadCont (MIO i r) 

data TyVar Source

Instances

HasValue r (V TyVar r) i 

data TyVal Source

Instances

HasValue r (V TyVal r) i 
Eq a => Eq (V TyVal r a) 
Num a => Num (V TyVal r a) 
Show a => Show (V TyVal r a) 
IsString s => IsString (V TyVal r s) 

data TyComp i v Source

Instances

HasValue r (V b r) a => HasValue r (V (TyComp a b) r) a 

(=:) :: (HasValue r valt i, HasValue r (V TyVar r) i) => V TyVar r a -> valt a -> MIO i r ()Source

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

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

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

class HasValue r b i | b -> r i whereSource

Although the functional dependency b -> i is declared, it does not do anything useful.

Methods

val :: b a -> MIO i r aSource

Instances

HasValue r IO i 
HasValue r (MIO i r) i 
HasValue r (V b r) a => HasValue r (V (TyComp a b) r) a 
HasValue r (V TyVal r) i 
HasValue r (V TyVar r) i 

class CState i whereSource

Methods

return' :: HasValue r (V a r) i => V a r r -> MIO i r (RetTy i r)Source

return' value acts like an imperative return. It passes the given value to the return continuation.