{-# LANGUAGE PostfixOperators #-}
module GOOL.Drasil.LanguageRenderer.Macros (
ifExists, decrement1, increment, increment1, runStrategy,
listSlice, stringListVals, stringListLists, forRange, notifyObservers,
notifyObservers', checkState
) where
import GOOL.Drasil.CodeType (CodeType(..))
import GOOL.Drasil.ClassInterface (Label, MSBody, MSBlock, VSType, SVariable,
SValue, VSFunction, MSStatement, bodyStatements, oneLiner, TypeElim(getType),
VariableElim(variableType), listOf, ValueSym(valueType),
NumericExpression((#+), (#*), (#/)), Comparison(..), at, ($.),
StatementSym(multi), AssignStatement((&+=), (&-=), (&++)), (&=),
observerListName)
import qualified GOOL.Drasil.ClassInterface as S (BlockSym(block),
TypeSym(int, string, listInnerType), VariableSym(var), Literal(litInt),
VariableValue(valueOf), ValueExpression(notNull),
List(listSize, listAppend, listAccess), StatementSym(valStmt),
AssignStatement(assign), DeclStatement(varDecDef, listDec),
ControlStatement(ifCond, switch, for, forRange))
import GOOL.Drasil.RendererClasses (RenderSym, RenderValue(cast))
import qualified GOOL.Drasil.RendererClasses as S (
RenderStatement(stmt, emptyStmt))
import qualified GOOL.Drasil.RendererClasses as RC (BodyElim(..),
StatementElim(statement))
import GOOL.Drasil.Helpers (toCode, onStateValue, on2StateValues)
import GOOL.Drasil.State (MS, lensMStoVS)
import Data.Maybe (fromMaybe)
import Control.Lens.Zoom (zoom)
import Text.PrettyPrint.HughesPJ (Doc, vcat)
ifExists :: (RenderSym r) => SValue r -> MSBody r -> MSBody r -> MSStatement r
ifExists :: SValue r -> MSBody r -> MSBody r -> MSStatement r
ifExists v :: SValue r
v ifBody :: MSBody r
ifBody = [(SValue r, MSBody r)] -> MSBody r -> MSStatement r
forall (r :: * -> *).
ControlStatement r =>
[(SValue r, MSBody r)] -> MSBody r -> MSStatement r
S.ifCond [(SValue r -> SValue r
forall (r :: * -> *). ValueExpression r => SValue r -> SValue r
S.notNull SValue r
v, MSBody r
ifBody)]
decrement1 :: (RenderSym r) => SVariable r -> MSStatement r
decrement1 :: SVariable r -> MSStatement r
decrement1 v :: SVariable r
v = SVariable r
v SVariable r -> SValue r -> MSStatement r
forall (r :: * -> *).
AssignStatement r =>
SVariable r -> SValue r -> MSStatement r
&-= Integer -> SValue r
forall (r :: * -> *). Literal r => Integer -> SValue r
S.litInt 1
increment :: (RenderSym r) => SVariable r -> SValue r -> MSStatement r
increment :: SVariable r -> SValue r -> MSStatement r
increment vr :: SVariable r
vr vl :: SValue r
vl = SVariable r
vr SVariable r -> SValue r -> MSStatement r
forall (r :: * -> *).
AssignStatement r =>
SVariable r -> SValue r -> MSStatement r
&= SVariable r -> SValue r
forall (r :: * -> *). VariableValue r => SVariable r -> SValue r
S.valueOf SVariable r
vr SValue r -> SValue r -> SValue r
forall (r :: * -> *).
NumericExpression r =>
SValue r -> SValue r -> SValue r
#+ SValue r
vl
increment1 :: (RenderSym r) => SVariable r -> MSStatement r
increment1 :: SVariable r -> MSStatement r
increment1 vr :: SVariable r
vr = SVariable r
vr SVariable r -> SValue r -> MSStatement r
forall (r :: * -> *).
AssignStatement r =>
SVariable r -> SValue r -> MSStatement r
&+= Integer -> SValue r
forall (r :: * -> *). Literal r => Integer -> SValue r
S.litInt 1
strat :: (RenderSym r, Monad r) => MSStatement r -> MSBody r -> MS (r Doc)
strat :: MSStatement r -> MSBody r -> MS (r Doc)
strat = (r (Statement r) -> r (Body r) -> r Doc)
-> MSStatement r -> MSBody r -> MS (r Doc)
forall a b c s.
(a -> b -> c) -> State s a -> State s b -> State s c
on2StateValues (\result :: r (Statement r)
result b :: r (Body r)
b -> Doc -> r Doc
forall (r :: * -> *) a. Monad r => a -> r a
toCode (Doc -> r Doc) -> Doc -> r Doc
forall a b. (a -> b) -> a -> b
$ [Doc] -> Doc
vcat [r (Body r) -> Doc
forall (r :: * -> *). BodyElim r => r (Body r) -> Doc
RC.body r (Body r)
b,
r (Statement r) -> Doc
forall (r :: * -> *). StatementElim r => r (Statement r) -> Doc
RC.statement r (Statement r)
result])
runStrategy :: (RenderSym r, Monad r) => Label -> [(Label, MSBody r)] ->
Maybe (SValue r) -> Maybe (SVariable r) -> MS (r Doc)
runStrategy :: Label
-> [(Label, MSBody r)]
-> Maybe (SValue r)
-> Maybe (SVariable r)
-> MS (r Doc)
runStrategy l :: Label
l strats :: [(Label, MSBody r)]
strats rv :: Maybe (SValue r)
rv av :: Maybe (SVariable r)
av = MS (r Doc)
-> (MSBody r -> MS (r Doc)) -> Maybe (MSBody r) -> MS (r Doc)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
(Label -> Label -> MS (r Doc)
forall a. Label -> Label -> a
strError Label
l "RunStrategy called on non-existent strategy")
(MSStatement r -> MSBody r -> MS (r Doc)
forall (r :: * -> *).
(RenderSym r, Monad r) =>
MSStatement r -> MSBody r -> MS (r Doc)
strat (MSStatement r -> MSStatement r
forall (r :: * -> *).
RenderStatement r =>
MSStatement r -> MSStatement r
S.stmt MSStatement r
resultState)) (Label -> [(Label, MSBody r)] -> Maybe (MSBody r)
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Label
l [(Label, MSBody r)]
strats)
where resultState :: MSStatement r
resultState = MSStatement r
-> (SVariable r -> MSStatement r)
-> Maybe (SVariable r)
-> MSStatement r
forall b a. b -> (a -> b) -> Maybe a -> b
maybe MSStatement r
forall (r :: * -> *). RenderStatement r => MSStatement r
S.emptyStmt SVariable r -> MSStatement r
asgState Maybe (SVariable r)
av
asgState :: SVariable r -> MSStatement r
asgState v :: SVariable r
v = MSStatement r
-> (SValue r -> MSStatement r) -> Maybe (SValue r) -> MSStatement r
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Label -> Label -> MSStatement r
forall a. Label -> Label -> a
strError Label
l
"Attempt to assign null return to a Value") (SVariable r
v SVariable r -> SValue r -> MSStatement r
forall (r :: * -> *).
AssignStatement r =>
SVariable r -> SValue r -> MSStatement r
&=) Maybe (SValue r)
rv
strError :: Label -> Label -> a
strError n :: Label
n s :: Label
s = Label -> a
forall a. HasCallStack => Label -> a
error (Label -> a) -> Label -> a
forall a b. (a -> b) -> a -> b
$ "Strategy '" Label -> Label -> Label
forall a. [a] -> [a] -> [a]
++ Label
n Label -> Label -> Label
forall a. [a] -> [a] -> [a]
++ "': " Label -> Label -> Label
forall a. [a] -> [a] -> [a]
++ Label
s Label -> Label -> Label
forall a. [a] -> [a] -> [a]
++ "."
listSlice :: (RenderSym r) => Maybe (SValue r) -> Maybe (SValue r) ->
Maybe (SValue r) -> SVariable r -> SValue r -> MSBlock r
listSlice :: Maybe (SValue r)
-> Maybe (SValue r)
-> Maybe (SValue r)
-> SVariable r
-> SValue r
-> MSBlock r
listSlice b :: Maybe (SValue r)
b e :: Maybe (SValue r)
e s :: Maybe (SValue r)
s vnew :: SVariable r
vnew vold :: SValue r
vold =
let l_temp :: Label
l_temp = "temp"
var_temp :: SVariable r
var_temp = Label -> VSType r -> SVariable r
forall (r :: * -> *).
VariableSym r =>
Label -> VSType r -> SVariable r
S.var Label
l_temp ((r (Variable r) -> r (Type r)) -> SVariable r -> VSType r
forall a b s. (a -> b) -> State s a -> State s b
onStateValue r (Variable r) -> r (Type r)
forall (r :: * -> *).
VariableElim r =>
r (Variable r) -> r (Type r)
variableType SVariable r
vnew)
v_temp :: SValue r
v_temp = SVariable r -> SValue r
forall (r :: * -> *). VariableValue r => SVariable r -> SValue r
S.valueOf SVariable r
var_temp
l_i :: Label
l_i = "i_temp"
var_i :: SVariable r
var_i = Label -> VSType r -> SVariable r
forall (r :: * -> *).
VariableSym r =>
Label -> VSType r -> SVariable r
S.var Label
l_i VSType r
forall (r :: * -> *). TypeSym r => VSType r
S.int
v_i :: SValue r
v_i = SVariable r -> SValue r
forall (r :: * -> *). VariableValue r => SVariable r -> SValue r
S.valueOf SVariable r
var_i
in
[MSStatement r] -> MSBlock r
forall (r :: * -> *). BlockSym r => [MSStatement r] -> MSBlock r
S.block [
Integer -> SVariable r -> MSStatement r
forall (r :: * -> *).
DeclStatement r =>
Integer -> SVariable r -> MSStatement r
S.listDec 0 SVariable r
var_temp,
MSStatement r
-> SValue r -> MSStatement r -> MSBody r -> MSStatement r
forall (r :: * -> *).
ControlStatement r =>
MSStatement r
-> SValue r -> MSStatement r -> MSBody r -> MSStatement r
S.for (SVariable r -> SValue r -> MSStatement r
forall (r :: * -> *).
DeclStatement r =>
SVariable r -> SValue r -> MSStatement r
S.varDecDef SVariable r
var_i (SValue r -> Maybe (SValue r) -> SValue r
forall a. a -> Maybe a -> a
fromMaybe (Integer -> SValue r
forall (r :: * -> *). Literal r => Integer -> SValue r
S.litInt 0) Maybe (SValue r)
b))
(SValue r
v_i SValue r -> SValue r -> SValue r
forall (r :: * -> *).
Comparison r =>
SValue r -> SValue r -> SValue r
?< SValue r -> Maybe (SValue r) -> SValue r
forall a. a -> Maybe a -> a
fromMaybe (SValue r -> SValue r
forall (r :: * -> *). List r => SValue r -> SValue r
S.listSize SValue r
vold) Maybe (SValue r)
e) (MSStatement r
-> (SValue r -> MSStatement r) -> Maybe (SValue r) -> MSStatement r
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (SVariable r
var_i SVariable r -> MSStatement r
forall (r :: * -> *).
AssignStatement r =>
SVariable r -> MSStatement r
&++) (SVariable r
var_i SVariable r -> SValue r -> MSStatement r
forall (r :: * -> *).
AssignStatement r =>
SVariable r -> SValue r -> MSStatement r
&+=) Maybe (SValue r)
s)
(MSStatement r -> MSBody r
forall (r :: * -> *). BodySym r => MSStatement r -> MSBody r
oneLiner (MSStatement r -> MSBody r) -> MSStatement r -> MSBody r
forall a b. (a -> b) -> a -> b
$ SValue r -> MSStatement r
forall (r :: * -> *). StatementSym r => SValue r -> MSStatement r
S.valStmt (SValue r -> MSStatement r) -> SValue r -> MSStatement r
forall a b. (a -> b) -> a -> b
$ SValue r -> SValue r -> SValue r
forall (r :: * -> *). List r => SValue r -> SValue r -> SValue r
S.listAppend SValue r
v_temp (SValue r -> SValue r -> SValue r
forall (r :: * -> *). List r => SValue r -> SValue r -> SValue r
S.listAccess SValue r
vold SValue r
v_i)),
SVariable r
vnew SVariable r -> SValue r -> MSStatement r
forall (r :: * -> *).
AssignStatement r =>
SVariable r -> SValue r -> MSStatement r
&= SValue r
v_temp]
stringListVals :: (RenderSym r) => [SVariable r] -> SValue r -> MSStatement r
stringListVals :: [SVariable r] -> SValue r -> MSStatement r
stringListVals vars :: [SVariable r]
vars sl :: SValue r
sl = LensLike'
(Zoomed (StateT ValueState Identity) (r (Value r)))
MethodState
ValueState
-> SValue r -> StateT MethodState Identity (r (Value r))
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
zoom LensLike'
(Zoomed (StateT ValueState Identity) (r (Value r)))
MethodState
ValueState
Lens' MethodState ValueState
lensMStoVS SValue r
sl StateT MethodState Identity (r (Value r))
-> (r (Value r) -> MSStatement r) -> MSStatement r
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (\slst :: r (Value r)
slst -> [MSStatement r] -> MSStatement r
forall (r :: * -> *).
StatementSym r =>
[MSStatement r] -> MSStatement r
multi ([MSStatement r] -> MSStatement r)
-> [MSStatement r] -> MSStatement r
forall a b. (a -> b) -> a -> b
$ CodeType -> [MSStatement r]
checkList
(r (Type r) -> CodeType
forall (r :: * -> *). TypeElim r => r (Type r) -> CodeType
getType (r (Type r) -> CodeType) -> r (Type r) -> CodeType
forall a b. (a -> b) -> a -> b
$ r (Value r) -> r (Type r)
forall (r :: * -> *). ValueSym r => r (Value r) -> r (Type r)
valueType r (Value r)
slst))
where checkList :: CodeType -> [MSStatement r]
checkList (List String) = [SVariable r] -> Integer -> [MSStatement r]
assignVals [SVariable r]
vars 0
checkList _ = Label -> [MSStatement r]
forall a. HasCallStack => Label -> a
error
"Value passed to stringListVals must be a list of strings"
assignVals :: [SVariable r] -> Integer -> [MSStatement r]
assignVals [] _ = []
assignVals (v :: SVariable r
v:vs :: [SVariable r]
vs) n :: Integer
n = SVariable r -> SValue r -> MSStatement r
forall (r :: * -> *).
AssignStatement r =>
SVariable r -> SValue r -> MSStatement r
S.assign SVariable r
v (VSType r -> SValue r -> SValue r
forall (r :: * -> *).
RenderValue r =>
VSType r -> SValue r -> SValue r
cast ((r (Variable r) -> r (Type r)) -> SVariable r -> VSType r
forall a b s. (a -> b) -> State s a -> State s b
onStateValue r (Variable r) -> r (Type r)
forall (r :: * -> *).
VariableElim r =>
r (Variable r) -> r (Type r)
variableType SVariable r
v)
(SValue r -> SValue r -> SValue r
forall (r :: * -> *). List r => SValue r -> SValue r -> SValue r
S.listAccess SValue r
sl (Integer -> SValue r
forall (r :: * -> *). Literal r => Integer -> SValue r
S.litInt Integer
n))) MSStatement r -> [MSStatement r] -> [MSStatement r]
forall a. a -> [a] -> [a]
: [SVariable r] -> Integer -> [MSStatement r]
assignVals [SVariable r]
vs (Integer
nInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
+1)
stringListLists :: (RenderSym r) => [SVariable r] -> SValue r -> MSStatement r
stringListLists :: [SVariable r] -> SValue r -> MSStatement r
stringListLists lsts :: [SVariable r]
lsts sl :: SValue r
sl = LensLike'
(Zoomed (StateT ValueState Identity) (r (Value r)))
MethodState
ValueState
-> SValue r -> StateT MethodState Identity (r (Value r))
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
zoom LensLike'
(Zoomed (StateT ValueState Identity) (r (Value r)))
MethodState
ValueState
Lens' MethodState ValueState
lensMStoVS SValue r
sl StateT MethodState Identity (r (Value r))
-> (r (Value r) -> MSStatement r) -> MSStatement r
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (\slst :: r (Value r)
slst -> CodeType -> MSStatement r
checkList (r (Type r) -> CodeType
forall (r :: * -> *). TypeElim r => r (Type r) -> CodeType
getType (r (Type r) -> CodeType) -> r (Type r) -> CodeType
forall a b. (a -> b) -> a -> b
$
r (Value r) -> r (Type r)
forall (r :: * -> *). ValueSym r => r (Value r) -> r (Type r)
valueType r (Value r)
slst))
where checkList :: CodeType -> MSStatement r
checkList (List String) = (SVariable r -> StateT MethodState Identity (r (Variable r)))
-> [SVariable r] -> StateT MethodState Identity [r (Variable r)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (LensLike'
(Zoomed (StateT ValueState Identity) (r (Variable r)))
MethodState
ValueState
-> SVariable r -> StateT MethodState Identity (r (Variable r))
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
zoom LensLike'
(Zoomed (StateT ValueState Identity) (r (Variable r)))
MethodState
ValueState
Lens' MethodState ValueState
lensMStoVS) [SVariable r]
lsts StateT MethodState Identity [r (Variable r)]
-> ([r (Variable r)] -> MSStatement r) -> MSStatement r
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [CodeType] -> MSStatement r
listVals ([CodeType] -> MSStatement r)
-> ([r (Variable r)] -> [CodeType])
-> [r (Variable r)]
-> MSStatement r
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
(r (Variable r) -> CodeType) -> [r (Variable r)] -> [CodeType]
forall a b. (a -> b) -> [a] -> [b]
map (r (Type r) -> CodeType
forall (r :: * -> *). TypeElim r => r (Type r) -> CodeType
getType (r (Type r) -> CodeType)
-> (r (Variable r) -> r (Type r)) -> r (Variable r) -> CodeType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. r (Variable r) -> r (Type r)
forall (r :: * -> *).
VariableElim r =>
r (Variable r) -> r (Type r)
variableType)
checkList _ = Label -> MSStatement r
forall a. HasCallStack => Label -> a
error
"Value passed to stringListLists must be a list of strings"
listVals :: [CodeType] -> MSStatement r
listVals [] = MSStatement r
loop
listVals (List _:vs :: [CodeType]
vs) = [CodeType] -> MSStatement r
listVals [CodeType]
vs
listVals _ = Label -> MSStatement r
forall a. HasCallStack => Label -> a
error
"All values passed to stringListLists must have list types"
loop :: MSStatement r
loop = SVariable r
-> SValue r -> SValue r -> SValue r -> MSBody r -> MSStatement r
forall (r :: * -> *).
ControlStatement r =>
SVariable r
-> SValue r -> SValue r -> SValue r -> MSBody r -> MSStatement r
S.forRange SVariable r
var_i (Integer -> SValue r
forall (r :: * -> *). Literal r => Integer -> SValue r
S.litInt 0) (SValue r -> SValue r
forall (r :: * -> *). List r => SValue r -> SValue r
S.listSize SValue r
sl SValue r -> SValue r -> SValue r
forall (r :: * -> *).
NumericExpression r =>
SValue r -> SValue r -> SValue r
#/ SValue r
numLists)
(Integer -> SValue r
forall (r :: * -> *). Literal r => Integer -> SValue r
S.litInt 1) ([MSStatement r] -> MSBody r
forall (r :: * -> *). BodySym r => [MSStatement r] -> MSBody r
bodyStatements ([MSStatement r] -> MSBody r) -> [MSStatement r] -> MSBody r
forall a b. (a -> b) -> a -> b
$ [SValue r] -> Integer -> [MSStatement r]
appendLists ((SVariable r -> SValue r) -> [SVariable r] -> [SValue r]
forall a b. (a -> b) -> [a] -> [b]
map SVariable r -> SValue r
forall (r :: * -> *). VariableValue r => SVariable r -> SValue r
S.valueOf [SVariable r]
lsts) 0)
appendLists :: [SValue r] -> Integer -> [MSStatement r]
appendLists [] _ = []
appendLists (v :: SValue r
v:vs :: [SValue r]
vs) n :: Integer
n = SValue r -> MSStatement r
forall (r :: * -> *). StatementSym r => SValue r -> MSStatement r
S.valStmt (SValue r -> SValue r -> SValue r
forall (r :: * -> *). List r => SValue r -> SValue r -> SValue r
S.listAppend SValue r
v (VSType r -> SValue r -> SValue r
forall (r :: * -> *).
RenderValue r =>
VSType r -> SValue r -> SValue r
cast
(VSType r -> VSType r
forall (r :: * -> *). TypeSym r => VSType r -> VSType r
S.listInnerType (VSType r -> VSType r) -> VSType r -> VSType r
forall a b. (a -> b) -> a -> b
$ (r (Value r) -> r (Type r)) -> SValue r -> VSType r
forall a b s. (a -> b) -> State s a -> State s b
onStateValue r (Value r) -> r (Type r)
forall (r :: * -> *). ValueSym r => r (Value r) -> r (Type r)
valueType SValue r
v)
(SValue r -> SValue r -> SValue r
forall (r :: * -> *). List r => SValue r -> SValue r -> SValue r
S.listAccess SValue r
sl ((SValue r
v_i SValue r -> SValue r -> SValue r
forall (r :: * -> *).
NumericExpression r =>
SValue r -> SValue r -> SValue r
#* SValue r
numLists) SValue r -> SValue r -> SValue r
forall (r :: * -> *).
NumericExpression r =>
SValue r -> SValue r -> SValue r
#+ Integer -> SValue r
forall (r :: * -> *). Literal r => Integer -> SValue r
S.litInt Integer
n))))
MSStatement r -> [MSStatement r] -> [MSStatement r]
forall a. a -> [a] -> [a]
: [SValue r] -> Integer -> [MSStatement r]
appendLists [SValue r]
vs (Integer
nInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
+1)
numLists :: SValue r
numLists = Integer -> SValue r
forall (r :: * -> *). Literal r => Integer -> SValue r
S.litInt (Int -> Integer
forall a. Integral a => a -> Integer
toInteger (Int -> Integer) -> Int -> Integer
forall a b. (a -> b) -> a -> b
$ [SVariable r] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [SVariable r]
lsts)
var_i :: SVariable r
var_i = Label -> VSType r -> SVariable r
forall (r :: * -> *).
VariableSym r =>
Label -> VSType r -> SVariable r
S.var "stringlist_i" VSType r
forall (r :: * -> *). TypeSym r => VSType r
S.int
v_i :: SValue r
v_i = SVariable r -> SValue r
forall (r :: * -> *). VariableValue r => SVariable r -> SValue r
S.valueOf SVariable r
var_i
forRange :: (RenderSym r) => SVariable r -> SValue r -> SValue r -> SValue r ->
MSBody r -> MSStatement r
forRange :: SVariable r
-> SValue r -> SValue r -> SValue r -> MSBody r -> MSStatement r
forRange i :: SVariable r
i initv :: SValue r
initv finalv :: SValue r
finalv stepv :: SValue r
stepv = MSStatement r
-> SValue r -> MSStatement r -> MSBody r -> MSStatement r
forall (r :: * -> *).
ControlStatement r =>
MSStatement r
-> SValue r -> MSStatement r -> MSBody r -> MSStatement r
S.for (SVariable r -> SValue r -> MSStatement r
forall (r :: * -> *).
DeclStatement r =>
SVariable r -> SValue r -> MSStatement r
S.varDecDef SVariable r
i SValue r
initv) (SVariable r -> SValue r
forall (r :: * -> *). VariableValue r => SVariable r -> SValue r
S.valueOf SVariable r
i SValue r -> SValue r -> SValue r
forall (r :: * -> *).
Comparison r =>
SValue r -> SValue r -> SValue r
?<
SValue r
finalv) (SVariable r
i SVariable r -> SValue r -> MSStatement r
forall (r :: * -> *).
AssignStatement r =>
SVariable r -> SValue r -> MSStatement r
&+= SValue r
stepv)
observerIndex :: (RenderSym r) => SVariable r
observerIndex :: SVariable r
observerIndex = Label -> VSType r -> SVariable r
forall (r :: * -> *).
VariableSym r =>
Label -> VSType r -> SVariable r
S.var "observerIndex" VSType r
forall (r :: * -> *). TypeSym r => VSType r
S.int
observerIdxVal :: (RenderSym r) => SValue r
observerIdxVal :: SValue r
observerIdxVal = SVariable r -> SValue r
forall (r :: * -> *). VariableValue r => SVariable r -> SValue r
S.valueOf SVariable r
forall (r :: * -> *). RenderSym r => SVariable r
observerIndex
obsList :: (RenderSym r) => VSType r -> SValue r
obsList :: VSType r -> SValue r
obsList t :: VSType r
t = SVariable r -> SValue r
forall (r :: * -> *). VariableValue r => SVariable r -> SValue r
S.valueOf (SVariable r -> SValue r) -> SVariable r -> SValue r
forall a b. (a -> b) -> a -> b
$ Label
observerListName Label -> VSType r -> SVariable r
forall (r :: * -> *).
VariableSym r =>
Label -> VSType r -> SVariable r
`listOf` VSType r
t
notify :: (RenderSym r) => VSType r -> VSFunction r -> MSBody r
notify :: VSType r -> VSFunction r -> MSBody r
notify t :: VSType r
t f :: VSFunction r
f = MSStatement r -> MSBody r
forall (r :: * -> *). BodySym r => MSStatement r -> MSBody r
oneLiner (MSStatement r -> MSBody r) -> MSStatement r -> MSBody r
forall a b. (a -> b) -> a -> b
$ SValue r -> MSStatement r
forall (r :: * -> *). StatementSym r => SValue r -> MSStatement r
S.valStmt (SValue r -> MSStatement r) -> SValue r -> MSStatement r
forall a b. (a -> b) -> a -> b
$ SValue r -> SValue r -> SValue r
forall (r :: * -> *). List r => SValue r -> SValue r -> SValue r
at (VSType r -> SValue r
forall (r :: * -> *). RenderSym r => VSType r -> SValue r
obsList VSType r
t) SValue r
forall (r :: * -> *). RenderSym r => SValue r
observerIdxVal SValue r -> VSFunction r -> SValue r
forall (r :: * -> *).
FunctionSym r =>
SValue r -> VSFunction r -> SValue r
$. VSFunction r
f
notifyObservers :: (RenderSym r) => VSFunction r -> VSType r -> MSStatement r
notifyObservers :: VSFunction r -> VSType r -> MSStatement r
notifyObservers f :: VSFunction r
f t :: VSType r
t = MSStatement r
-> SValue r -> MSStatement r -> MSBody r -> MSStatement r
forall (r :: * -> *).
ControlStatement r =>
MSStatement r
-> SValue r -> MSStatement r -> MSBody r -> MSStatement r
S.for MSStatement r
initv (SValue r
forall (r :: * -> *). RenderSym r => SValue r
observerIdxVal SValue r -> SValue r -> SValue r
forall (r :: * -> *).
Comparison r =>
SValue r -> SValue r -> SValue r
?< SValue r -> SValue r
forall (r :: * -> *). List r => SValue r -> SValue r
S.listSize (VSType r -> SValue r
forall (r :: * -> *). RenderSym r => VSType r -> SValue r
obsList VSType r
t))
(SVariable r
forall (r :: * -> *). RenderSym r => SVariable r
observerIndex SVariable r -> MSStatement r
forall (r :: * -> *).
AssignStatement r =>
SVariable r -> MSStatement r
&++) (VSType r -> VSFunction r -> MSBody r
forall (r :: * -> *).
RenderSym r =>
VSType r -> VSFunction r -> MSBody r
notify VSType r
t VSFunction r
f)
where initv :: MSStatement r
initv = SVariable r -> SValue r -> MSStatement r
forall (r :: * -> *).
DeclStatement r =>
SVariable r -> SValue r -> MSStatement r
S.varDecDef SVariable r
forall (r :: * -> *). RenderSym r => SVariable r
observerIndex (SValue r -> MSStatement r) -> SValue r -> MSStatement r
forall a b. (a -> b) -> a -> b
$ Integer -> SValue r
forall (r :: * -> *). Literal r => Integer -> SValue r
S.litInt 0
notifyObservers' :: (RenderSym r) => VSFunction r -> VSType r -> MSStatement r
notifyObservers' :: VSFunction r -> VSType r -> MSStatement r
notifyObservers' f :: VSFunction r
f t :: VSType r
t = SVariable r
-> SValue r -> SValue r -> SValue r -> MSBody r -> MSStatement r
forall (r :: * -> *).
ControlStatement r =>
SVariable r
-> SValue r -> SValue r -> SValue r -> MSBody r -> MSStatement r
S.forRange SVariable r
forall (r :: * -> *). RenderSym r => SVariable r
observerIndex SValue r
initv (SValue r -> SValue r
forall (r :: * -> *). List r => SValue r -> SValue r
S.listSize (SValue r -> SValue r) -> SValue r -> SValue r
forall a b. (a -> b) -> a -> b
$ VSType r -> SValue r
forall (r :: * -> *). RenderSym r => VSType r -> SValue r
obsList VSType r
t)
(Integer -> SValue r
forall (r :: * -> *). Literal r => Integer -> SValue r
S.litInt 1) (VSType r -> VSFunction r -> MSBody r
forall (r :: * -> *).
RenderSym r =>
VSType r -> VSFunction r -> MSBody r
notify VSType r
t VSFunction r
f)
where initv :: SValue r
initv = Integer -> SValue r
forall (r :: * -> *). Literal r => Integer -> SValue r
S.litInt 0
checkState :: (RenderSym r) => Label -> [(SValue r, MSBody r)] -> MSBody r ->
MSStatement r
checkState :: Label -> [(SValue r, MSBody r)] -> MSBody r -> MSStatement r
checkState l :: Label
l = SValue r -> [(SValue r, MSBody r)] -> MSBody r -> MSStatement r
forall (r :: * -> *).
ControlStatement r =>
SValue r -> [(SValue r, MSBody r)] -> MSBody r -> MSStatement r
S.switch (SVariable r -> SValue r
forall (r :: * -> *). VariableValue r => SVariable r -> SValue r
S.valueOf (SVariable r -> SValue r) -> SVariable r -> SValue r
forall a b. (a -> b) -> a -> b
$ Label -> VSType r -> SVariable r
forall (r :: * -> *).
VariableSym r =>
Label -> VSType r -> SVariable r
S.var Label
l VSType r
forall (r :: * -> *). TypeSym r => VSType r
S.string)