{-# LANGUAGE PostfixOperators, Rank2Types #-}
{-# OPTIONS_GHC -Wno-redundant-constraints #-}
module Language.Drasil.Code.Imperative.Import (codeType, spaceCodeType,
publicFunc, publicFuncProc, privateMethod, privateFuncProc, publicInOutFunc,
publicInOutFuncProc, privateInOutMethod, privateInOutFuncProc, genConstructor,
mkVar, mkVarProc, mkVal, mkValProc, convExpr, convExprProc, convStmt,
convStmtProc, genModDef, genModDefProc, genModFuncs, genModFuncsProc,
genModClasses, readData, readDataProc, renderC
) where
import Language.Drasil (HasSymbol, HasUID(..), HasSpace(..),
Space (Rational, Real), RealInterval(..), UID, Constraint(..), Inclusive (..))
import Database.Drasil (symbResolve)
import Language.Drasil.CodeExpr (sy, ($<), ($>), ($<=), ($>=), ($&&), in')
import qualified Language.Drasil.CodeExpr.Development as S (CodeExpr(..))
import Language.Drasil.CodeExpr.Development (CodeExpr(..), ArithBinOp(..),
AssocArithOper(..), AssocBoolOper(..), AssocConcatOper(..), BoolBinOp(..), EqBinOp(..),
LABinOp(..), OrdBinOp(..), UFunc(..), UFuncB(..), UFuncVV(..), UFuncVN(..),
VVNBinOp(..), VVVBinOp(..), NVVBinOp(..), ESSBinOp(..), ESBBinOp(..))
import Language.Drasil.Code.Imperative.Comments (getComment)
import Language.Drasil.Code.Imperative.ConceptMatch (conceptToGOOL)
import Language.Drasil.Code.Imperative.GenerateGOOL (auxClass, fApp, fAppProc,
ctorCall, genModuleWithImports, genModuleWithImportsProc, primaryClass)
import Language.Drasil.Code.Imperative.Helpers (lookupC, convScope)
import Language.Drasil.Code.Imperative.Logging (maybeLog, logBody)
import Language.Drasil.Code.Imperative.DrasilState (GenState, DrasilState(..),
ScopeType(..), genICName)
import Language.Drasil.Chunk.Code (CodeIdea(codeName), CodeVarChunk, obv,
quantvar, quantfunc, ccObjVar, DefiningCodeExpr(..))
import Language.Drasil.Chunk.Parameter (ParameterChunk(..), PassBy(..), pcAuto)
import Language.Drasil.Code.CodeQuantityDicts (inFileName, inParams, consts)
import Language.Drasil.Choices (Comments(..), ConstantRepr(..),
ConstantStructure(..), Structure(..), InternalConcept(..))
import Language.Drasil.CodeSpec (HasOldCodeSpec(..))
import Language.Drasil.Code.DataDesc (DataItem, LinePattern(Repeat, Straight),
Data(Line, Lines, JunkData, Singleton), DataDesc, isLine, isLines, getInputs,
getPatternInputs)
import Language.Drasil.Literal.Development
import Language.Drasil.Mod (Func(..), FuncData(..), FuncDef(..), FuncStmt(..),
Mod(..), Name, Description, StateVariable(..), fstdecl)
import qualified Language.Drasil.Mod as M (Class(..))
import Language.Drasil.Printers (showHasSymbImpl)
import Drasil.GOOL (Label, MSBody, MSBlock, VSType, SVariable, SValue,
MSStatement, MSParameter, SMethod, CSStateVar, SClass, NamedArgs,
Initializers, SharedProg, OOProg, PermanenceSym(..), bodyStatements,
BlockSym(..), TypeSym(..), VariableSym(..), ScopeSym(..), OOVariableSym(..),
staticConst, VariableElim(..), ($->), ValueSym(..), Literal(..),
VariableValue(..), NumericExpression(..), BooleanExpression(..),
Comparison(..), ValueExpression(..), OOValueExpression(..),
objMethodCallMixedArgs, List(..), StatementSym(..), AssignStatement(..),
DeclStatement(..), IOStatement(..), StringStatement(..), ControlStatement(..),
ifNoElse, VisibilitySym(..), ParameterSym(..), MethodSym(..), OOMethodSym(..),
pubDVar, privDVar, nonInitConstructor, convType, convTypeOO,
VisibilityTag(..), CodeType(..), onStateValue)
import qualified Drasil.GOOL as S (Set(..))
import qualified Drasil.GOOL as OO (SFile)
import qualified Drasil.GOOL as C (CodeType(List, Array))
import Drasil.GProc (ProcProg)
import qualified Drasil.GProc as Proc (SFile)
import Prelude hiding (sin, cos, tan, log, exp)
import Data.List ((\\), intersect)
import qualified Data.Map as Map (lookup)
import Control.Monad (liftM2,liftM3)
import Control.Monad.State (get, modify)
import Control.Lens ((^.))
codeType :: (HasSpace c) => c -> GenState CodeType
codeType :: forall c. HasSpace c => c -> GenState CodeType
codeType c
c = Space -> GenState CodeType
spaceCodeType (c
c c -> Getting Space c Space -> Space
forall s a. s -> Getting a s a -> a
^. Getting Space c Space
forall c. HasSpace c => Getter c Space
Getter c Space
typ)
spaceCodeType :: Space -> GenState CodeType
spaceCodeType :: Space -> GenState CodeType
spaceCodeType Space
s = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
DrasilState -> Space -> GenState CodeType
spaceMatches DrasilState
g Space
s
value :: (OOProg r) => UID -> Name -> VSType r -> GenState (SValue r)
value :: forall (r :: * -> *).
OOProg r =>
UID -> Name -> VSType r -> GenState (SValue r)
value UID
u Name
s VSType r
t = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
let cs :: CodeSpec
cs = DrasilState -> CodeSpec
codeSpec DrasilState
g
mm :: ConstantMap
mm = CodeSpec
cs CodeSpec -> Getting ConstantMap CodeSpec ConstantMap -> ConstantMap
forall s a. s -> Getting a s a -> a
^. Getting ConstantMap CodeSpec ConstantMap
forall c. HasOldCodeSpec c => Lens' c ConstantMap
Lens' CodeSpec ConstantMap
constMapO
constDef :: Maybe CodeDefinition
constDef = do
CodeDefinition
cd <- UID -> ConstantMap -> Maybe CodeDefinition
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup UID
u ConstantMap
mm
ConstantStructure -> CodeDefinition -> Maybe CodeDefinition
forall {a}. ConstantStructure -> a -> Maybe a
maybeInline (DrasilState -> ConstantStructure
conStruct DrasilState
g) CodeDefinition
cd
maybeInline :: ConstantStructure -> a -> Maybe a
maybeInline ConstantStructure
Inline a
m = a -> Maybe a
forall a. a -> Maybe a
Just a
m
maybeInline ConstantStructure
_ a
_ = Maybe a
forall a. Maybe a
Nothing
cm :: MatchedConceptMap
cm = DrasilState -> MatchedConceptMap
concMatches DrasilState
g
cdCncpt :: Maybe CodeConcept
cdCncpt = UID -> MatchedConceptMap -> Maybe CodeConcept
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup UID
u MatchedConceptMap
cm
SValue r
val <- GenState (SValue r)
-> (CodeDefinition -> GenState (SValue r))
-> Maybe CodeDefinition
-> GenState (SValue r)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (SVariable r -> SValue r
forall (r :: * -> *). VariableValue r => SVariable r -> SValue r
valueOf (SVariable r -> SValue r)
-> StateT DrasilState Identity (SVariable r) -> GenState (SValue r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name -> VSType r -> StateT DrasilState Identity (SVariable r)
forall (r :: * -> *).
OOProg r =>
Name -> VSType r -> GenState (SVariable r)
variable Name
s VSType r
t) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr (CodeExpr -> GenState (SValue r))
-> (CodeDefinition -> CodeExpr)
-> CodeDefinition
-> GenState (SValue r)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CodeDefinition
-> Getting CodeExpr CodeDefinition CodeExpr -> CodeExpr
forall s a. s -> Getting a s a -> a
^. Getting CodeExpr CodeDefinition CodeExpr
forall c. DefiningCodeExpr c => Lens' c CodeExpr
Lens' CodeDefinition CodeExpr
codeExpr)) Maybe CodeDefinition
constDef
SValue r -> GenState (SValue r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (SValue r -> GenState (SValue r))
-> SValue r -> GenState (SValue r)
forall a b. (a -> b) -> a -> b
$ SValue r
-> (CodeConcept -> SValue r) -> Maybe CodeConcept -> SValue r
forall b a. b -> (a -> b) -> Maybe a -> b
maybe SValue r
val CodeConcept -> SValue r
forall (r :: * -> *). SharedProg r => CodeConcept -> SValue r
conceptToGOOL Maybe CodeConcept
cdCncpt
variable :: (OOProg r) => Name -> VSType r -> GenState (SVariable r)
variable :: forall (r :: * -> *).
OOProg r =>
Name -> VSType r -> GenState (SVariable r)
variable Name
s VSType r
t = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
let cs :: CodeSpec
cs = DrasilState -> CodeSpec
codeSpec DrasilState
g
defFunc :: ConstantRepr -> Name -> VSType r -> SVariable r
defFunc ConstantRepr
Var = Name -> VSType r -> SVariable r
forall (r :: * -> *).
VariableSym r =>
Name -> VSType r -> SVariable r
var
defFunc ConstantRepr
Const = Name -> VSType r -> SVariable r
forall (r :: * -> *).
OOVariableSym r =>
Name -> VSType r -> SVariable r
staticConst
if Name
s Name -> [Name] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (Input -> Name) -> [Input] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map Input -> Name
forall c. CodeIdea c => c -> Name
codeName (CodeSpec
cs CodeSpec -> Getting [Input] CodeSpec [Input] -> [Input]
forall s a. s -> Getting a s a -> a
^. Getting [Input] CodeSpec [Input]
forall c. HasOldCodeSpec c => Lens' c [Input]
Lens' CodeSpec [Input]
inputsO)
then Structure -> ConstantRepr -> SVariable r -> GenState (SVariable r)
forall (r :: * -> *).
OOProg r =>
Structure -> ConstantRepr -> SVariable r -> GenState (SVariable r)
inputVariable (DrasilState -> Structure
inStruct DrasilState
g) ConstantRepr
Var (Name -> VSType r -> SVariable r
forall (r :: * -> *).
VariableSym r =>
Name -> VSType r -> SVariable r
var Name
s VSType r
t)
else if Name
s Name -> [Name] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (CodeDefinition -> Name) -> [CodeDefinition] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map CodeDefinition -> Name
forall c. CodeIdea c => c -> Name
codeName (CodeSpec
cs CodeSpec
-> Getting [CodeDefinition] CodeSpec [CodeDefinition]
-> [CodeDefinition]
forall s a. s -> Getting a s a -> a
^. Getting [CodeDefinition] CodeSpec [CodeDefinition]
forall c. HasOldCodeSpec c => Lens' c [CodeDefinition]
Lens' CodeSpec [CodeDefinition]
constantsO)
then ConstantStructure
-> ConstantRepr -> SVariable r -> GenState (SVariable r)
forall (r :: * -> *).
OOProg r =>
ConstantStructure
-> ConstantRepr -> SVariable r -> GenState (SVariable r)
constVariable (DrasilState -> ConstantStructure
conStruct DrasilState
g) (DrasilState -> ConstantRepr
conRepr DrasilState
g)
((ConstantRepr -> Name -> VSType r -> SVariable r
forall {r :: * -> *}.
OOVariableSym r =>
ConstantRepr -> Name -> VSType r -> SVariable r
defFunc (ConstantRepr -> Name -> VSType r -> SVariable r)
-> ConstantRepr -> Name -> VSType r -> SVariable r
forall a b. (a -> b) -> a -> b
$ DrasilState -> ConstantRepr
conRepr DrasilState
g) Name
s VSType r
t)
else SVariable r -> GenState (SVariable r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVariable r -> GenState (SVariable r))
-> SVariable r -> GenState (SVariable r)
forall a b. (a -> b) -> a -> b
$ Name -> VSType r -> SVariable r
forall (r :: * -> *).
VariableSym r =>
Name -> VSType r -> SVariable r
var Name
s VSType r
t
inputVariable :: (OOProg r) => Structure -> ConstantRepr -> SVariable r ->
GenState (SVariable r)
inputVariable :: forall (r :: * -> *).
OOProg r =>
Structure -> ConstantRepr -> SVariable r -> GenState (SVariable r)
inputVariable Structure
Unbundled ConstantRepr
_ SVariable r
v = SVariable r -> StateT DrasilState Identity (SVariable r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return SVariable r
v
inputVariable Structure
Bundled ConstantRepr
Var SVariable r
v = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
Name
inClsName <- InternalConcept -> GenState Name
genICName InternalConcept
InputParameters
SVariable r
ip <- Input -> StateT DrasilState Identity (SVariable r)
forall (r :: * -> *). OOProg r => Input -> GenState (SVariable r)
mkVar (QuantityDict -> Input
forall c. (Quantity c, MayHaveUnit c) => c -> Input
quantvar QuantityDict
inParams)
SVariable r -> StateT DrasilState Identity (SVariable r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVariable r -> StateT DrasilState Identity (SVariable r))
-> SVariable r -> StateT DrasilState Identity (SVariable r)
forall a b. (a -> b) -> a -> b
$ if DrasilState -> Name
currentClass DrasilState
g Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
== Name
inClsName then SVariable r -> SVariable r
forall (r :: * -> *). OOVariableSym r => SVariable r -> SVariable r
objVarSelf SVariable r
v else SVariable r
ip SVariable r -> SVariable r -> SVariable r
forall (r :: * -> *).
OOVariableSym r =>
SVariable r -> SVariable r -> SVariable r
$-> SVariable r
v
inputVariable Structure
Bundled ConstantRepr
Const SVariable r
v = do
SVariable r
ip <- Input -> StateT DrasilState Identity (SVariable r)
forall (r :: * -> *). OOProg r => Input -> GenState (SVariable r)
mkVar (QuantityDict -> Input
forall c. (Quantity c, MayHaveUnit c) => c -> Input
quantvar QuantityDict
inParams)
SVariable r
-> SVariable r -> StateT DrasilState Identity (SVariable r)
forall (r :: * -> *).
OOProg r =>
SVariable r -> SVariable r -> GenState (SVariable r)
classVariable SVariable r
ip SVariable r
v
constVariable :: (OOProg r) => ConstantStructure -> ConstantRepr ->
SVariable r -> GenState (SVariable r)
constVariable :: forall (r :: * -> *).
OOProg r =>
ConstantStructure
-> ConstantRepr -> SVariable r -> GenState (SVariable r)
constVariable (Store Structure
Unbundled) ConstantRepr
_ SVariable r
v = SVariable r -> StateT DrasilState Identity (SVariable r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return SVariable r
v
constVariable (Store Structure
Bundled) ConstantRepr
Var SVariable r
v = do
SVariable r
cs <- Input -> StateT DrasilState Identity (SVariable r)
forall (r :: * -> *). OOProg r => Input -> GenState (SVariable r)
mkVar (QuantityDict -> Input
forall c. (Quantity c, MayHaveUnit c) => c -> Input
quantvar QuantityDict
consts)
SVariable r -> StateT DrasilState Identity (SVariable r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVariable r -> StateT DrasilState Identity (SVariable r))
-> SVariable r -> StateT DrasilState Identity (SVariable r)
forall a b. (a -> b) -> a -> b
$ SVariable r
cs SVariable r -> SVariable r -> SVariable r
forall (r :: * -> *).
OOVariableSym r =>
SVariable r -> SVariable r -> SVariable r
$-> SVariable r
v
constVariable (Store Structure
Bundled) ConstantRepr
Const SVariable r
v = do
SVariable r
cs <- Input -> StateT DrasilState Identity (SVariable r)
forall (r :: * -> *). OOProg r => Input -> GenState (SVariable r)
mkVar (QuantityDict -> Input
forall c. (Quantity c, MayHaveUnit c) => c -> Input
quantvar QuantityDict
consts)
SVariable r
-> SVariable r -> StateT DrasilState Identity (SVariable r)
forall (r :: * -> *).
OOProg r =>
SVariable r -> SVariable r -> GenState (SVariable r)
classVariable SVariable r
cs SVariable r
v
constVariable ConstantStructure
WithInputs ConstantRepr
cr SVariable r
v = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
Structure
-> ConstantRepr
-> SVariable r
-> StateT DrasilState Identity (SVariable r)
forall (r :: * -> *).
OOProg r =>
Structure -> ConstantRepr -> SVariable r -> GenState (SVariable r)
inputVariable (DrasilState -> Structure
inStruct DrasilState
g) ConstantRepr
cr SVariable r
v
constVariable ConstantStructure
Inline ConstantRepr
_ SVariable r
_ = Name -> StateT DrasilState Identity (SVariable r)
forall a. HasCallStack => Name -> a
error (Name -> StateT DrasilState Identity (SVariable r))
-> Name -> StateT DrasilState Identity (SVariable r)
forall a b. (a -> b) -> a -> b
$ Name
"mkVar called on a constant, but user " Name -> Name -> Name
forall a. [a] -> [a] -> [a]
++
Name
"chose to Inline constants. Generator has a bug."
classVariable :: (OOProg r) => SVariable r -> SVariable r ->
GenState (SVariable r)
classVariable :: forall (r :: * -> *).
OOProg r =>
SVariable r -> SVariable r -> GenState (SVariable r)
classVariable SVariable r
c SVariable r
v = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
let checkCurrent :: Name -> VSType r -> SVariable r -> SVariable r
checkCurrent Name
m = if DrasilState -> Name
currentModule DrasilState
g Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
== Name
m then VSType r -> SVariable r -> SVariable r
forall (r :: * -> *).
OOVariableSym r =>
VSType r -> SVariable r -> SVariable r
classVar else VSType r -> SVariable r -> SVariable r
forall (r :: * -> *).
OOVariableSym r =>
VSType r -> SVariable r -> SVariable r
extClassVar
SVariable r -> GenState (SVariable r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVariable r -> GenState (SVariable r))
-> SVariable r -> GenState (SVariable r)
forall a b. (a -> b) -> a -> b
$ do
r (Variable r)
v' <- SVariable r
v
let nm :: Name
nm = r (Variable r) -> Name
forall (r :: * -> *). VariableElim r => r (Variable r) -> Name
variableName r (Variable r)
v'
(State ValueState (r (Type r)) -> SVariable r -> SVariable r)
-> (Name
-> State ValueState (r (Type r)) -> SVariable r -> SVariable r)
-> Maybe Name
-> State ValueState (r (Type r))
-> SVariable r
-> SVariable r
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Name -> State ValueState (r (Type r)) -> SVariable r -> SVariable r
forall a. HasCallStack => Name -> a
error (Name
-> State ValueState (r (Type r)) -> SVariable r -> SVariable r)
-> Name
-> State ValueState (r (Type r))
-> SVariable r
-> SVariable r
forall a b. (a -> b) -> a -> b
$ Name
"Variable " Name -> Name -> Name
forall a. [a] -> [a] -> [a]
++ Name
nm Name -> Name -> Name
forall a. [a] -> [a] -> [a]
++ Name
" missing from export map")
Name -> State ValueState (r (Type r)) -> SVariable r -> SVariable r
forall {r :: * -> *}.
OOVariableSym r =>
Name -> VSType r -> SVariable r -> SVariable r
checkCurrent (Name -> Map Name Name -> Maybe Name
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Name
nm (DrasilState -> Map Name Name
eMap DrasilState
g)) ((r (Variable r) -> r (Type r))
-> SVariable r -> State ValueState (r (Type 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
c) SVariable r
v
mkVal :: (OOProg r) => CodeVarChunk -> GenState (SValue r)
mkVal :: forall (r :: * -> *). OOProg r => Input -> GenState (SValue r)
mkVal Input
v = do
CodeType
t <- Input -> GenState CodeType
forall c. HasSpace c => c -> GenState CodeType
codeType Input
v
let toGOOLVal :: Maybe c -> GenState (SValue r)
toGOOLVal Maybe c
Nothing = UID -> Name -> VSType r -> GenState (SValue r)
forall (r :: * -> *).
OOProg r =>
UID -> Name -> VSType r -> GenState (SValue r)
value (Input
v Input -> Getting UID Input UID -> UID
forall s a. s -> Getting a s a -> a
^. Getting UID Input UID
forall c. HasUID c => Getter c UID
Getter Input UID
uid) (Input -> Name
forall c. CodeIdea c => c -> Name
codeName Input
v) (CodeType -> VSType r
forall (r :: * -> *). OOTypeSym r => CodeType -> VSType r
convTypeOO CodeType
t)
toGOOLVal (Just c
o) = do
CodeType
ot <- c -> GenState CodeType
forall c. HasSpace c => c -> GenState CodeType
codeType c
o
SValue r -> GenState (SValue r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (SValue r -> GenState (SValue r))
-> SValue r -> GenState (SValue r)
forall a b. (a -> b) -> a -> b
$ SVariable r -> SValue r
forall (r :: * -> *). VariableValue r => SVariable r -> SValue r
valueOf (SVariable r -> SValue r) -> SVariable r -> SValue r
forall a b. (a -> b) -> a -> b
$ SVariable r -> SVariable r -> SVariable r
forall (r :: * -> *).
OOVariableSym r =>
SVariable r -> SVariable r -> SVariable r
objVar (Name -> VSType r -> SVariable r
forall (r :: * -> *).
VariableSym r =>
Name -> VSType r -> SVariable r
var (c -> Name
forall c. CodeIdea c => c -> Name
codeName c
o) (CodeType -> VSType r
forall (r :: * -> *). OOTypeSym r => CodeType -> VSType r
convTypeOO CodeType
ot))
(Name -> VSType r -> SVariable r
forall (r :: * -> *).
VariableSym r =>
Name -> VSType r -> SVariable r
var (Input -> Name
forall c. CodeIdea c => c -> Name
codeName Input
v) (CodeType -> VSType r
forall (r :: * -> *). OOTypeSym r => CodeType -> VSType r
convTypeOO CodeType
t))
Maybe CodeChunk -> GenState (SValue r)
forall {r :: * -> *} {c}.
(OOProg r, HasSpace c, CodeIdea c) =>
Maybe c -> GenState (SValue r)
toGOOLVal (Input
v Input
-> Getting (Maybe CodeChunk) Input (Maybe CodeChunk)
-> Maybe CodeChunk
forall s a. s -> Getting a s a -> a
^. Getting (Maybe CodeChunk) Input (Maybe CodeChunk)
Lens' Input (Maybe CodeChunk)
obv)
mkVar :: (OOProg r) => CodeVarChunk -> GenState (SVariable r)
mkVar :: forall (r :: * -> *). OOProg r => Input -> GenState (SVariable r)
mkVar Input
v = do
CodeType
t <- Input -> GenState CodeType
forall c. HasSpace c => c -> GenState CodeType
codeType Input
v
let toGOOLVar :: Maybe c -> GenState (SVariable r)
toGOOLVar Maybe c
Nothing = Name -> VSType r -> GenState (SVariable r)
forall (r :: * -> *).
OOProg r =>
Name -> VSType r -> GenState (SVariable r)
variable (Input -> Name
forall c. CodeIdea c => c -> Name
codeName Input
v) (CodeType -> VSType r
forall (r :: * -> *). OOTypeSym r => CodeType -> VSType r
convTypeOO CodeType
t)
toGOOLVar (Just c
o) = do
CodeType
ot <- c -> GenState CodeType
forall c. HasSpace c => c -> GenState CodeType
codeType c
o
SVariable r -> GenState (SVariable r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVariable r -> GenState (SVariable r))
-> SVariable r -> GenState (SVariable r)
forall a b. (a -> b) -> a -> b
$ SVariable r -> SVariable r -> SVariable r
forall (r :: * -> *).
OOVariableSym r =>
SVariable r -> SVariable r -> SVariable r
objVar (Name -> VSType r -> SVariable r
forall (r :: * -> *).
VariableSym r =>
Name -> VSType r -> SVariable r
var (c -> Name
forall c. CodeIdea c => c -> Name
codeName c
o) (CodeType -> VSType r
forall (r :: * -> *). OOTypeSym r => CodeType -> VSType r
convTypeOO CodeType
ot))
(Name -> VSType r -> SVariable r
forall (r :: * -> *).
VariableSym r =>
Name -> VSType r -> SVariable r
var (Input -> Name
forall c. CodeIdea c => c -> Name
codeName Input
v) (CodeType -> VSType r
forall (r :: * -> *). OOTypeSym r => CodeType -> VSType r
convTypeOO CodeType
t))
Maybe CodeChunk -> GenState (SVariable r)
forall {r :: * -> *} {c}.
(OOProg r, HasSpace c, CodeIdea c) =>
Maybe c -> GenState (SVariable r)
toGOOLVar (Input
v Input
-> Getting (Maybe CodeChunk) Input (Maybe CodeChunk)
-> Maybe CodeChunk
forall s a. s -> Getting a s a -> a
^. Getting (Maybe CodeChunk) Input (Maybe CodeChunk)
Lens' Input (Maybe CodeChunk)
obv)
mkParam :: (OOProg r) => ParameterChunk -> GenState (MSParameter r)
mkParam :: forall (r :: * -> *).
OOProg r =>
ParameterChunk -> GenState (MSParameter r)
mkParam ParameterChunk
p = do
VS (r (Variable r))
v <- Input -> StateT DrasilState Identity (VS (r (Variable r)))
forall (r :: * -> *). OOProg r => Input -> GenState (SVariable r)
mkVar (ParameterChunk -> Input
forall c. (Quantity c, MayHaveUnit c) => c -> Input
quantvar ParameterChunk
p)
MSParameter r -> GenState (MSParameter r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (MSParameter r -> GenState (MSParameter r))
-> MSParameter r -> GenState (MSParameter r)
forall a b. (a -> b) -> a -> b
$ PassBy -> VS (r (Variable r)) -> MSParameter r
forall {r :: * -> *}.
ParameterSym r =>
PassBy -> VS (r (Variable r)) -> MS (r (Parameter r))
paramFunc (ParameterChunk -> PassBy
passBy ParameterChunk
p) VS (r (Variable r))
v
where paramFunc :: PassBy -> VS (r (Variable r)) -> MS (r (Parameter r))
paramFunc PassBy
Ref = VS (r (Variable r)) -> MS (r (Parameter r))
forall (r :: * -> *).
ParameterSym r =>
SVariable r -> MSParameter r
pointerParam
paramFunc PassBy
Val = VS (r (Variable r)) -> MS (r (Parameter r))
forall (r :: * -> *).
ParameterSym r =>
SVariable r -> MSParameter r
param
publicFunc :: (OOProg r) => Label -> VSType r -> Description ->
[ParameterChunk] -> Maybe Description -> [MSBlock r] ->
GenState (SMethod r)
publicFunc :: forall (r :: * -> *).
OOProg r =>
Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
publicFunc Name
n VSType r
t Name
desc [ParameterChunk]
ps Maybe Name
r [MSBlock r]
b = do
(DrasilState -> DrasilState) -> StateT DrasilState Identity ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\DrasilState
st -> DrasilState
st {currentScope = Local})
([MSParameter r] -> MSBody r -> SMethod r)
-> Name
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
forall (r :: * -> *).
OOProg r =>
([MSParameter r] -> MSBody r -> SMethod r)
-> Name
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
genMethod (Name
-> r (Visibility r)
-> VSType r
-> [MSParameter r]
-> MSBody r
-> SMethod r
forall (r :: * -> *).
MethodSym r =>
Name
-> r (Visibility r)
-> VSType r
-> [MSParameter r]
-> MSBody r
-> SMethod r
function Name
n r (Visibility r)
forall (r :: * -> *). VisibilitySym r => r (Visibility r)
public VSType r
t) Name
n Name
desc [ParameterChunk]
ps Maybe Name
r [MSBlock r]
b
publicMethod :: (OOProg r) => Label -> VSType r -> Description ->
[ParameterChunk] -> Maybe Description -> [MSBlock r] ->
GenState (SMethod r)
publicMethod :: forall (r :: * -> *).
OOProg r =>
Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
publicMethod Name
n VSType r
t = do
([MSParameter r] -> MSBody r -> SMethod r)
-> Name
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
forall (r :: * -> *).
OOProg r =>
([MSParameter r] -> MSBody r -> SMethod r)
-> Name
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
genMethod (Name
-> r (Visibility r)
-> r (Permanence r)
-> VSType r
-> [MSParameter r]
-> MSBody r
-> SMethod r
forall (r :: * -> *).
OOMethodSym r =>
Name
-> r (Visibility r)
-> r (Permanence r)
-> VSType r
-> [MSParameter r]
-> MSBody r
-> SMethod r
method Name
n r (Visibility r)
forall (r :: * -> *). VisibilitySym r => r (Visibility r)
public r (Permanence r)
forall (r :: * -> *). PermanenceSym r => r (Permanence r)
dynamic VSType r
t) Name
n
privateMethod :: (OOProg r) => Label -> VSType r -> Description ->
[ParameterChunk] -> Maybe Description -> [MSBlock r] ->
GenState (SMethod r)
privateMethod :: forall (r :: * -> *).
OOProg r =>
Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
privateMethod Name
n VSType r
t = do
([MSParameter r] -> MSBody r -> SMethod r)
-> Name
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
forall (r :: * -> *).
OOProg r =>
([MSParameter r] -> MSBody r -> SMethod r)
-> Name
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
genMethod (Name
-> r (Visibility r)
-> r (Permanence r)
-> VSType r
-> [MSParameter r]
-> MSBody r
-> SMethod r
forall (r :: * -> *).
OOMethodSym r =>
Name
-> r (Visibility r)
-> r (Permanence r)
-> VSType r
-> [MSParameter r]
-> MSBody r
-> SMethod r
method Name
n r (Visibility r)
forall (r :: * -> *). VisibilitySym r => r (Visibility r)
private r (Permanence r)
forall (r :: * -> *). PermanenceSym r => r (Permanence r)
dynamic VSType r
t) Name
n
publicInOutFunc :: (OOProg r) => Label -> Description -> [CodeVarChunk] ->
[CodeVarChunk] -> [MSBlock r] -> GenState (SMethod r)
publicInOutFunc :: forall (r :: * -> *).
OOProg r =>
Name
-> Name
-> [Input]
-> [Input]
-> [MSBlock r]
-> GenState (SMethod r)
publicInOutFunc Name
n = ([SVariable r]
-> [SVariable r]
-> [SVariable r]
-> MSBody r
-> StateT MethodState Identity (r (Method r)))
-> (Name
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> MSBody r
-> StateT MethodState Identity (r (Method r)))
-> Name
-> Name
-> [Input]
-> [Input]
-> [StateT MethodState Identity (r (Block r))]
-> StateT
DrasilState Identity (StateT MethodState Identity (r (Method r)))
forall (r :: * -> *).
OOProg r =>
([SVariable r]
-> [SVariable r] -> [SVariable r] -> MSBody r -> SMethod r)
-> (Name
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> MSBody r
-> SMethod r)
-> Name
-> Name
-> [Input]
-> [Input]
-> [MSBlock r]
-> GenState (SMethod r)
genInOutFunc (Name
-> r (Visibility r)
-> [SVariable r]
-> [SVariable r]
-> [SVariable r]
-> MSBody r
-> StateT MethodState Identity (r (Method r))
forall (r :: * -> *).
MethodSym r =>
Name -> r (Visibility r) -> InOutFunc r
inOutFunc Name
n r (Visibility r)
forall (r :: * -> *). VisibilitySym r => r (Visibility r)
public) (Name
-> r (Visibility r)
-> Name
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> MSBody r
-> StateT MethodState Identity (r (Method r))
forall (r :: * -> *).
MethodSym r =>
Name -> r (Visibility r) -> DocInOutFunc r
docInOutFunc Name
n r (Visibility r)
forall (r :: * -> *). VisibilitySym r => r (Visibility r)
public) Name
n
privateInOutMethod :: (OOProg r) => Label -> Description -> [CodeVarChunk] ->
[CodeVarChunk] -> [MSBlock r] -> GenState (SMethod r)
privateInOutMethod :: forall (r :: * -> *).
OOProg r =>
Name
-> Name
-> [Input]
-> [Input]
-> [MSBlock r]
-> GenState (SMethod r)
privateInOutMethod Name
n = ([SVariable r]
-> [SVariable r]
-> [SVariable r]
-> MSBody r
-> StateT MethodState Identity (r (Method r)))
-> (Name
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> MSBody r
-> StateT MethodState Identity (r (Method r)))
-> Name
-> Name
-> [Input]
-> [Input]
-> [StateT MethodState Identity (r (Block r))]
-> StateT
DrasilState Identity (StateT MethodState Identity (r (Method r)))
forall (r :: * -> *).
OOProg r =>
([SVariable r]
-> [SVariable r] -> [SVariable r] -> MSBody r -> SMethod r)
-> (Name
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> MSBody r
-> SMethod r)
-> Name
-> Name
-> [Input]
-> [Input]
-> [MSBlock r]
-> GenState (SMethod r)
genInOutFunc (Name
-> r (Visibility r)
-> r (Permanence r)
-> [SVariable r]
-> [SVariable r]
-> [SVariable r]
-> MSBody r
-> StateT MethodState Identity (r (Method r))
forall (r :: * -> *).
OOMethodSym r =>
Name -> r (Visibility r) -> r (Permanence r) -> InOutFunc r
inOutMethod Name
n r (Visibility r)
forall (r :: * -> *). VisibilitySym r => r (Visibility r)
private r (Permanence r)
forall (r :: * -> *). PermanenceSym r => r (Permanence r)
dynamic) (Name
-> r (Visibility r)
-> r (Permanence r)
-> Name
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> MSBody r
-> StateT MethodState Identity (r (Method r))
forall (r :: * -> *).
OOMethodSym r =>
Name -> r (Visibility r) -> r (Permanence r) -> DocInOutFunc r
docInOutMethod Name
n r (Visibility r)
forall (r :: * -> *). VisibilitySym r => r (Visibility r)
private r (Permanence r)
forall (r :: * -> *). PermanenceSym r => r (Permanence r)
dynamic) Name
n
genConstructor :: (OOProg r) => Label -> Description -> [ParameterChunk] ->
[MSBlock r] -> GenState (SMethod r)
genConstructor :: forall (r :: * -> *).
OOProg r =>
Name
-> Name -> [ParameterChunk] -> [MSBlock r] -> GenState (SMethod r)
genConstructor Name
n Name
desc [ParameterChunk]
p = do
([MSParameter r] -> MSBody r -> SMethod r)
-> Name
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
forall (r :: * -> *).
OOProg r =>
([MSParameter r] -> MSBody r -> SMethod r)
-> Name
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
genMethod [MSParameter r] -> MSBody r -> SMethod r
forall (r :: * -> *).
OOMethodSym r =>
[MSParameter r] -> MSBody r -> SMethod r
nonInitConstructor Name
n Name
desc [ParameterChunk]
p Maybe Name
forall a. Maybe a
Nothing
genInitConstructor :: (OOProg r) => Label -> Description -> [ParameterChunk]
-> Initializers r -> [MSBlock r] -> GenState (SMethod r)
genInitConstructor :: forall (r :: * -> *).
OOProg r =>
Name
-> Name
-> [ParameterChunk]
-> Initializers r
-> [MSBlock r]
-> GenState (SMethod r)
genInitConstructor Name
n Name
desc [ParameterChunk]
p Initializers r
is = ([MSParameter r]
-> MSBody r -> StateT MethodState Identity (r (Method r)))
-> Name
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [StateT MethodState Identity (r (Block r))]
-> StateT
DrasilState Identity (StateT MethodState Identity (r (Method r)))
forall (r :: * -> *).
OOProg r =>
([MSParameter r] -> MSBody r -> SMethod r)
-> Name
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
genMethod ([MSParameter r]
-> Initializers r
-> MSBody r
-> StateT MethodState Identity (r (Method r))
forall (r :: * -> *).
OOMethodSym r =>
[MSParameter r] -> Initializers r -> MSBody r -> SMethod r
`constructor` Initializers r
is) Name
n Name
desc [ParameterChunk]
p
Maybe Name
forall a. Maybe a
Nothing
genMethod :: (OOProg r) => ([MSParameter r] -> MSBody r -> SMethod r) ->
Label -> Description -> [ParameterChunk] -> Maybe Description -> [MSBlock r]
-> GenState (SMethod r)
genMethod :: forall (r :: * -> *).
OOProg r =>
([MSParameter r] -> MSBody r -> SMethod r)
-> Name
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
genMethod [MSParameter r] -> MSBody r -> SMethod r
f Name
n Name
desc [ParameterChunk]
p Maybe Name
r [MSBlock r]
b = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
[VS (r (Variable r))]
vars <- (ParameterChunk
-> StateT DrasilState Identity (VS (r (Variable r))))
-> [ParameterChunk]
-> StateT DrasilState Identity [VS (r (Variable r))]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (Input -> StateT DrasilState Identity (VS (r (Variable r)))
forall (r :: * -> *). OOProg r => Input -> GenState (SVariable r)
mkVar (Input -> StateT DrasilState Identity (VS (r (Variable r))))
-> (ParameterChunk -> Input)
-> ParameterChunk
-> StateT DrasilState Identity (VS (r (Variable r)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParameterChunk -> Input
forall c. (Quantity c, MayHaveUnit c) => c -> Input
quantvar) [ParameterChunk]
p
[MSParameter r]
ps <- (ParameterChunk -> StateT DrasilState Identity (MSParameter r))
-> [ParameterChunk] -> StateT DrasilState Identity [MSParameter r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ParameterChunk -> StateT DrasilState Identity (MSParameter r)
forall (r :: * -> *).
OOProg r =>
ParameterChunk -> GenState (MSParameter r)
mkParam [ParameterChunk]
p
MSBody r
bod <- Name
-> [VS (r (Variable r))]
-> [MSBlock r]
-> StateT DrasilState Identity (MSBody r)
forall (r :: * -> *).
SharedProg r =>
Name -> [SVariable r] -> [MSBlock r] -> GenState (MSBody r)
logBody Name
n [VS (r (Variable r))]
vars [MSBlock r]
b
let fn :: SMethod r
fn = [MSParameter r] -> MSBody r -> SMethod r
f [MSParameter r]
ps MSBody r
bod
[Name]
pComms <- (ParameterChunk -> GenState Name)
-> [ParameterChunk] -> StateT DrasilState Identity [Name]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ParameterChunk -> GenState Name
forall c. CodeIdea c => c -> GenState Name
getComment [ParameterChunk]
p
SMethod r -> GenState (SMethod r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (SMethod r -> GenState (SMethod r))
-> SMethod r -> GenState (SMethod r)
forall a b. (a -> b) -> a -> b
$ if Comments
CommentFunc Comments -> [Comments] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` DrasilState -> [Comments]
commented DrasilState
g
then Name -> [Name] -> Maybe Name -> SMethod r -> SMethod r
forall (r :: * -> *).
MethodSym r =>
Name -> [Name] -> Maybe Name -> SMethod r -> SMethod r
docFunc Name
desc [Name]
pComms Maybe Name
r SMethod r
fn else SMethod r
fn
genInOutFunc :: (OOProg r) => ([SVariable r] -> [SVariable r] ->
[SVariable r] -> MSBody r -> SMethod r) ->
(String -> [(String, SVariable r)] -> [(String, SVariable r)] ->
[(String, SVariable r)] -> MSBody r -> SMethod r)
-> Label -> Description -> [CodeVarChunk] -> [CodeVarChunk] ->
[MSBlock r] -> GenState (SMethod r)
genInOutFunc :: forall (r :: * -> *).
OOProg r =>
([SVariable r]
-> [SVariable r] -> [SVariable r] -> MSBody r -> SMethod r)
-> (Name
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> MSBody r
-> SMethod r)
-> Name
-> Name
-> [Input]
-> [Input]
-> [MSBlock r]
-> GenState (SMethod r)
genInOutFunc [SVariable r]
-> [SVariable r] -> [SVariable r] -> MSBody r -> SMethod r
f Name
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> MSBody r
-> SMethod r
docf Name
n Name
desc [Input]
ins' [Input]
outs' [MSBlock r]
b = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
(DrasilState -> DrasilState) -> StateT DrasilState Identity ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\DrasilState
st -> DrasilState
st {currentScope = Local})
let ins :: [Input]
ins = [Input]
ins' [Input] -> [Input] -> [Input]
forall a. Eq a => [a] -> [a] -> [a]
\\ [Input]
outs'
outs :: [Input]
outs = [Input]
outs' [Input] -> [Input] -> [Input]
forall a. Eq a => [a] -> [a] -> [a]
\\ [Input]
ins'
both :: [Input]
both = [Input]
ins' [Input] -> [Input] -> [Input]
forall a. Eq a => [a] -> [a] -> [a]
`intersect` [Input]
outs'
[SVariable r]
inVs <- (Input -> StateT DrasilState Identity (SVariable r))
-> [Input] -> StateT DrasilState Identity [SVariable r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Input -> StateT DrasilState Identity (SVariable r)
forall (r :: * -> *). OOProg r => Input -> GenState (SVariable r)
mkVar [Input]
ins
[SVariable r]
outVs <- (Input -> StateT DrasilState Identity (SVariable r))
-> [Input] -> StateT DrasilState Identity [SVariable r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Input -> StateT DrasilState Identity (SVariable r)
forall (r :: * -> *). OOProg r => Input -> GenState (SVariable r)
mkVar [Input]
outs
[SVariable r]
bothVs <- (Input -> StateT DrasilState Identity (SVariable r))
-> [Input] -> StateT DrasilState Identity [SVariable r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Input -> StateT DrasilState Identity (SVariable r)
forall (r :: * -> *). OOProg r => Input -> GenState (SVariable r)
mkVar [Input]
both
MSBody r
bod <- Name
-> [SVariable r]
-> [MSBlock r]
-> StateT DrasilState Identity (MSBody r)
forall (r :: * -> *).
SharedProg r =>
Name -> [SVariable r] -> [MSBlock r] -> GenState (MSBody r)
logBody Name
n ([SVariable r]
bothVs [SVariable r] -> [SVariable r] -> [SVariable r]
forall a. [a] -> [a] -> [a]
++ [SVariable r]
inVs) [MSBlock r]
b
[Name]
pComms <- (Input -> GenState Name)
-> [Input] -> StateT DrasilState Identity [Name]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Input -> GenState Name
forall c. CodeIdea c => c -> GenState Name
getComment [Input]
ins
[Name]
oComms <- (Input -> GenState Name)
-> [Input] -> StateT DrasilState Identity [Name]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Input -> GenState Name
forall c. CodeIdea c => c -> GenState Name
getComment [Input]
outs
[Name]
bComms <- (Input -> GenState Name)
-> [Input] -> StateT DrasilState Identity [Name]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Input -> GenState Name
forall c. CodeIdea c => c -> GenState Name
getComment [Input]
both
SMethod r -> GenState (SMethod r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (SMethod r -> GenState (SMethod r))
-> SMethod r -> GenState (SMethod r)
forall a b. (a -> b) -> a -> b
$ if Comments
CommentFunc Comments -> [Comments] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` DrasilState -> [Comments]
commented DrasilState
g
then Name
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> MSBody r
-> SMethod r
docf Name
desc ([Name] -> [SVariable r] -> [(Name, SVariable r)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Name]
pComms [SVariable r]
inVs) ([Name] -> [SVariable r] -> [(Name, SVariable r)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Name]
oComms [SVariable r]
outVs) ([Name] -> [SVariable r] -> [(Name, SVariable r)]
forall a b. [a] -> [b] -> [(a, b)]
zip
[Name]
bComms [SVariable r]
bothVs) MSBody r
bod else [SVariable r]
-> [SVariable r] -> [SVariable r] -> MSBody r -> SMethod r
f [SVariable r]
inVs [SVariable r]
outVs [SVariable r]
bothVs MSBody r
bod
convExpr :: (OOProg r) => CodeExpr -> GenState (SValue r)
convExpr :: forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr (Lit (Dbl Double
d)) = do
CodeType
sm <- Space -> GenState CodeType
spaceCodeType Space
Real
let getLiteral :: CodeType -> SValue r
getLiteral CodeType
Double = Double -> SValue r
forall (r :: * -> *). Literal r => Double -> SValue r
litDouble Double
d
getLiteral CodeType
Float = Float -> SValue r
forall (r :: * -> *). Literal r => Float -> SValue r
litFloat (Double -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
d)
getLiteral CodeType
_ = Name -> SValue r
forall a. HasCallStack => Name -> a
error Name
"convExpr: Real space matched to invalid CodeType; should be Double or Float"
SValue r -> GenState (SValue r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (SValue r -> GenState (SValue r))
-> SValue r -> GenState (SValue r)
forall a b. (a -> b) -> a -> b
$ CodeType -> SValue r
forall {r :: * -> *}. Literal r => CodeType -> SValue r
getLiteral CodeType
sm
convExpr (Lit (ExactDbl Integer
d)) = CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr (CodeExpr -> GenState (SValue r))
-> CodeExpr -> GenState (SValue r)
forall a b. (a -> b) -> a -> b
$ Literal -> CodeExpr
Lit (Literal -> CodeExpr) -> (Double -> Literal) -> Double -> CodeExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> Literal
Dbl (Double -> CodeExpr) -> Double -> CodeExpr
forall a b. (a -> b) -> a -> b
$ Integer -> Double
forall a. Num a => Integer -> a
fromInteger Integer
d
convExpr (Lit (Int Integer
i)) = SValue r -> GenState (SValue r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (SValue r -> GenState (SValue r))
-> SValue r -> GenState (SValue r)
forall a b. (a -> b) -> a -> b
$ Integer -> SValue r
forall (r :: * -> *). Literal r => Integer -> SValue r
litInt Integer
i
convExpr (Lit (Str Name
s)) = SValue r -> GenState (SValue r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (SValue r -> GenState (SValue r))
-> SValue r -> GenState (SValue r)
forall a b. (a -> b) -> a -> b
$ Name -> SValue r
forall (r :: * -> *). Literal r => Name -> SValue r
litString Name
s
convExpr (Lit (Perc Integer
a Integer
b)) = do
CodeType
sm <- Space -> GenState CodeType
spaceCodeType Space
Rational
let getLiteral :: CodeType -> Double -> SValue r
getLiteral CodeType
Double = Double -> SValue r
forall (r :: * -> *). Literal r => Double -> SValue r
litDouble
getLiteral CodeType
Float = Float -> SValue r
forall (r :: * -> *). Literal r => Float -> SValue r
litFloat (Float -> SValue r) -> (Double -> Float) -> Double -> SValue r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac
getLiteral CodeType
_ = Name -> Double -> SValue r
forall a. HasCallStack => Name -> a
error Name
"convExpr: Rational space matched to invalid CodeType; should be Double or Float"
SValue r -> GenState (SValue r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (SValue r -> GenState (SValue r))
-> SValue r -> GenState (SValue r)
forall a b. (a -> b) -> a -> b
$ CodeType -> Double -> SValue r
forall {r :: * -> *}. Literal r => CodeType -> Double -> SValue r
getLiteral CodeType
sm (Integer -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
a Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ (Double
10 Double -> Double -> Double
forall a. Floating a => a -> a -> a
** Integer -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
b))
convExpr (AssocA AssocArithOper
Add [CodeExpr]
l) = (SValue r -> SValue r -> SValue r) -> [SValue r] -> SValue r
forall a. (a -> a -> a) -> [a] -> a
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldl1 SValue r -> SValue r -> SValue r
forall (r :: * -> *).
NumericExpression r =>
SValue r -> SValue r -> SValue r
(#+) ([SValue r] -> SValue r)
-> StateT DrasilState Identity [SValue r] -> GenState (SValue r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (CodeExpr -> GenState (SValue r))
-> [CodeExpr] -> StateT DrasilState Identity [SValue r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr [CodeExpr]
l
convExpr (AssocA AssocArithOper
Mul [CodeExpr]
l) = (SValue r -> SValue r -> SValue r) -> [SValue r] -> SValue r
forall a. (a -> a -> a) -> [a] -> a
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldl1 SValue r -> SValue r -> SValue r
forall (r :: * -> *).
NumericExpression r =>
SValue r -> SValue r -> SValue r
(#*) ([SValue r] -> SValue r)
-> StateT DrasilState Identity [SValue r] -> GenState (SValue r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (CodeExpr -> GenState (SValue r))
-> [CodeExpr] -> StateT DrasilState Identity [SValue r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr [CodeExpr]
l
convExpr (AssocB AssocBoolOper
And [CodeExpr]
l) = (SValue r -> SValue r -> SValue r) -> [SValue r] -> SValue r
forall a. (a -> a -> a) -> [a] -> a
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldl1 SValue r -> SValue r -> SValue r
forall (r :: * -> *).
BooleanExpression r =>
SValue r -> SValue r -> SValue r
(?&&) ([SValue r] -> SValue r)
-> StateT DrasilState Identity [SValue r] -> GenState (SValue r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (CodeExpr -> GenState (SValue r))
-> [CodeExpr] -> StateT DrasilState Identity [SValue r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr [CodeExpr]
l
convExpr (AssocB AssocBoolOper
Or [CodeExpr]
l) = (SValue r -> SValue r -> SValue r) -> [SValue r] -> SValue r
forall a. (a -> a -> a) -> [a] -> a
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldl1 SValue r -> SValue r -> SValue r
forall (r :: * -> *).
BooleanExpression r =>
SValue r -> SValue r -> SValue r
(?||) ([SValue r] -> SValue r)
-> StateT DrasilState Identity [SValue r] -> GenState (SValue r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (CodeExpr -> GenState (SValue r))
-> [CodeExpr] -> StateT DrasilState Identity [SValue r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr [CodeExpr]
l
convExpr (AssocC AssocConcatOper
SUnion [CodeExpr]
l) = (SValue r -> SValue r -> SValue r) -> [SValue r] -> SValue r
forall a. (a -> a -> a) -> [a] -> a
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldl1 SValue r -> SValue r -> SValue r
forall (r :: * -> *).
NumericExpression r =>
SValue r -> SValue r -> SValue r
(#+) ([SValue r] -> SValue r)
-> StateT DrasilState Identity [SValue r] -> GenState (SValue r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (CodeExpr -> GenState (SValue r))
-> [CodeExpr] -> StateT DrasilState Identity [SValue r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr [CodeExpr]
l
convExpr (C UID
c) = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
let v :: Input
v = QuantityDict -> Input
forall c. (Quantity c, MayHaveUnit c) => c -> Input
quantvar (DrasilState -> UID -> QuantityDict
lookupC DrasilState
g UID
c)
Input -> GenState (SValue r)
forall (r :: * -> *). OOProg r => Input -> GenState (SValue r)
mkVal Input
v
convExpr (FCall UID
c [CodeExpr]
x [(UID, CodeExpr)]
ns) = UID
-> [CodeExpr]
-> [(UID, CodeExpr)]
-> (Name
-> Name
-> VSType r
-> [SValue r]
-> NamedArgs r
-> GenState (SValue r))
-> (Name
-> Name -> VSType r -> [SValue r] -> NamedArgs r -> SValue r)
-> GenState (SValue r)
forall (r :: * -> *).
OOProg r =>
UID
-> [CodeExpr]
-> [(UID, CodeExpr)]
-> (Name
-> Name
-> VSType r
-> [SValue r]
-> NamedArgs r
-> GenState (SValue r))
-> (Name
-> Name -> VSType r -> [SValue r] -> NamedArgs r -> SValue r)
-> GenState (SValue r)
convCall UID
c [CodeExpr]
x [(UID, CodeExpr)]
ns Name
-> Name
-> VSType r
-> [SValue r]
-> NamedArgs r
-> GenState (SValue r)
forall (r :: * -> *).
OOProg r =>
Name
-> Name
-> VSType r
-> [SValue r]
-> NamedArgs r
-> GenState (SValue r)
fApp Name -> Name -> VSType r -> [SValue r] -> NamedArgs r -> SValue r
forall (r :: * -> *). ValueExpression r => Name -> MixedCall r
libFuncAppMixedArgs
convExpr (New UID
c [CodeExpr]
x [(UID, CodeExpr)]
ns) = UID
-> [CodeExpr]
-> [(UID, CodeExpr)]
-> (Name
-> Name
-> VSType r
-> [SValue r]
-> NamedArgs r
-> GenState (SValue r))
-> (Name
-> Name -> VSType r -> [SValue r] -> NamedArgs r -> SValue r)
-> GenState (SValue r)
forall (r :: * -> *).
OOProg r =>
UID
-> [CodeExpr]
-> [(UID, CodeExpr)]
-> (Name
-> Name
-> VSType r
-> [SValue r]
-> NamedArgs r
-> GenState (SValue r))
-> (Name
-> Name -> VSType r -> [SValue r] -> NamedArgs r -> SValue r)
-> GenState (SValue r)
convCall UID
c [CodeExpr]
x [(UID, CodeExpr)]
ns (\Name
m Name
_ -> Name
-> VSType r -> [SValue r] -> NamedArgs r -> GenState (SValue r)
forall (r :: * -> *).
OOProg r =>
Name
-> VSType r -> [SValue r] -> NamedArgs r -> GenState (SValue r)
ctorCall Name
m)
(\Name
m Name
_ -> Name -> VSType r -> [SValue r] -> NamedArgs r -> SValue r
forall (r :: * -> *).
OOValueExpression r =>
Name -> MixedCtorCall r
libNewObjMixedArgs Name
m)
convExpr (Message UID
a UID
m [CodeExpr]
x [(UID, CodeExpr)]
ns) = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
let info :: ChunkDB
info = DrasilState -> CodeSpec
codeSpec DrasilState
g CodeSpec -> Getting ChunkDB CodeSpec ChunkDB -> ChunkDB
forall s a. s -> Getting a s a -> a
^. Getting ChunkDB CodeSpec ChunkDB
forall c. HasOldCodeSpec c => Lens' c ChunkDB
Lens' CodeSpec ChunkDB
sysinfodbO
objCd :: Input
objCd = QuantityDict -> Input
forall c. (Quantity c, MayHaveUnit c) => c -> Input
quantvar (ChunkDB -> UID -> QuantityDict
symbResolve ChunkDB
info UID
a)
SValue r
o <- Input -> GenState (SValue r)
forall (r :: * -> *). OOProg r => Input -> GenState (SValue r)
mkVal Input
objCd
UID
-> [CodeExpr]
-> [(UID, CodeExpr)]
-> (Name
-> Name
-> VSType r
-> [SValue r]
-> NamedArgs r
-> GenState (SValue r))
-> (Name
-> Name -> VSType r -> [SValue r] -> NamedArgs r -> SValue r)
-> GenState (SValue r)
forall (r :: * -> *).
OOProg r =>
UID
-> [CodeExpr]
-> [(UID, CodeExpr)]
-> (Name
-> Name
-> VSType r
-> [SValue r]
-> NamedArgs r
-> GenState (SValue r))
-> (Name
-> Name -> VSType r -> [SValue r] -> NamedArgs r -> SValue r)
-> GenState (SValue r)
convCall UID
m [CodeExpr]
x [(UID, CodeExpr)]
ns
(\Name
_ Name
n VSType r
t [SValue r]
ps NamedArgs r
nas -> SValue r -> GenState (SValue r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (VSType r
-> SValue r -> Name -> [SValue r] -> NamedArgs r -> SValue r
forall (r :: * -> *).
InternalValueExp r =>
VSType r
-> SValue r -> Name -> [SValue r] -> NamedArgs r -> SValue r
objMethodCallMixedArgs VSType r
t SValue r
o Name
n [SValue r]
ps NamedArgs r
nas))
(\Name
_ Name
n VSType r
t -> VSType r
-> SValue r -> Name -> [SValue r] -> NamedArgs r -> SValue r
forall (r :: * -> *).
InternalValueExp r =>
VSType r
-> SValue r -> Name -> [SValue r] -> NamedArgs r -> SValue r
objMethodCallMixedArgs VSType r
t SValue r
o Name
n)
convExpr (Field UID
o UID
f) = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
let ob :: Input
ob = QuantityDict -> Input
forall c. (Quantity c, MayHaveUnit c) => c -> Input
quantvar (DrasilState -> UID -> QuantityDict
lookupC DrasilState
g UID
o)
fld :: Input
fld = QuantityDict -> Input
forall c. (Quantity c, MayHaveUnit c) => c -> Input
quantvar (DrasilState -> UID -> QuantityDict
lookupC DrasilState
g UID
f)
VS (r (Variable r))
v <- Input -> StateT DrasilState Identity (VS (r (Variable r)))
forall (r :: * -> *). OOProg r => Input -> GenState (SVariable r)
mkVar (Input -> Input -> Input
ccObjVar Input
ob Input
fld)
SValue r -> GenState (SValue r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (SValue r -> GenState (SValue r))
-> SValue r -> GenState (SValue r)
forall a b. (a -> b) -> a -> b
$ VS (r (Variable r)) -> SValue r
forall (r :: * -> *). VariableValue r => SVariable r -> SValue r
valueOf VS (r (Variable r))
v
convExpr (UnaryOp UFunc
o CodeExpr
u) = (SValue r -> SValue r)
-> GenState (SValue r) -> GenState (SValue r)
forall a b.
(a -> b)
-> StateT DrasilState Identity a -> StateT DrasilState Identity b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (UFunc -> SValue r -> SValue r
forall (r :: * -> *). SharedProg r => UFunc -> SValue r -> SValue r
unop UFunc
o) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
u)
convExpr (UnaryOpB UFuncB
o CodeExpr
u) = (SValue r -> SValue r)
-> GenState (SValue r) -> GenState (SValue r)
forall a b.
(a -> b)
-> StateT DrasilState Identity a -> StateT DrasilState Identity b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (UFuncB -> SValue r -> SValue r
forall (r :: * -> *).
SharedProg r =>
UFuncB -> SValue r -> SValue r
unopB UFuncB
o) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
u)
convExpr (UnaryOpVV UFuncVV
o CodeExpr
u) = (SValue r -> SValue r)
-> GenState (SValue r) -> GenState (SValue r)
forall a b.
(a -> b)
-> StateT DrasilState Identity a -> StateT DrasilState Identity b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (UFuncVV -> SValue r -> SValue r
forall (r :: * -> *).
SharedProg r =>
UFuncVV -> SValue r -> SValue r
unopVV UFuncVV
o) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
u)
convExpr (UnaryOpVN UFuncVN
o CodeExpr
u) = (SValue r -> SValue r)
-> GenState (SValue r) -> GenState (SValue r)
forall a b.
(a -> b)
-> StateT DrasilState Identity a -> StateT DrasilState Identity b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (UFuncVN -> SValue r -> SValue r
forall (r :: * -> *).
SharedProg r =>
UFuncVN -> SValue r -> SValue r
unopVN UFuncVN
o) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
u)
convExpr (ArithBinaryOp ArithBinOp
Frac (Lit (Int Integer
a)) (Lit (Int Integer
b))) = do
CodeType
sm <- Space -> GenState CodeType
spaceCodeType Space
Rational
let getLiteral :: CodeType -> SValue r
getLiteral CodeType
Double = Double -> SValue r
forall (r :: * -> *). Literal r => Double -> SValue r
litDouble (Integer -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
a) SValue r -> SValue r -> SValue r
forall (r :: * -> *).
NumericExpression r =>
SValue r -> SValue r -> SValue r
#/ Double -> SValue r
forall (r :: * -> *). Literal r => Double -> SValue r
litDouble (Integer -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
b)
getLiteral CodeType
Float = Float -> SValue r
forall (r :: * -> *). Literal r => Float -> SValue r
litFloat (Integer -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
a) SValue r -> SValue r -> SValue r
forall (r :: * -> *).
NumericExpression r =>
SValue r -> SValue r -> SValue r
#/ Float -> SValue r
forall (r :: * -> *). Literal r => Float -> SValue r
litFloat (Integer -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
b)
getLiteral CodeType
_ = Name -> SValue r
forall a. HasCallStack => Name -> a
error Name
"convExpr: Rational space matched to invalid CodeType; should be Double or Float"
SValue r -> GenState (SValue r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (SValue r -> GenState (SValue r))
-> SValue r -> GenState (SValue r)
forall a b. (a -> b) -> a -> b
$ CodeType -> SValue r
forall {r :: * -> *}.
(NumericExpression r, Literal r) =>
CodeType -> SValue r
getLiteral CodeType
sm
convExpr (ArithBinaryOp ArithBinOp
o CodeExpr
a CodeExpr
b) = (SValue r -> SValue r -> SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 (ArithBinOp -> SValue r -> SValue r -> SValue r
forall (r :: * -> *).
SharedProg r =>
ArithBinOp -> SValue r -> SValue r -> SValue r
arithBfunc ArithBinOp
o) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
a) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
b)
convExpr (BoolBinaryOp BoolBinOp
o CodeExpr
a CodeExpr
b) = (SValue r -> SValue r -> SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 (BoolBinOp -> SValue r -> SValue r -> SValue r
forall (r :: * -> *). BoolBinOp -> SValue r -> SValue r -> SValue r
boolBfunc BoolBinOp
o) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
a) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
b)
convExpr (LABinaryOp LABinOp
o CodeExpr
a CodeExpr
b) = (SValue r -> SValue r -> SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 (LABinOp -> SValue r -> SValue r -> SValue r
forall (r :: * -> *).
SharedProg r =>
LABinOp -> SValue r -> SValue r -> SValue r
laBfunc LABinOp
o) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
a) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
b)
convExpr (EqBinaryOp EqBinOp
o CodeExpr
a CodeExpr
b) = (SValue r -> SValue r -> SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 (EqBinOp -> SValue r -> SValue r -> SValue r
forall (r :: * -> *).
SharedProg r =>
EqBinOp -> SValue r -> SValue r -> SValue r
eqBfunc EqBinOp
o) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
a) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
b)
convExpr (OrdBinaryOp OrdBinOp
o CodeExpr
a CodeExpr
b) = (SValue r -> SValue r -> SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 (OrdBinOp -> SValue r -> SValue r -> SValue r
forall (r :: * -> *).
SharedProg r =>
OrdBinOp -> SValue r -> SValue r -> SValue r
ordBfunc OrdBinOp
o) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
a) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
b)
convExpr (VVVBinaryOp VVVBinOp
o CodeExpr
a CodeExpr
b) = (SValue r -> SValue r -> SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 (VVVBinOp -> SValue r -> SValue r -> SValue r
forall (r :: * -> *). VVVBinOp -> SValue r -> SValue r -> SValue r
vecVecVecBfunc VVVBinOp
o) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
a) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
b)
convExpr (VVNBinaryOp VVNBinOp
o CodeExpr
a CodeExpr
b) = (SValue r -> SValue r -> SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 (VVNBinOp -> SValue r -> SValue r -> SValue r
forall (r :: * -> *). VVNBinOp -> SValue r -> SValue r -> SValue r
vecVecNumBfunc VVNBinOp
o) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
a) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
b)
convExpr (NVVBinaryOp NVVBinOp
o CodeExpr
a CodeExpr
b) = (SValue r -> SValue r -> SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 (NVVBinOp -> SValue r -> SValue r -> SValue r
forall (r :: * -> *). NVVBinOp -> SValue r -> SValue r -> SValue r
numVecVecBfunc NVVBinOp
o) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
a) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
b)
convExpr (ESSBinaryOp ESSBinOp
o CodeExpr
a CodeExpr
b) = (SValue r -> SValue r -> SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 (ESSBinOp -> SValue r -> SValue r -> SValue r
forall (r :: * -> *).
SharedProg r =>
ESSBinOp -> SValue r -> SValue r -> SValue r
elementSetSetBfunc ESSBinOp
o) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
a) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
b)
convExpr (ESBBinaryOp ESBBinOp
o CodeExpr
a CodeExpr
b) = (SValue r -> SValue r -> SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 (ESBBinOp -> SValue r -> SValue r -> SValue r
forall (r :: * -> *).
SharedProg r =>
ESBBinOp -> SValue r -> SValue r -> SValue r
elementSetBoolBfunc ESBBinOp
o) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
a) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
b)
convExpr (Case Completeness
c [(CodeExpr, CodeExpr)]
l) = [(CodeExpr, CodeExpr)] -> GenState (SValue r)
forall {r :: * -> *}.
OOProg r =>
[(CodeExpr, CodeExpr)]
-> StateT DrasilState Identity (VS (r (Value r)))
doit [(CodeExpr, CodeExpr)]
l
where
doit :: [(CodeExpr, CodeExpr)]
-> StateT DrasilState Identity (VS (r (Value r)))
doit [] = Name -> StateT DrasilState Identity (VS (r (Value r)))
forall a. HasCallStack => Name -> a
error Name
"should never happen"
doit [(CodeExpr
e,CodeExpr
_)] = CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
e
doit ((CodeExpr
e,CodeExpr
cond):[(CodeExpr, CodeExpr)]
xs) = (VS (r (Value r))
-> VS (r (Value r)) -> VS (r (Value r)) -> VS (r (Value r)))
-> StateT DrasilState Identity (VS (r (Value r)))
-> StateT DrasilState Identity (VS (r (Value r)))
-> StateT DrasilState Identity (VS (r (Value r)))
-> StateT DrasilState Identity (VS (r (Value r)))
forall (m :: * -> *) a1 a2 a3 r.
Monad m =>
(a1 -> a2 -> a3 -> r) -> m a1 -> m a2 -> m a3 -> m r
liftM3 VS (r (Value r))
-> VS (r (Value r)) -> VS (r (Value r)) -> VS (r (Value r))
forall (r :: * -> *).
ValueExpression r =>
SValue r -> SValue r -> SValue r -> SValue r
inlineIf (CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
cond) (CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
e)
(CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr (Completeness -> [(CodeExpr, CodeExpr)] -> CodeExpr
Case Completeness
c [(CodeExpr, CodeExpr)]
xs))
convExpr (Matrix [[CodeExpr]
l]) = do
[SValue r]
ar <- (CodeExpr -> GenState (SValue r))
-> [CodeExpr] -> StateT DrasilState Identity [SValue r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr [CodeExpr]
l
SValue r -> GenState (SValue r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (SValue r -> GenState (SValue r))
-> SValue r -> GenState (SValue r)
forall a b. (a -> b) -> a -> b
$ VSType r -> [SValue r] -> SValue r
forall (r :: * -> *).
Literal r =>
VSType r -> [SValue r] -> SValue r
litArray ((r (Value r) -> r (Type r)) -> SValue r -> VSType r
forall a b.
(a -> b)
-> StateT ValueState Identity a -> StateT ValueState Identity b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap r (Value r) -> r (Type r)
forall (r :: * -> *). ValueSym r => r (Value r) -> r (Type r)
valueType ([SValue r] -> SValue r
forall a. HasCallStack => [a] -> a
head [SValue r]
ar)) [SValue r]
ar
convExpr Matrix{} = Name -> GenState (SValue r)
forall a. HasCallStack => Name -> a
error Name
"convExpr: Matrix"
convExpr (S.Set Space
s [CodeExpr]
l) = do
[SValue r]
ar <- (CodeExpr -> GenState (SValue r))
-> [CodeExpr] -> StateT DrasilState Identity [SValue r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr [CodeExpr]
l
CodeType
sm <- Space -> GenState CodeType
spaceCodeType Space
s
SValue r -> GenState (SValue r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (SValue r -> GenState (SValue r))
-> SValue r -> GenState (SValue r)
forall a b. (a -> b) -> a -> b
$ VSType r -> [SValue r] -> SValue r
forall (r :: * -> *).
Literal r =>
VSType r -> [SValue r] -> SValue r
litSet (CodeType -> VSType r
forall (r :: * -> *). OOTypeSym r => CodeType -> VSType r
convTypeOO CodeType
sm) [SValue r]
ar
convExpr(Variable Name
s (S.Set Space
l [CodeExpr]
_)) = do
CodeType
sm <- Space -> GenState CodeType
spaceCodeType Space
l
let varSet :: VS (r (Variable r))
varSet = Name -> VSType r -> VS (r (Variable r))
forall (r :: * -> *).
VariableSym r =>
Name -> VSType r -> SVariable r
var Name
s (VSType r -> VSType r
forall (r :: * -> *). TypeSym r => VSType r -> VSType r
setType (VSType r -> VSType r) -> VSType r -> VSType r
forall a b. (a -> b) -> a -> b
$ CodeType -> VSType r
forall (r :: * -> *). OOTypeSym r => CodeType -> VSType r
convTypeOO CodeType
sm)
SValue r -> GenState (SValue r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (SValue r -> GenState (SValue r))
-> SValue r -> GenState (SValue r)
forall a b. (a -> b) -> a -> b
$ VS (r (Variable r)) -> SValue r
forall (r :: * -> *). VariableValue r => SVariable r -> SValue r
valueOf VS (r (Variable r))
varSet
convExpr(Variable Name
_ CodeExpr
_) = Name -> GenState (SValue r)
forall a. HasCallStack => Name -> a
error Name
"convExpr: Variable"
convExpr Operator{} = Name -> GenState (SValue r)
forall a. HasCallStack => Name -> a
error Name
"convExpr: Operator"
convExpr (RealI UID
c RealInterval CodeExpr CodeExpr
ri) = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr (CodeExpr -> GenState (SValue r))
-> CodeExpr -> GenState (SValue r)
forall a b. (a -> b) -> a -> b
$ QuantityDict -> RealInterval CodeExpr CodeExpr -> CodeExpr
forall c.
(HasUID c, HasSymbol c) =>
c -> RealInterval CodeExpr CodeExpr -> CodeExpr
renderRealInt (DrasilState -> UID -> QuantityDict
lookupC DrasilState
g UID
c) RealInterval CodeExpr CodeExpr
ri
convCall :: (OOProg r) => UID -> [CodeExpr] -> [(UID, CodeExpr)] ->
(Name -> Name -> VSType r -> [SValue r] -> NamedArgs r ->
GenState (SValue r)) -> (Name -> Name -> VSType r -> [SValue r]
-> NamedArgs r -> SValue r) -> GenState (SValue r)
convCall :: forall (r :: * -> *).
OOProg r =>
UID
-> [CodeExpr]
-> [(UID, CodeExpr)]
-> (Name
-> Name
-> VSType r
-> [SValue r]
-> NamedArgs r
-> GenState (SValue r))
-> (Name
-> Name -> VSType r -> [SValue r] -> NamedArgs r -> SValue r)
-> GenState (SValue r)
convCall UID
c [CodeExpr]
x [(UID, CodeExpr)]
ns Name
-> Name
-> VSType r
-> [SValue r]
-> NamedArgs r
-> GenState (SValue r)
f Name -> Name -> VSType r -> [SValue r] -> NamedArgs r -> SValue r
libf = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
let info :: ChunkDB
info = DrasilState -> CodeSpec
codeSpec DrasilState
g CodeSpec -> Getting ChunkDB CodeSpec ChunkDB -> ChunkDB
forall s a. s -> Getting a s a -> a
^. Getting ChunkDB CodeSpec ChunkDB
forall c. HasOldCodeSpec c => Lens' c ChunkDB
Lens' CodeSpec ChunkDB
sysinfodbO
mem :: Map Name Name
mem = DrasilState -> Map Name Name
eMap DrasilState
g
lem :: Map Name Name
lem = DrasilState -> Map Name Name
libEMap DrasilState
g
funcCd :: CodeFuncChunk
funcCd = QuantityDict -> CodeFuncChunk
forall c. (Quantity c, MayHaveUnit c) => c -> CodeFuncChunk
quantfunc (ChunkDB -> UID -> QuantityDict
symbResolve ChunkDB
info UID
c)
funcNm :: Name
funcNm = CodeFuncChunk -> Name
forall c. CodeIdea c => c -> Name
codeName CodeFuncChunk
funcCd
CodeType
funcTp <- CodeFuncChunk -> GenState CodeType
forall c. HasSpace c => c -> GenState CodeType
codeType CodeFuncChunk
funcCd
[SValue r]
args <- (CodeExpr -> GenState (SValue r))
-> [CodeExpr] -> StateT DrasilState Identity [SValue r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr [CodeExpr]
x
[VS (r (Variable r))]
nms <- ((UID, CodeExpr)
-> StateT DrasilState Identity (VS (r (Variable r))))
-> [(UID, CodeExpr)]
-> StateT DrasilState Identity [VS (r (Variable r))]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (Input -> StateT DrasilState Identity (VS (r (Variable r)))
forall (r :: * -> *). OOProg r => Input -> GenState (SVariable r)
mkVar (Input -> StateT DrasilState Identity (VS (r (Variable r))))
-> ((UID, CodeExpr) -> Input)
-> (UID, CodeExpr)
-> StateT DrasilState Identity (VS (r (Variable r)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QuantityDict -> Input
forall c. (Quantity c, MayHaveUnit c) => c -> Input
quantvar (QuantityDict -> Input)
-> ((UID, CodeExpr) -> QuantityDict) -> (UID, CodeExpr) -> Input
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ChunkDB -> UID -> QuantityDict
symbResolve ChunkDB
info (UID -> QuantityDict)
-> ((UID, CodeExpr) -> UID) -> (UID, CodeExpr) -> QuantityDict
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (UID, CodeExpr) -> UID
forall a b. (a, b) -> a
fst) [(UID, CodeExpr)]
ns
[SValue r]
nargs <- ((UID, CodeExpr) -> GenState (SValue r))
-> [(UID, CodeExpr)] -> StateT DrasilState Identity [SValue r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr (CodeExpr -> GenState (SValue r))
-> ((UID, CodeExpr) -> CodeExpr)
-> (UID, CodeExpr)
-> GenState (SValue r)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (UID, CodeExpr) -> CodeExpr
forall a b. (a, b) -> b
snd) [(UID, CodeExpr)]
ns
GenState (SValue r)
-> (Name -> GenState (SValue r))
-> Maybe Name
-> GenState (SValue r)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (GenState (SValue r)
-> (Name -> GenState (SValue r))
-> Maybe Name
-> GenState (SValue r)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Name -> GenState (SValue r)
forall a. HasCallStack => Name -> a
error (Name -> GenState (SValue r)) -> Name -> GenState (SValue r)
forall a b. (a -> b) -> a -> b
$ Name
"Call to non-existent function " Name -> Name -> Name
forall a. [a] -> [a] -> [a]
++ Name
funcNm)
(\Name
m -> SValue r -> GenState (SValue r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (SValue r -> GenState (SValue r))
-> SValue r -> GenState (SValue r)
forall a b. (a -> b) -> a -> b
$ Name -> Name -> VSType r -> [SValue r] -> NamedArgs r -> SValue r
libf Name
m Name
funcNm (CodeType -> VSType r
forall (r :: * -> *). OOTypeSym r => CodeType -> VSType r
convTypeOO CodeType
funcTp) [SValue r]
args ([VS (r (Variable r))] -> [SValue r] -> NamedArgs r
forall a b. [a] -> [b] -> [(a, b)]
zip [VS (r (Variable r))]
nms [SValue r]
nargs))
(Name -> Map Name Name -> Maybe Name
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Name
funcNm Map Name Name
lem))
(\Name
m -> Name
-> Name
-> VSType r
-> [SValue r]
-> NamedArgs r
-> GenState (SValue r)
f Name
m Name
funcNm (CodeType -> VSType r
forall (r :: * -> *). OOTypeSym r => CodeType -> VSType r
convTypeOO CodeType
funcTp) [SValue r]
args ([VS (r (Variable r))] -> [SValue r] -> NamedArgs r
forall a b. [a] -> [b] -> [(a, b)]
zip [VS (r (Variable r))]
nms [SValue r]
nargs))
(Name -> Map Name Name -> Maybe Name
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Name
funcNm Map Name Name
mem)
renderC :: (HasUID c, HasSymbol c) => c -> Constraint CodeExpr -> CodeExpr
renderC :: forall c.
(HasUID c, HasSymbol c) =>
c -> Constraint CodeExpr -> CodeExpr
renderC c
s (Range ConstraintReason
_ RealInterval CodeExpr CodeExpr
rr) = c -> RealInterval CodeExpr CodeExpr -> CodeExpr
forall c.
(HasUID c, HasSymbol c) =>
c -> RealInterval CodeExpr CodeExpr -> CodeExpr
renderRealInt c
s RealInterval CodeExpr CodeExpr
rr
renderC c
s (Elem ConstraintReason
_ CodeExpr
rr) = c -> CodeExpr -> CodeExpr
forall c. (HasUID c, HasSymbol c) => c -> CodeExpr -> CodeExpr
renderSet c
s CodeExpr
rr
renderRealInt :: (HasUID c, HasSymbol c) => c -> RealInterval CodeExpr CodeExpr -> CodeExpr
renderRealInt :: forall c.
(HasUID c, HasSymbol c) =>
c -> RealInterval CodeExpr CodeExpr -> CodeExpr
renderRealInt c
s (Bounded (Inclusive
Inc, CodeExpr
a) (Inclusive
Inc, CodeExpr
b)) = (CodeExpr
a CodeExpr -> CodeExpr -> CodeExpr
forall r. ExprC r => r -> r -> r
$<= c -> CodeExpr
forall c. (HasUID c, HasSymbol c) => c -> CodeExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy c
s) CodeExpr -> CodeExpr -> CodeExpr
forall r. ExprC r => r -> r -> r
$&& (c -> CodeExpr
forall c. (HasUID c, HasSymbol c) => c -> CodeExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy c
s CodeExpr -> CodeExpr -> CodeExpr
forall r. ExprC r => r -> r -> r
$<= CodeExpr
b)
renderRealInt c
s (Bounded (Inclusive
Inc, CodeExpr
a) (Inclusive
Exc, CodeExpr
b)) = (CodeExpr
a CodeExpr -> CodeExpr -> CodeExpr
forall r. ExprC r => r -> r -> r
$<= c -> CodeExpr
forall c. (HasUID c, HasSymbol c) => c -> CodeExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy c
s) CodeExpr -> CodeExpr -> CodeExpr
forall r. ExprC r => r -> r -> r
$&& (c -> CodeExpr
forall c. (HasUID c, HasSymbol c) => c -> CodeExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy c
s CodeExpr -> CodeExpr -> CodeExpr
forall r. ExprC r => r -> r -> r
$< CodeExpr
b)
renderRealInt c
s (Bounded (Inclusive
Exc, CodeExpr
a) (Inclusive
Inc, CodeExpr
b)) = (CodeExpr
a CodeExpr -> CodeExpr -> CodeExpr
forall r. ExprC r => r -> r -> r
$< c -> CodeExpr
forall c. (HasUID c, HasSymbol c) => c -> CodeExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy c
s) CodeExpr -> CodeExpr -> CodeExpr
forall r. ExprC r => r -> r -> r
$&& (c -> CodeExpr
forall c. (HasUID c, HasSymbol c) => c -> CodeExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy c
s CodeExpr -> CodeExpr -> CodeExpr
forall r. ExprC r => r -> r -> r
$<= CodeExpr
b)
renderRealInt c
s (Bounded (Inclusive
Exc, CodeExpr
a) (Inclusive
Exc, CodeExpr
b)) = (CodeExpr
a CodeExpr -> CodeExpr -> CodeExpr
forall r. ExprC r => r -> r -> r
$< c -> CodeExpr
forall c. (HasUID c, HasSymbol c) => c -> CodeExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy c
s) CodeExpr -> CodeExpr -> CodeExpr
forall r. ExprC r => r -> r -> r
$&& (c -> CodeExpr
forall c. (HasUID c, HasSymbol c) => c -> CodeExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy c
s CodeExpr -> CodeExpr -> CodeExpr
forall r. ExprC r => r -> r -> r
$< CodeExpr
b)
renderRealInt c
s (UpTo (Inclusive
Inc, CodeExpr
a)) = c -> CodeExpr
forall c. (HasUID c, HasSymbol c) => c -> CodeExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy c
s CodeExpr -> CodeExpr -> CodeExpr
forall r. ExprC r => r -> r -> r
$<= CodeExpr
a
renderRealInt c
s (UpTo (Inclusive
Exc, CodeExpr
a)) = c -> CodeExpr
forall c. (HasUID c, HasSymbol c) => c -> CodeExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy c
s CodeExpr -> CodeExpr -> CodeExpr
forall r. ExprC r => r -> r -> r
$< CodeExpr
a
renderRealInt c
s (UpFrom (Inclusive
Inc, CodeExpr
a)) = c -> CodeExpr
forall c. (HasUID c, HasSymbol c) => c -> CodeExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy c
s CodeExpr -> CodeExpr -> CodeExpr
forall r. ExprC r => r -> r -> r
$>= CodeExpr
a
renderRealInt c
s (UpFrom (Inclusive
Exc, CodeExpr
a)) = c -> CodeExpr
forall c. (HasUID c, HasSymbol c) => c -> CodeExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy c
s CodeExpr -> CodeExpr -> CodeExpr
forall r. ExprC r => r -> r -> r
$> CodeExpr
a
renderSet :: (HasUID c, HasSymbol c) => c -> CodeExpr -> CodeExpr
renderSet :: forall c. (HasUID c, HasSymbol c) => c -> CodeExpr -> CodeExpr
renderSet c
e CodeExpr
s = CodeExpr -> CodeExpr -> CodeExpr
forall r. ExprC r => r -> r -> r
in' (Name -> CodeExpr -> CodeExpr
Variable (Name
"set_" Name -> Name -> Name
forall a. [a] -> [a] -> [a]
++ c -> Name
forall x. HasSymbol x => x -> Name
showHasSymbImpl c
e) CodeExpr
s) (c -> CodeExpr
forall c. (HasUID c, HasSymbol c) => c -> CodeExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy c
e)
unop :: (SharedProg r) => UFunc -> (SValue r -> SValue r)
unop :: forall (r :: * -> *). SharedProg r => UFunc -> SValue r -> SValue r
unop UFunc
Sqrt = SValue r -> SValue r
forall (r :: * -> *). NumericExpression r => SValue r -> SValue r
(#/^)
unop UFunc
Log = SValue r -> SValue r
forall (r :: * -> *). NumericExpression r => SValue r -> SValue r
log
unop UFunc
Ln = SValue r -> SValue r
forall (r :: * -> *). NumericExpression r => SValue r -> SValue r
ln
unop UFunc
Abs = SValue r -> SValue r
forall (r :: * -> *). NumericExpression r => SValue r -> SValue r
(#|)
unop UFunc
Exp = SValue r -> SValue r
forall (r :: * -> *). NumericExpression r => SValue r -> SValue r
exp
unop UFunc
Sin = SValue r -> SValue r
forall (r :: * -> *). NumericExpression r => SValue r -> SValue r
sin
unop UFunc
Cos = SValue r -> SValue r
forall (r :: * -> *). NumericExpression r => SValue r -> SValue r
cos
unop UFunc
Tan = SValue r -> SValue r
forall (r :: * -> *). NumericExpression r => SValue r -> SValue r
tan
unop UFunc
Csc = SValue r -> SValue r
forall (r :: * -> *). NumericExpression r => SValue r -> SValue r
csc
unop UFunc
Sec = SValue r -> SValue r
forall (r :: * -> *). NumericExpression r => SValue r -> SValue r
sec
unop UFunc
Cot = SValue r -> SValue r
forall (r :: * -> *). NumericExpression r => SValue r -> SValue r
cot
unop UFunc
Arcsin = SValue r -> SValue r
forall (r :: * -> *). NumericExpression r => SValue r -> SValue r
arcsin
unop UFunc
Arccos = SValue r -> SValue r
forall (r :: * -> *). NumericExpression r => SValue r -> SValue r
arccos
unop UFunc
Arctan = SValue r -> SValue r
forall (r :: * -> *). NumericExpression r => SValue r -> SValue r
arctan
unop UFunc
Neg = SValue r -> SValue r
forall (r :: * -> *). NumericExpression r => SValue r -> SValue r
(#~)
unopB :: (SharedProg r) => UFuncB -> (SValue r -> SValue r)
unopB :: forall (r :: * -> *).
SharedProg r =>
UFuncB -> SValue r -> SValue r
unopB UFuncB
Not = SValue r -> SValue r
forall (r :: * -> *). BooleanExpression r => SValue r -> SValue r
(?!)
unopVN :: (SharedProg r) => UFuncVN -> (SValue r -> SValue r)
unopVN :: forall (r :: * -> *).
SharedProg r =>
UFuncVN -> SValue r -> SValue r
unopVN UFuncVN
Dim = SValue r -> SValue r
forall (r :: * -> *). List r => SValue r -> SValue r
listSize
unopVN UFuncVN
Norm = Name -> SValue r -> SValue r
forall a. HasCallStack => Name -> a
error Name
"unop: Norm not implemented"
unopVV :: (SharedProg r) => UFuncVV -> (SValue r -> SValue r)
unopVV :: forall (r :: * -> *).
SharedProg r =>
UFuncVV -> SValue r -> SValue r
unopVV UFuncVV
NegV = Name -> VS (r (Value r)) -> VS (r (Value r))
forall a. HasCallStack => Name -> a
error Name
"unop: Negation on Vectors not implemented"
arithBfunc :: (SharedProg r) => ArithBinOp -> (SValue r -> SValue r -> SValue r)
arithBfunc :: forall (r :: * -> *).
SharedProg r =>
ArithBinOp -> SValue r -> SValue r -> SValue r
arithBfunc ArithBinOp
Pow = SValue r -> SValue r -> SValue r
forall (r :: * -> *).
NumericExpression r =>
SValue r -> SValue r -> SValue r
(#^)
arithBfunc ArithBinOp
Subt = SValue r -> SValue r -> SValue r
forall (r :: * -> *).
NumericExpression r =>
SValue r -> SValue r -> SValue r
(#-)
arithBfunc ArithBinOp
Frac = SValue r -> SValue r -> SValue r
forall (r :: * -> *).
NumericExpression r =>
SValue r -> SValue r -> SValue r
(#/)
boolBfunc :: BoolBinOp -> (SValue r -> SValue r -> SValue r)
boolBfunc :: forall (r :: * -> *). BoolBinOp -> SValue r -> SValue r -> SValue r
boolBfunc BoolBinOp
Impl = Name -> VS (r (Value r)) -> VS (r (Value r)) -> VS (r (Value r))
forall a. HasCallStack => Name -> a
error Name
"convExpr :=>"
boolBfunc BoolBinOp
Iff = Name -> VS (r (Value r)) -> VS (r (Value r)) -> VS (r (Value r))
forall a. HasCallStack => Name -> a
error Name
"convExpr :<=>"
eqBfunc :: (SharedProg r) => EqBinOp -> (SValue r -> SValue r -> SValue r)
eqBfunc :: forall (r :: * -> *).
SharedProg r =>
EqBinOp -> SValue r -> SValue r -> SValue r
eqBfunc EqBinOp
Eq = SValue r -> SValue r -> SValue r
forall (r :: * -> *).
Comparison r =>
SValue r -> SValue r -> SValue r
(?==)
eqBfunc EqBinOp
NEq = SValue r -> SValue r -> SValue r
forall (r :: * -> *).
Comparison r =>
SValue r -> SValue r -> SValue r
(?!=)
laBfunc :: (SharedProg r) => LABinOp -> (SValue r -> SValue r -> SValue r)
laBfunc :: forall (r :: * -> *).
SharedProg r =>
LABinOp -> SValue r -> SValue r -> SValue r
laBfunc LABinOp
Index = SValue r -> SValue r -> SValue r
forall (r :: * -> *). List r => SValue r -> SValue r -> SValue r
listAccess
laBfunc LABinOp
IndexOf = SValue r -> SValue r -> SValue r
forall (r :: * -> *). List r => SValue r -> SValue r -> SValue r
indexOf
ordBfunc :: (SharedProg r) => OrdBinOp -> (SValue r -> SValue r -> SValue r)
ordBfunc :: forall (r :: * -> *).
SharedProg r =>
OrdBinOp -> SValue r -> SValue r -> SValue r
ordBfunc OrdBinOp
Gt = SValue r -> SValue r -> SValue r
forall (r :: * -> *).
Comparison r =>
SValue r -> SValue r -> SValue r
(?>)
ordBfunc OrdBinOp
Lt = SValue r -> SValue r -> SValue r
forall (r :: * -> *).
Comparison r =>
SValue r -> SValue r -> SValue r
(?<)
ordBfunc OrdBinOp
LEq = SValue r -> SValue r -> SValue r
forall (r :: * -> *).
Comparison r =>
SValue r -> SValue r -> SValue r
(?<=)
ordBfunc OrdBinOp
GEq = SValue r -> SValue r -> SValue r
forall (r :: * -> *).
Comparison r =>
SValue r -> SValue r -> SValue r
(?>=)
vecVecVecBfunc :: VVVBinOp -> (SValue r -> SValue r -> SValue r)
vecVecVecBfunc :: forall (r :: * -> *). VVVBinOp -> SValue r -> SValue r -> SValue r
vecVecVecBfunc VVVBinOp
Cross = Name -> VS (r (Value r)) -> VS (r (Value r)) -> VS (r (Value r))
forall a. HasCallStack => Name -> a
error Name
"bfunc: Cross not implemented"
vecVecVecBfunc VVVBinOp
VAdd = Name -> VS (r (Value r)) -> VS (r (Value r)) -> VS (r (Value r))
forall a. HasCallStack => Name -> a
error Name
"bfunc: Vector addition not implemented"
vecVecVecBfunc VVVBinOp
VSub = Name -> VS (r (Value r)) -> VS (r (Value r)) -> VS (r (Value r))
forall a. HasCallStack => Name -> a
error Name
"bfunc: Vector subtraction not implemented"
vecVecNumBfunc :: VVNBinOp -> (SValue r -> SValue r -> SValue r)
vecVecNumBfunc :: forall (r :: * -> *). VVNBinOp -> SValue r -> SValue r -> SValue r
vecVecNumBfunc VVNBinOp
Dot = Name -> VS (r (Value r)) -> VS (r (Value r)) -> VS (r (Value r))
forall a. HasCallStack => Name -> a
error Name
"convExpr DotProduct"
numVecVecBfunc :: NVVBinOp -> (SValue r -> SValue r -> SValue r)
numVecVecBfunc :: forall (r :: * -> *). NVVBinOp -> SValue r -> SValue r -> SValue r
numVecVecBfunc NVVBinOp
Scale = Name -> VS (r (Value r)) -> VS (r (Value r)) -> VS (r (Value r))
forall a. HasCallStack => Name -> a
error Name
"convExpr Scaling of Vectors"
elementSetSetBfunc :: (SharedProg r) => ESSBinOp -> (SValue r -> SValue r -> SValue r)
elementSetSetBfunc :: forall (r :: * -> *).
SharedProg r =>
ESSBinOp -> SValue r -> SValue r -> SValue r
elementSetSetBfunc ESSBinOp
SAdd = SValue r -> SValue r -> SValue r
forall (r :: * -> *). Set r => SValue r -> SValue r -> SValue r
S.setAdd
elementSetSetBfunc ESSBinOp
SRemove = SValue r -> SValue r -> SValue r
forall (r :: * -> *). Set r => SValue r -> SValue r -> SValue r
S.setRemove
elementSetBoolBfunc :: (SharedProg r) => ESBBinOp -> (SValue r -> SValue r -> SValue r)
elementSetBoolBfunc :: forall (r :: * -> *).
SharedProg r =>
ESBBinOp -> SValue r -> SValue r -> SValue r
elementSetBoolBfunc ESBBinOp
SContains = SValue r -> SValue r -> SValue r
forall (r :: * -> *). Set r => SValue r -> SValue r -> SValue r
S.contains
genModDef :: (OOProg r) => Mod -> GenState (OO.SFile r)
genModDef :: forall (r :: * -> *). OOProg r => Mod -> GenState (SFile r)
genModDef (Mod Name
n Name
desc [Name]
is [Class]
cs [Func]
fs) = Name
-> Name
-> [Name]
-> [GenState (Maybe (SMethod r))]
-> [GenState (Maybe (SClass r))]
-> StateT
DrasilState Identity (StateT FileState Identity (r (File r)))
forall (r :: * -> *).
OOProg r =>
Name
-> Name
-> [Name]
-> [GenState (Maybe (SMethod r))]
-> [GenState (Maybe (SClass r))]
-> GenState (SFile r)
genModuleWithImports Name
n Name
desc [Name]
is ((Func -> GenState (Maybe (SMethod r)))
-> [Func] -> [GenState (Maybe (SMethod r))]
forall a b. (a -> b) -> [a] -> [b]
map ((SMethod r -> Maybe (SMethod r))
-> StateT DrasilState Identity (SMethod r)
-> GenState (Maybe (SMethod r))
forall a b.
(a -> b)
-> StateT DrasilState Identity a -> StateT DrasilState Identity b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap
SMethod r -> Maybe (SMethod r)
forall a. a -> Maybe a
Just (StateT DrasilState Identity (SMethod r)
-> GenState (Maybe (SMethod r)))
-> (Func -> StateT DrasilState Identity (SMethod r))
-> Func
-> GenState (Maybe (SMethod r))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> StateT DrasilState Identity (SMethod r))
-> [StateVariable]
-> Func
-> StateT DrasilState Identity (SMethod r)
forall (r :: * -> *).
OOProg r =>
(Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r))
-> [StateVariable] -> Func -> GenState (SMethod r)
genFunc Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> StateT DrasilState Identity (SMethod r)
forall (r :: * -> *).
OOProg r =>
Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
publicFunc []) [Func]
fs)
(case [Class]
cs of [] -> []
(Class
cl:[Class]
cls) -> (SClass r -> Maybe (SClass r))
-> StateT DrasilState Identity (SClass r)
-> GenState (Maybe (SClass r))
forall a b.
(a -> b)
-> StateT DrasilState Identity a -> StateT DrasilState Identity b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SClass r -> Maybe (SClass r)
forall a. a -> Maybe a
Just ((Name
-> Maybe Name
-> Name
-> [CSStateVar r]
-> GenState [SMethod r]
-> GenState [SMethod r]
-> StateT DrasilState Identity (SClass r))
-> Class -> StateT DrasilState Identity (SClass r)
forall (r :: * -> *).
OOProg r =>
(Name
-> Maybe Name
-> Name
-> [CSStateVar r]
-> GenState [SMethod r]
-> GenState [SMethod r]
-> GenState (SClass r))
-> Class -> GenState (SClass r)
genClass Name
-> Maybe Name
-> Name
-> [CSStateVar r]
-> GenState [SMethod r]
-> GenState [SMethod r]
-> StateT DrasilState Identity (SClass r)
forall (r :: * -> *).
OOProg r =>
Name
-> Maybe Name
-> Name
-> [CSStateVar r]
-> GenState [SMethod r]
-> GenState [SMethod r]
-> GenState (SClass r)
primaryClass Class
cl) GenState (Maybe (SClass r))
-> [GenState (Maybe (SClass r))] -> [GenState (Maybe (SClass r))]
forall a. a -> [a] -> [a]
:
(Class -> GenState (Maybe (SClass r)))
-> [Class] -> [GenState (Maybe (SClass r))]
forall a b. (a -> b) -> [a] -> [b]
map ((SClass r -> Maybe (SClass r))
-> StateT DrasilState Identity (SClass r)
-> GenState (Maybe (SClass r))
forall a b.
(a -> b)
-> StateT DrasilState Identity a -> StateT DrasilState Identity b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SClass r -> Maybe (SClass r)
forall a. a -> Maybe a
Just (StateT DrasilState Identity (SClass r)
-> GenState (Maybe (SClass r)))
-> (Class -> StateT DrasilState Identity (SClass r))
-> Class
-> GenState (Maybe (SClass r))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Name
-> Maybe Name
-> Name
-> [CSStateVar r]
-> GenState [SMethod r]
-> GenState [SMethod r]
-> StateT DrasilState Identity (SClass r))
-> Class -> StateT DrasilState Identity (SClass r)
forall (r :: * -> *).
OOProg r =>
(Name
-> Maybe Name
-> Name
-> [CSStateVar r]
-> GenState [SMethod r]
-> GenState [SMethod r]
-> GenState (SClass r))
-> Class -> GenState (SClass r)
genClass Name
-> Maybe Name
-> Name
-> [CSStateVar r]
-> GenState [SMethod r]
-> GenState [SMethod r]
-> StateT DrasilState Identity (SClass r)
forall (r :: * -> *).
OOProg r =>
Name
-> Maybe Name
-> Name
-> [CSStateVar r]
-> GenState [SMethod r]
-> GenState [SMethod r]
-> GenState (SClass r)
auxClass) [Class]
cls)
genModFuncs :: (OOProg r) => Mod -> [GenState (SMethod r)]
genModFuncs :: forall (r :: * -> *). OOProg r => Mod -> [GenState (SMethod r)]
genModFuncs (Mod Name
_ Name
_ [Name]
_ [Class]
_ [Func]
fs) = (Func -> GenState (MS (r (Method r))))
-> [Func] -> [GenState (MS (r (Method r)))]
forall a b. (a -> b) -> [a] -> [b]
map ((Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (MS (r (Method r))))
-> [StateVariable] -> Func -> GenState (MS (r (Method r)))
forall (r :: * -> *).
OOProg r =>
(Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r))
-> [StateVariable] -> Func -> GenState (SMethod r)
genFunc Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (MS (r (Method r)))
forall (r :: * -> *).
OOProg r =>
Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
publicFunc []) [Func]
fs
genModClasses :: (OOProg r) => Mod -> [GenState (SClass r)]
genModClasses :: forall (r :: * -> *). OOProg r => Mod -> [GenState (SClass r)]
genModClasses (Mod Name
_ Name
_ [Name]
_ [Class]
cs [Func]
_) = (Class -> GenState (CS (r (Class r))))
-> [Class] -> [GenState (CS (r (Class r)))]
forall a b. (a -> b) -> [a] -> [b]
map ((Name
-> Maybe Name
-> Name
-> [CSStateVar r]
-> GenState [SMethod r]
-> GenState [SMethod r]
-> GenState (CS (r (Class r))))
-> Class -> GenState (CS (r (Class r)))
forall (r :: * -> *).
OOProg r =>
(Name
-> Maybe Name
-> Name
-> [CSStateVar r]
-> GenState [SMethod r]
-> GenState [SMethod r]
-> GenState (SClass r))
-> Class -> GenState (SClass r)
genClass Name
-> Maybe Name
-> Name
-> [CSStateVar r]
-> GenState [SMethod r]
-> GenState [SMethod r]
-> GenState (CS (r (Class r)))
forall (r :: * -> *).
OOProg r =>
Name
-> Maybe Name
-> Name
-> [CSStateVar r]
-> GenState [SMethod r]
-> GenState [SMethod r]
-> GenState (SClass r)
auxClass) [Class]
cs
genClass :: (OOProg r) => (Name -> Maybe Name -> Description -> [CSStateVar r]
-> GenState [SMethod r] -> GenState [SMethod r] -> GenState (SClass r)) ->
M.Class -> GenState (SClass r)
genClass :: forall (r :: * -> *).
OOProg r =>
(Name
-> Maybe Name
-> Name
-> [CSStateVar r]
-> GenState [SMethod r]
-> GenState [SMethod r]
-> GenState (SClass r))
-> Class -> GenState (SClass r)
genClass Name
-> Maybe Name
-> Name
-> [CSStateVar r]
-> GenState [SMethod r]
-> GenState [SMethod r]
-> GenState (SClass r)
f (M.ClassDef Name
n Maybe Name
i Name
desc [StateVariable]
svs [Func]
cs [Func]
ms) = let svar :: VisibilityTag -> SVariable r -> CSStateVar r
svar VisibilityTag
Pub = SVariable r -> CSStateVar r
forall (r :: * -> *). StateVarSym r => SVariable r -> CSStateVar r
pubDVar
svar VisibilityTag
Priv = SVariable r -> CSStateVar r
forall (r :: * -> *). StateVarSym r => SVariable r -> CSStateVar r
privDVar
in do
(DrasilState -> DrasilState) -> StateT DrasilState Identity ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\DrasilState
st -> DrasilState
st {currentScope = Local})
[CSStateVar r]
svrs <- (StateVariable -> StateT DrasilState Identity (CSStateVar r))
-> [StateVariable] -> StateT DrasilState Identity [CSStateVar r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (\(SV VisibilityTag
s Input
v) -> (CodeType -> CSStateVar r)
-> GenState CodeType -> StateT DrasilState Identity (CSStateVar r)
forall a b.
(a -> b)
-> StateT DrasilState Identity a -> StateT DrasilState Identity b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (VisibilityTag -> VS (r (Variable r)) -> CSStateVar r
forall {r :: * -> *}.
StateVarSym r =>
VisibilityTag -> SVariable r -> CSStateVar r
svar VisibilityTag
s (VS (r (Variable r)) -> CSStateVar r)
-> (CodeType -> VS (r (Variable r))) -> CodeType -> CSStateVar r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> VS (r (Type r)) -> VS (r (Variable r))
forall (r :: * -> *).
VariableSym r =>
Name -> VSType r -> SVariable r
var (Input -> Name
forall c. CodeIdea c => c -> Name
codeName Input
v) (VS (r (Type r)) -> VS (r (Variable r)))
-> (CodeType -> VS (r (Type r))) -> CodeType -> VS (r (Variable r))
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
CodeType -> VS (r (Type r))
forall (r :: * -> *). OOTypeSym r => CodeType -> VSType r
convTypeOO) (Input -> GenState CodeType
forall c. HasSpace c => c -> GenState CodeType
codeType Input
v)) [StateVariable]
svs
Name
-> Maybe Name
-> Name
-> [CSStateVar r]
-> GenState [SMethod r]
-> GenState [SMethod r]
-> GenState (SClass r)
f Name
n Maybe Name
i Name
desc [CSStateVar r]
svrs ((Func -> StateT DrasilState Identity (SMethod r))
-> [Func] -> GenState [SMethod r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((Name
-> VS (r (Type r))
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> StateT DrasilState Identity (SMethod r))
-> [StateVariable]
-> Func
-> StateT DrasilState Identity (SMethod r)
forall (r :: * -> *).
OOProg r =>
(Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r))
-> [StateVariable] -> Func -> GenState (SMethod r)
genFunc Name
-> VS (r (Type r))
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> StateT DrasilState Identity (SMethod r)
forall (r :: * -> *).
OOProg r =>
Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
publicMethod [StateVariable]
svs) [Func]
cs)
((Func -> StateT DrasilState Identity (SMethod r))
-> [Func] -> GenState [SMethod r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((Name
-> VS (r (Type r))
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> StateT DrasilState Identity (SMethod r))
-> [StateVariable]
-> Func
-> StateT DrasilState Identity (SMethod r)
forall (r :: * -> *).
OOProg r =>
(Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r))
-> [StateVariable] -> Func -> GenState (SMethod r)
genFunc Name
-> VS (r (Type r))
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> StateT DrasilState Identity (SMethod r)
forall (r :: * -> *).
OOProg r =>
Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
publicMethod [StateVariable]
svs) [Func]
ms)
genFunc :: (OOProg r) => (Name -> VSType r -> Description -> [ParameterChunk]
-> Maybe Description -> [MSBlock r] -> GenState (SMethod r)) ->
[StateVariable] -> Func -> GenState (SMethod r)
genFunc :: forall (r :: * -> *).
OOProg r =>
(Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r))
-> [StateVariable] -> Func -> GenState (SMethod r)
genFunc Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
f [StateVariable]
svs (FDef (FuncDef Name
n Name
desc [ParameterChunk]
parms Space
o Maybe Name
rd [FuncStmt]
s)) = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
(DrasilState -> DrasilState) -> StateT DrasilState Identity ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\DrasilState
st -> DrasilState
st {currentScope = Local})
[MS (r (Statement r))]
stmts <- (FuncStmt -> StateT DrasilState Identity (MS (r (Statement r))))
-> [FuncStmt] -> StateT DrasilState Identity [MS (r (Statement r))]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FuncStmt -> StateT DrasilState Identity (MS (r (Statement r)))
forall (r :: * -> *).
OOProg r =>
FuncStmt -> GenState (MSStatement r)
convStmt [FuncStmt]
s
[VS (r (Variable r))]
vars <- (Input -> StateT DrasilState Identity (VS (r (Variable r))))
-> [Input] -> StateT DrasilState Identity [VS (r (Variable r))]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Input -> StateT DrasilState Identity (VS (r (Variable r)))
forall (r :: * -> *). OOProg r => Input -> GenState (SVariable r)
mkVar (ChunkDB -> [FuncStmt] -> [Input]
fstdecl (DrasilState -> CodeSpec
codeSpec DrasilState
g CodeSpec -> Getting ChunkDB CodeSpec ChunkDB -> ChunkDB
forall s a. s -> Getting a s a -> a
^. Getting ChunkDB CodeSpec ChunkDB
forall c. HasOldCodeSpec c => Lens' c ChunkDB
Lens' CodeSpec ChunkDB
sysinfodbO) [FuncStmt]
s
[Input] -> [Input] -> [Input]
forall a. Eq a => [a] -> [a] -> [a]
\\ ((ParameterChunk -> Input) -> [ParameterChunk] -> [Input]
forall a b. (a -> b) -> [a] -> [b]
map ParameterChunk -> Input
forall c. (Quantity c, MayHaveUnit c) => c -> Input
quantvar [ParameterChunk]
parms [Input] -> [Input] -> [Input]
forall a. [a] -> [a] -> [a]
++ (StateVariable -> Input) -> [StateVariable] -> [Input]
forall a b. (a -> b) -> [a] -> [b]
map StateVariable -> Input
stVar [StateVariable]
svs))
CodeType
t <- Space -> GenState CodeType
spaceCodeType Space
o
Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
f Name
n (CodeType -> VSType r
forall (r :: * -> *). OOTypeSym r => CodeType -> VSType r
convTypeOO CodeType
t) Name
desc [ParameterChunk]
parms Maybe Name
rd [[MS (r (Statement r))] -> MSBlock r
forall (r :: * -> *). BlockSym r => [MSStatement r] -> MSBlock r
block ([MS (r (Statement r))] -> MSBlock r)
-> [MS (r (Statement r))] -> MSBlock r
forall a b. (a -> b) -> a -> b
$ (VS (r (Variable r)) -> MS (r (Statement r)))
-> [VS (r (Variable r))] -> [MS (r (Statement r))]
forall a b. (a -> b) -> [a] -> [b]
map (VS (r (Variable r)) -> r (Scope r) -> MS (r (Statement r))
forall (r :: * -> *).
DeclStatement r =>
SVariable r -> r (Scope r) -> MSStatement r
`varDec` r (Scope r)
forall (r :: * -> *). ScopeSym r => r (Scope r)
local) [VS (r (Variable r))]
vars, [MS (r (Statement r))] -> MSBlock r
forall (r :: * -> *). BlockSym r => [MSStatement r] -> MSBlock r
block [MS (r (Statement r))]
stmts]
genFunc Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
_ [StateVariable]
svs (FDef (CtorDef Name
n Name
desc [ParameterChunk]
parms [Initializer]
i [FuncStmt]
s)) = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
(DrasilState -> DrasilState) -> StateT DrasilState Identity ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\DrasilState
st -> DrasilState
st {currentScope = Local})
[VS (r (Value r))]
inits <- (Initializer -> StateT DrasilState Identity (VS (r (Value r))))
-> [Initializer] -> StateT DrasilState Identity [VS (r (Value r))]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr (CodeExpr -> StateT DrasilState Identity (VS (r (Value r))))
-> (Initializer -> CodeExpr)
-> Initializer
-> StateT DrasilState Identity (VS (r (Value r)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Initializer -> CodeExpr
forall a b. (a, b) -> b
snd) [Initializer]
i
[VS (r (Variable r))]
initvars <- (Initializer -> StateT DrasilState Identity (VS (r (Variable r))))
-> [Initializer]
-> StateT DrasilState Identity [VS (r (Variable r))]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((\Input
iv -> (CodeType -> VS (r (Variable r)))
-> GenState CodeType
-> StateT DrasilState Identity (VS (r (Variable r)))
forall a b.
(a -> b)
-> StateT DrasilState Identity a -> StateT DrasilState Identity b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Name -> VSType r -> VS (r (Variable r))
forall (r :: * -> *).
VariableSym r =>
Name -> VSType r -> SVariable r
var (Input -> Name
forall c. CodeIdea c => c -> Name
codeName Input
iv) (VSType r -> VS (r (Variable r)))
-> (CodeType -> VSType r) -> CodeType -> VS (r (Variable r))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CodeType -> VSType r
forall (r :: * -> *). OOTypeSym r => CodeType -> VSType r
convTypeOO)
(Input -> GenState CodeType
forall c. HasSpace c => c -> GenState CodeType
codeType Input
iv)) (Input -> StateT DrasilState Identity (VS (r (Variable r))))
-> (Initializer -> Input)
-> Initializer
-> StateT DrasilState Identity (VS (r (Variable r)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Initializer -> Input
forall a b. (a, b) -> a
fst) [Initializer]
i
[MS (r (Statement r))]
stmts <- (FuncStmt -> StateT DrasilState Identity (MS (r (Statement r))))
-> [FuncStmt] -> StateT DrasilState Identity [MS (r (Statement r))]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FuncStmt -> StateT DrasilState Identity (MS (r (Statement r)))
forall (r :: * -> *).
OOProg r =>
FuncStmt -> GenState (MSStatement r)
convStmt [FuncStmt]
s
[VS (r (Variable r))]
vars <- (Input -> StateT DrasilState Identity (VS (r (Variable r))))
-> [Input] -> StateT DrasilState Identity [VS (r (Variable r))]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Input -> StateT DrasilState Identity (VS (r (Variable r)))
forall (r :: * -> *). OOProg r => Input -> GenState (SVariable r)
mkVar (ChunkDB -> [FuncStmt] -> [Input]
fstdecl (DrasilState -> CodeSpec
codeSpec DrasilState
g CodeSpec -> Getting ChunkDB CodeSpec ChunkDB -> ChunkDB
forall s a. s -> Getting a s a -> a
^. Getting ChunkDB CodeSpec ChunkDB
forall c. HasOldCodeSpec c => Lens' c ChunkDB
Lens' CodeSpec ChunkDB
sysinfodbO) [FuncStmt]
s
[Input] -> [Input] -> [Input]
forall a. Eq a => [a] -> [a] -> [a]
\\ ((ParameterChunk -> Input) -> [ParameterChunk] -> [Input]
forall a b. (a -> b) -> [a] -> [b]
map ParameterChunk -> Input
forall c. (Quantity c, MayHaveUnit c) => c -> Input
quantvar [ParameterChunk]
parms [Input] -> [Input] -> [Input]
forall a. [a] -> [a] -> [a]
++ (StateVariable -> Input) -> [StateVariable] -> [Input]
forall a b. (a -> b) -> [a] -> [b]
map StateVariable -> Input
stVar [StateVariable]
svs))
Name
-> Name
-> [ParameterChunk]
-> Initializers r
-> [MSBlock r]
-> GenState (SMethod r)
forall (r :: * -> *).
OOProg r =>
Name
-> Name
-> [ParameterChunk]
-> Initializers r
-> [MSBlock r]
-> GenState (SMethod r)
genInitConstructor Name
n Name
desc [ParameterChunk]
parms ([VS (r (Variable r))] -> [VS (r (Value r))] -> Initializers r
forall a b. [a] -> [b] -> [(a, b)]
zip [VS (r (Variable r))]
initvars [VS (r (Value r))]
inits)
[[MS (r (Statement r))] -> MSBlock r
forall (r :: * -> *). BlockSym r => [MSStatement r] -> MSBlock r
block ([MS (r (Statement r))] -> MSBlock r)
-> [MS (r (Statement r))] -> MSBlock r
forall a b. (a -> b) -> a -> b
$ (VS (r (Variable r)) -> MS (r (Statement r)))
-> [VS (r (Variable r))] -> [MS (r (Statement r))]
forall a b. (a -> b) -> [a] -> [b]
map (VS (r (Variable r)) -> r (Scope r) -> MS (r (Statement r))
forall (r :: * -> *).
DeclStatement r =>
SVariable r -> r (Scope r) -> MSStatement r
`varDec` r (Scope r)
forall (r :: * -> *). ScopeSym r => r (Scope r)
local) [VS (r (Variable r))]
vars, [MS (r (Statement r))] -> MSBlock r
forall (r :: * -> *). BlockSym r => [MSStatement r] -> MSBlock r
block [MS (r (Statement r))]
stmts]
genFunc Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
_ [StateVariable]
_ (FData (FuncData Name
n Name
desc DataDesc
ddef)) = do
(DrasilState -> DrasilState) -> StateT DrasilState Identity ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\DrasilState
st -> DrasilState
st {currentScope = Local})
Name -> Name -> DataDesc -> GenState (SMethod r)
forall (r :: * -> *).
OOProg r =>
Name -> Name -> DataDesc -> GenState (SMethod r)
genDataFunc Name
n Name
desc DataDesc
ddef
convStmt :: (OOProg r) => FuncStmt -> GenState (MSStatement r)
convStmt :: forall (r :: * -> *).
OOProg r =>
FuncStmt -> GenState (MSStatement r)
convStmt (FAsg Input
v (Matrix [[CodeExpr]
es])) = do
[VS (r (Value r))]
els <- (CodeExpr -> StateT DrasilState Identity (VS (r (Value r))))
-> [CodeExpr] -> StateT DrasilState Identity [VS (r (Value r))]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr [CodeExpr]
es
StateT ValueState Identity (r (Variable r))
v' <- Input
-> StateT
DrasilState Identity (StateT ValueState Identity (r (Variable r)))
forall (r :: * -> *). OOProg r => Input -> GenState (SVariable r)
mkVar Input
v
CodeType
t <- Input -> GenState CodeType
forall c. HasSpace c => c -> GenState CodeType
codeType Input
v
let listFunc :: CodeType -> VSType r -> [SValue r] -> SValue r
listFunc (C.List CodeType
_) = VSType r -> [SValue r] -> SValue r
forall (r :: * -> *).
Literal r =>
VSType r -> [SValue r] -> SValue r
litList
listFunc (C.Array CodeType
_) = VSType r -> [SValue r] -> SValue r
forall (r :: * -> *).
Literal r =>
VSType r -> [SValue r] -> SValue r
litArray
listFunc CodeType
_ = Name -> VSType r -> [SValue r] -> SValue r
forall a. HasCallStack => Name -> a
error Name
"Type mismatch between variable and value in assignment FuncStmt"
[MSStatement r]
l <- StateT ValueState Identity (r (Variable r))
-> StateT DrasilState Identity [MSStatement r]
forall (r :: * -> *).
SharedProg r =>
SVariable r -> GenState [MSStatement r]
maybeLog StateT ValueState Identity (r (Variable r))
v'
MSStatement r -> GenState (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (MSStatement r -> GenState (MSStatement r))
-> MSStatement r -> GenState (MSStatement r)
forall a b. (a -> b) -> a -> b
$ [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
$ StateT ValueState Identity (r (Variable r))
-> VS (r (Value r)) -> MSStatement r
forall (r :: * -> *).
AssignStatement r =>
SVariable r -> SValue r -> MSStatement r
assign StateT ValueState Identity (r (Variable r))
v' (CodeType
-> VS (r (Type r)) -> [VS (r (Value r))] -> VS (r (Value r))
forall {r :: * -> *}.
Literal r =>
CodeType -> VSType r -> [SValue r] -> SValue r
listFunc CodeType
t (VS (r (Type r)) -> VS (r (Type r))
forall (r :: * -> *). TypeSym r => VSType r -> VSType r
listInnerType (VS (r (Type r)) -> VS (r (Type r)))
-> VS (r (Type r)) -> VS (r (Type r))
forall a b. (a -> b) -> a -> b
$ (r (Variable r) -> r (Type r))
-> StateT ValueState Identity (r (Variable r)) -> VS (r (Type r))
forall a b.
(a -> b)
-> StateT ValueState Identity a -> StateT ValueState Identity b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap r (Variable r) -> r (Type r)
forall (r :: * -> *).
VariableElim r =>
r (Variable r) -> r (Type r)
variableType StateT ValueState Identity (r (Variable r))
v')
[VS (r (Value r))]
els) MSStatement r -> [MSStatement r] -> [MSStatement r]
forall a. a -> [a] -> [a]
: [MSStatement r]
l
convStmt (FAsg Input
v CodeExpr
e) = do
VS (r (Value r))
e' <- CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
e
StateT ValueState Identity (r (Variable r))
v' <- Input
-> StateT
DrasilState Identity (StateT ValueState Identity (r (Variable r)))
forall (r :: * -> *). OOProg r => Input -> GenState (SVariable r)
mkVar Input
v
[MSStatement r]
l <- StateT ValueState Identity (r (Variable r))
-> StateT DrasilState Identity [MSStatement r]
forall (r :: * -> *).
SharedProg r =>
SVariable r -> GenState [MSStatement r]
maybeLog StateT ValueState Identity (r (Variable r))
v'
MSStatement r -> GenState (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (MSStatement r -> GenState (MSStatement r))
-> MSStatement r -> GenState (MSStatement r)
forall a b. (a -> b) -> a -> b
$ [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
$ StateT ValueState Identity (r (Variable r))
-> VS (r (Value r)) -> MSStatement r
forall (r :: * -> *).
AssignStatement r =>
SVariable r -> SValue r -> MSStatement r
assign StateT ValueState Identity (r (Variable r))
v' VS (r (Value r))
e' MSStatement r -> [MSStatement r] -> [MSStatement r]
forall a. a -> [a] -> [a]
: [MSStatement r]
l
convStmt (FAsgIndex Input
v Integer
i CodeExpr
e) = do
VS (r (Value r))
e' <- CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
e
StateT ValueState Identity (r (Variable r))
v' <- Input
-> StateT
DrasilState Identity (StateT ValueState Identity (r (Variable r)))
forall (r :: * -> *). OOProg r => Input -> GenState (SVariable r)
mkVar Input
v
CodeType
t <- Input -> GenState CodeType
forall c. HasSpace c => c -> GenState CodeType
codeType Input
v
let asgFunc :: CodeType -> MSStatement r
asgFunc (C.List CodeType
_) = VS (r (Value r)) -> MSStatement r
forall (r :: * -> *). StatementSym r => SValue r -> MSStatement r
valStmt (VS (r (Value r)) -> MSStatement r)
-> VS (r (Value r)) -> MSStatement r
forall a b. (a -> b) -> a -> b
$ VS (r (Value r))
-> VS (r (Value r)) -> VS (r (Value r)) -> VS (r (Value r))
forall (r :: * -> *).
List r =>
SValue r -> SValue r -> SValue r -> SValue r
listSet (StateT ValueState Identity (r (Variable r)) -> VS (r (Value r))
forall (r :: * -> *). VariableValue r => SVariable r -> SValue r
valueOf StateT ValueState Identity (r (Variable r))
v') (Integer -> VS (r (Value r))
forall (r :: * -> *). Literal r => Integer -> SValue r
litInt Integer
i) VS (r (Value r))
e'
asgFunc (C.Array CodeType
_) = StateT ValueState Identity (r (Variable r))
-> VS (r (Value r)) -> MSStatement r
forall (r :: * -> *).
AssignStatement r =>
SVariable r -> SValue r -> MSStatement r
assign (Integer
-> StateT ValueState Identity (r (Variable r))
-> StateT ValueState Identity (r (Variable r))
forall (r :: * -> *).
VariableSym r =>
Integer -> SVariable r -> SVariable r
arrayElem Integer
i StateT ValueState Identity (r (Variable r))
v') VS (r (Value r))
e'
asgFunc CodeType
_ = Name -> MSStatement r
forall a. HasCallStack => Name -> a
error Name
"FAsgIndex used with non-indexed value"
vi :: StateT ValueState Identity (r (Variable r))
vi = Integer
-> StateT ValueState Identity (r (Variable r))
-> StateT ValueState Identity (r (Variable r))
forall (r :: * -> *).
VariableSym r =>
Integer -> SVariable r -> SVariable r
arrayElem Integer
i StateT ValueState Identity (r (Variable r))
v'
[MSStatement r]
l <- StateT ValueState Identity (r (Variable r))
-> StateT DrasilState Identity [MSStatement r]
forall (r :: * -> *).
SharedProg r =>
SVariable r -> GenState [MSStatement r]
maybeLog StateT ValueState Identity (r (Variable r))
vi
MSStatement r -> GenState (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (MSStatement r -> GenState (MSStatement r))
-> MSStatement r -> GenState (MSStatement r)
forall a b. (a -> b) -> a -> b
$ [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
asgFunc CodeType
t MSStatement r -> [MSStatement r] -> [MSStatement r]
forall a. a -> [a] -> [a]
: [MSStatement r]
l
convStmt (FFor Input
v CodeExpr
start CodeExpr
end CodeExpr
step [FuncStmt]
st) = do
[MSStatement r]
stmts <- (FuncStmt -> GenState (MSStatement r))
-> [FuncStmt] -> StateT DrasilState Identity [MSStatement r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FuncStmt -> GenState (MSStatement r)
forall (r :: * -> *).
OOProg r =>
FuncStmt -> GenState (MSStatement r)
convStmt [FuncStmt]
st
StateT ValueState Identity (r (Variable r))
vari <- Input
-> StateT
DrasilState Identity (StateT ValueState Identity (r (Variable r)))
forall (r :: * -> *). OOProg r => Input -> GenState (SVariable r)
mkVar Input
v
VS (r (Value r))
start' <- CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
start
VS (r (Value r))
end' <- CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
end
VS (r (Value r))
step' <- CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
step
MSStatement r -> GenState (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (MSStatement r -> GenState (MSStatement r))
-> MSStatement r -> GenState (MSStatement r)
forall a b. (a -> b) -> a -> b
$ StateT ValueState Identity (r (Variable r))
-> VS (r (Value r))
-> VS (r (Value r))
-> VS (r (Value r))
-> MSBody r
-> MSStatement r
forall (r :: * -> *).
ControlStatement r =>
SVariable r
-> SValue r -> SValue r -> SValue r -> MSBody r -> MSStatement r
forRange StateT ValueState Identity (r (Variable r))
vari VS (r (Value r))
start' VS (r (Value r))
end' VS (r (Value r))
step' ([MSStatement r] -> MSBody r
forall (r :: * -> *). BodySym r => [MSStatement r] -> MSBody r
bodyStatements [MSStatement r]
stmts)
convStmt (FForEach Input
v CodeExpr
e [FuncStmt]
st) = do
[MSStatement r]
stmts <- (FuncStmt -> GenState (MSStatement r))
-> [FuncStmt] -> StateT DrasilState Identity [MSStatement r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FuncStmt -> GenState (MSStatement r)
forall (r :: * -> *).
OOProg r =>
FuncStmt -> GenState (MSStatement r)
convStmt [FuncStmt]
st
StateT ValueState Identity (r (Variable r))
vari <- Input
-> StateT
DrasilState Identity (StateT ValueState Identity (r (Variable r)))
forall (r :: * -> *). OOProg r => Input -> GenState (SVariable r)
mkVar Input
v
VS (r (Value r))
e' <- CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
e
MSStatement r -> GenState (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (MSStatement r -> GenState (MSStatement r))
-> MSStatement r -> GenState (MSStatement r)
forall a b. (a -> b) -> a -> b
$ StateT ValueState Identity (r (Variable r))
-> VS (r (Value r)) -> MSBody r -> MSStatement r
forall (r :: * -> *).
ControlStatement r =>
SVariable r -> SValue r -> MSBody r -> MSStatement r
forEach StateT ValueState Identity (r (Variable r))
vari VS (r (Value r))
e' ([MSStatement r] -> MSBody r
forall (r :: * -> *). BodySym r => [MSStatement r] -> MSBody r
bodyStatements [MSStatement r]
stmts)
convStmt (FWhile CodeExpr
e [FuncStmt]
st) = do
[MSStatement r]
stmts <- (FuncStmt -> GenState (MSStatement r))
-> [FuncStmt] -> StateT DrasilState Identity [MSStatement r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FuncStmt -> GenState (MSStatement r)
forall (r :: * -> *).
OOProg r =>
FuncStmt -> GenState (MSStatement r)
convStmt [FuncStmt]
st
VS (r (Value r))
e' <- CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
e
MSStatement r -> GenState (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (MSStatement r -> GenState (MSStatement r))
-> MSStatement r -> GenState (MSStatement r)
forall a b. (a -> b) -> a -> b
$ VS (r (Value r)) -> MSBody r -> MSStatement r
forall (r :: * -> *).
ControlStatement r =>
SValue r -> MSBody r -> MSStatement r
while VS (r (Value r))
e' ([MSStatement r] -> MSBody r
forall (r :: * -> *). BodySym r => [MSStatement r] -> MSBody r
bodyStatements [MSStatement r]
stmts)
convStmt (FCond CodeExpr
e [FuncStmt]
tSt []) = do
[MSStatement r]
stmts <- (FuncStmt -> GenState (MSStatement r))
-> [FuncStmt] -> StateT DrasilState Identity [MSStatement r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FuncStmt -> GenState (MSStatement r)
forall (r :: * -> *).
OOProg r =>
FuncStmt -> GenState (MSStatement r)
convStmt [FuncStmt]
tSt
VS (r (Value r))
e' <- CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
e
MSStatement r -> GenState (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (MSStatement r -> GenState (MSStatement r))
-> MSStatement r -> GenState (MSStatement r)
forall a b. (a -> b) -> a -> b
$ [(VS (r (Value r)), MSBody r)] -> MSStatement r
forall (r :: * -> *).
ControlStatement r =>
[(SValue r, MSBody r)] -> MSStatement r
ifNoElse [(VS (r (Value r))
e', [MSStatement r] -> MSBody r
forall (r :: * -> *). BodySym r => [MSStatement r] -> MSBody r
bodyStatements [MSStatement r]
stmts)]
convStmt (FCond CodeExpr
e [FuncStmt]
tSt [FuncStmt]
eSt) = do
[MSStatement r]
stmt1 <- (FuncStmt -> GenState (MSStatement r))
-> [FuncStmt] -> StateT DrasilState Identity [MSStatement r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FuncStmt -> GenState (MSStatement r)
forall (r :: * -> *).
OOProg r =>
FuncStmt -> GenState (MSStatement r)
convStmt [FuncStmt]
tSt
[MSStatement r]
stmt2 <- (FuncStmt -> GenState (MSStatement r))
-> [FuncStmt] -> StateT DrasilState Identity [MSStatement r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FuncStmt -> GenState (MSStatement r)
forall (r :: * -> *).
OOProg r =>
FuncStmt -> GenState (MSStatement r)
convStmt [FuncStmt]
eSt
VS (r (Value r))
e' <- CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
e
MSStatement r -> GenState (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (MSStatement r -> GenState (MSStatement r))
-> MSStatement r -> GenState (MSStatement r)
forall a b. (a -> b) -> a -> b
$ [(VS (r (Value r)), MSBody r)] -> MSBody r -> MSStatement r
forall (r :: * -> *).
ControlStatement r =>
[(SValue r, MSBody r)] -> MSBody r -> MSStatement r
ifCond [(VS (r (Value r))
e', [MSStatement r] -> MSBody r
forall (r :: * -> *). BodySym r => [MSStatement r] -> MSBody r
bodyStatements [MSStatement r]
stmt1)] ([MSStatement r] -> MSBody r
forall (r :: * -> *). BodySym r => [MSStatement r] -> MSBody r
bodyStatements [MSStatement r]
stmt2)
convStmt (FRet CodeExpr
e) = do
VS (r (Value r))
e' <- CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
e
MSStatement r -> GenState (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (MSStatement r -> GenState (MSStatement r))
-> MSStatement r -> GenState (MSStatement r)
forall a b. (a -> b) -> a -> b
$ VS (r (Value r)) -> MSStatement r
forall (r :: * -> *).
ControlStatement r =>
SValue r -> MSStatement r
returnStmt VS (r (Value r))
e'
convStmt (FThrow Name
s) = MSStatement r -> GenState (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (MSStatement r -> GenState (MSStatement r))
-> MSStatement r -> GenState (MSStatement r)
forall a b. (a -> b) -> a -> b
$ Name -> MSStatement r
forall (r :: * -> *). ControlStatement r => Name -> MSStatement r
throw Name
s
convStmt (FTry [FuncStmt]
t [FuncStmt]
c) = do
[MSStatement r]
stmt1 <- (FuncStmt -> GenState (MSStatement r))
-> [FuncStmt] -> StateT DrasilState Identity [MSStatement r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FuncStmt -> GenState (MSStatement r)
forall (r :: * -> *).
OOProg r =>
FuncStmt -> GenState (MSStatement r)
convStmt [FuncStmt]
t
[MSStatement r]
stmt2 <- (FuncStmt -> GenState (MSStatement r))
-> [FuncStmt] -> StateT DrasilState Identity [MSStatement r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FuncStmt -> GenState (MSStatement r)
forall (r :: * -> *).
OOProg r =>
FuncStmt -> GenState (MSStatement r)
convStmt [FuncStmt]
c
MSStatement r -> GenState (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (MSStatement r -> GenState (MSStatement r))
-> MSStatement r -> GenState (MSStatement r)
forall a b. (a -> b) -> a -> b
$ MSBody r -> MSBody r -> MSStatement r
forall (r :: * -> *).
ControlStatement r =>
MSBody r -> MSBody r -> MSStatement r
tryCatch ([MSStatement r] -> MSBody r
forall (r :: * -> *). BodySym r => [MSStatement r] -> MSBody r
bodyStatements [MSStatement r]
stmt1) ([MSStatement r] -> MSBody r
forall (r :: * -> *). BodySym r => [MSStatement r] -> MSBody r
bodyStatements [MSStatement r]
stmt2)
convStmt FuncStmt
FContinue = MSStatement r -> GenState (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return MSStatement r
forall (r :: * -> *). ControlStatement r => MSStatement r
continue
convStmt (FDecDef Input
v (Matrix [[]])) = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
let scp :: r (Scope r)
scp = ScopeType -> r (Scope r)
forall (r :: * -> *). SharedProg r => ScopeType -> r (Scope r)
convScope (ScopeType -> r (Scope r)) -> ScopeType -> r (Scope r)
forall a b. (a -> b) -> a -> b
$ DrasilState -> ScopeType
currentScope DrasilState
g
StateT ValueState Identity (r (Variable r))
vari <- Input
-> StateT
DrasilState Identity (StateT ValueState Identity (r (Variable r)))
forall (r :: * -> *). OOProg r => Input -> GenState (SVariable r)
mkVar Input
v
let convDec :: CodeType -> r (Scope r) -> MSStatement r
convDec (C.List CodeType
_) = Integer
-> StateT ValueState Identity (r (Variable r))
-> r (Scope r)
-> MSStatement r
forall (r :: * -> *).
DeclStatement r =>
Integer -> SVariable r -> r (Scope r) -> MSStatement r
listDec Integer
0 StateT ValueState Identity (r (Variable r))
vari
convDec (C.Array CodeType
_) = Integer
-> StateT ValueState Identity (r (Variable r))
-> r (Scope r)
-> MSStatement r
forall (r :: * -> *).
DeclStatement r =>
Integer -> SVariable r -> r (Scope r) -> MSStatement r
arrayDec Integer
0 StateT ValueState Identity (r (Variable r))
vari
convDec CodeType
_ = StateT ValueState Identity (r (Variable r))
-> r (Scope r) -> MSStatement r
forall (r :: * -> *).
DeclStatement r =>
SVariable r -> r (Scope r) -> MSStatement r
varDec StateT ValueState Identity (r (Variable r))
vari
(CodeType -> MSStatement r)
-> GenState CodeType -> GenState (MSStatement r)
forall a b.
(a -> b)
-> StateT DrasilState Identity a -> StateT DrasilState Identity b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (CodeType -> r (Scope r) -> MSStatement r
`convDec` r (Scope r)
scp) (Input -> GenState CodeType
forall c. HasSpace c => c -> GenState CodeType
codeType Input
v)
convStmt (FDecDef Input
v CodeExpr
e) = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
let scp :: r (Scope r)
scp = ScopeType -> r (Scope r)
forall (r :: * -> *). SharedProg r => ScopeType -> r (Scope r)
convScope (ScopeType -> r (Scope r)) -> ScopeType -> r (Scope r)
forall a b. (a -> b) -> a -> b
$ DrasilState -> ScopeType
currentScope DrasilState
g
StateT ValueState Identity (r (Variable r))
v' <- Input
-> StateT
DrasilState Identity (StateT ValueState Identity (r (Variable r)))
forall (r :: * -> *). OOProg r => Input -> GenState (SVariable r)
mkVar Input
v
[MSStatement r]
l <- StateT ValueState Identity (r (Variable r))
-> StateT DrasilState Identity [MSStatement r]
forall (r :: * -> *).
SharedProg r =>
SVariable r -> GenState [MSStatement r]
maybeLog StateT ValueState Identity (r (Variable r))
v'
CodeType
t <- Input -> GenState CodeType
forall c. HasSpace c => c -> GenState CodeType
codeType Input
v
let convDecDef :: CodeExpr -> GenState (MSStatement r)
convDecDef (Matrix [[CodeExpr]
lst]) = do
let contDecDef :: CodeType
-> SVariable r -> r (Scope r) -> [SValue r] -> MSStatement r
contDecDef (C.List CodeType
_) = SVariable r -> r (Scope r) -> [SValue r] -> MSStatement r
forall (r :: * -> *).
DeclStatement r =>
SVariable r -> r (Scope r) -> [SValue r] -> MSStatement r
listDecDef
contDecDef (C.Array CodeType
_) = SVariable r -> r (Scope r) -> [SValue r] -> MSStatement r
forall (r :: * -> *).
DeclStatement r =>
SVariable r -> r (Scope r) -> [SValue r] -> MSStatement r
arrayDecDef
contDecDef CodeType
_ = Name -> SVariable r -> r (Scope r) -> [SValue r] -> MSStatement r
forall a. HasCallStack => Name -> a
error Name
"Type mismatch between variable and value in declare-define FuncStmt"
[VS (r (Value r))]
e' <- (CodeExpr -> StateT DrasilState Identity (VS (r (Value r))))
-> [CodeExpr] -> StateT DrasilState Identity [VS (r (Value r))]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr [CodeExpr]
lst
MSStatement r -> GenState (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (MSStatement r -> GenState (MSStatement r))
-> MSStatement r -> GenState (MSStatement r)
forall a b. (a -> b) -> a -> b
$ CodeType
-> StateT ValueState Identity (r (Variable r))
-> r (Scope r)
-> [VS (r (Value r))]
-> MSStatement r
forall {r :: * -> *}.
DeclStatement r =>
CodeType
-> SVariable r -> r (Scope r) -> [SValue r] -> MSStatement r
contDecDef CodeType
t StateT ValueState Identity (r (Variable r))
v' r (Scope r)
scp [VS (r (Value r))]
e'
convDecDef CodeExpr
_ = do
VS (r (Value r))
e' <- CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
e
MSStatement r -> GenState (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (MSStatement r -> GenState (MSStatement r))
-> MSStatement r -> GenState (MSStatement r)
forall a b. (a -> b) -> a -> b
$ StateT ValueState Identity (r (Variable r))
-> r (Scope r) -> VS (r (Value r)) -> MSStatement r
forall (r :: * -> *).
DeclStatement r =>
SVariable r -> r (Scope r) -> SValue r -> MSStatement r
varDecDef StateT ValueState Identity (r (Variable r))
v' r (Scope r)
scp VS (r (Value r))
e'
MSStatement r
dd <- CodeExpr -> GenState (MSStatement r)
convDecDef CodeExpr
e
MSStatement r -> GenState (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (MSStatement r -> GenState (MSStatement r))
-> MSStatement r -> GenState (MSStatement r)
forall a b. (a -> b) -> a -> b
$ [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
$ MSStatement r
dd MSStatement r -> [MSStatement r] -> [MSStatement r]
forall a. a -> [a] -> [a]
: [MSStatement r]
l
convStmt (FFuncDef CodeFuncChunk
f [ParameterChunk]
ps [FuncStmt]
sts) = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
let scp :: r (Scope r)
scp = ScopeType -> r (Scope r)
forall (r :: * -> *). SharedProg r => ScopeType -> r (Scope r)
convScope (ScopeType -> r (Scope r)) -> ScopeType -> r (Scope r)
forall a b. (a -> b) -> a -> b
$ DrasilState -> ScopeType
currentScope DrasilState
g
StateT ValueState Identity (r (Variable r))
f' <- Input
-> StateT
DrasilState Identity (StateT ValueState Identity (r (Variable r)))
forall (r :: * -> *). OOProg r => Input -> GenState (SVariable r)
mkVar (CodeFuncChunk -> Input
forall c. (Quantity c, MayHaveUnit c) => c -> Input
quantvar CodeFuncChunk
f)
[StateT ValueState Identity (r (Variable r))]
pms <- (ParameterChunk
-> StateT
DrasilState Identity (StateT ValueState Identity (r (Variable r))))
-> [ParameterChunk]
-> StateT
DrasilState Identity [StateT ValueState Identity (r (Variable r))]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (Input
-> StateT
DrasilState Identity (StateT ValueState Identity (r (Variable r)))
forall (r :: * -> *). OOProg r => Input -> GenState (SVariable r)
mkVar (Input
-> StateT
DrasilState Identity (StateT ValueState Identity (r (Variable r))))
-> (ParameterChunk -> Input)
-> ParameterChunk
-> StateT
DrasilState Identity (StateT ValueState Identity (r (Variable r)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParameterChunk -> Input
forall c. (Quantity c, MayHaveUnit c) => c -> Input
quantvar) [ParameterChunk]
ps
[MSStatement r]
b <- (FuncStmt -> GenState (MSStatement r))
-> [FuncStmt] -> StateT DrasilState Identity [MSStatement r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FuncStmt -> GenState (MSStatement r)
forall (r :: * -> *).
OOProg r =>
FuncStmt -> GenState (MSStatement r)
convStmt [FuncStmt]
sts
MSStatement r -> GenState (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (MSStatement r -> GenState (MSStatement r))
-> MSStatement r -> GenState (MSStatement r)
forall a b. (a -> b) -> a -> b
$ StateT ValueState Identity (r (Variable r))
-> r (Scope r)
-> [StateT ValueState Identity (r (Variable r))]
-> MSBody r
-> MSStatement r
forall (r :: * -> *).
DeclStatement r =>
SVariable r
-> r (Scope r) -> [SVariable r] -> MSBody r -> MSStatement r
funcDecDef StateT ValueState Identity (r (Variable r))
f' r (Scope r)
scp [StateT ValueState Identity (r (Variable r))]
pms ([MSStatement r] -> MSBody r
forall (r :: * -> *). BodySym r => [MSStatement r] -> MSBody r
bodyStatements [MSStatement r]
b)
convStmt (FVal CodeExpr
e) = do
VS (r (Value r))
e' <- CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
e
MSStatement r -> GenState (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (MSStatement r -> GenState (MSStatement r))
-> MSStatement r -> GenState (MSStatement r)
forall a b. (a -> b) -> a -> b
$ VS (r (Value r)) -> MSStatement r
forall (r :: * -> *). StatementSym r => SValue r -> MSStatement r
valStmt VS (r (Value r))
e'
convStmt (FMulti [FuncStmt]
ss) = do
[MSStatement r]
stmts <- (FuncStmt -> GenState (MSStatement r))
-> [FuncStmt] -> StateT DrasilState Identity [MSStatement r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FuncStmt -> GenState (MSStatement r)
forall (r :: * -> *).
OOProg r =>
FuncStmt -> GenState (MSStatement r)
convStmt [FuncStmt]
ss
MSStatement r -> GenState (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (MSStatement r -> GenState (MSStatement r))
-> MSStatement r -> GenState (MSStatement r)
forall a b. (a -> b) -> a -> b
$ [MSStatement r] -> MSStatement r
forall (r :: * -> *).
StatementSym r =>
[MSStatement r] -> MSStatement r
multi [MSStatement r]
stmts
convStmt (FAppend CodeExpr
a CodeExpr
b) = do
VS (r (Value r))
a' <- CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
a
VS (r (Value r))
b' <- CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
b
MSStatement r -> GenState (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (MSStatement r -> GenState (MSStatement r))
-> MSStatement r -> GenState (MSStatement r)
forall a b. (a -> b) -> a -> b
$ VS (r (Value r)) -> MSStatement r
forall (r :: * -> *). StatementSym r => SValue r -> MSStatement r
valStmt (VS (r (Value r)) -> MSStatement r)
-> VS (r (Value r)) -> MSStatement r
forall a b. (a -> b) -> a -> b
$ VS (r (Value r)) -> VS (r (Value r)) -> VS (r (Value r))
forall (r :: * -> *). List r => SValue r -> SValue r -> SValue r
listAppend VS (r (Value r))
a' VS (r (Value r))
b'
genDataFunc :: (OOProg r) => Name -> Description -> DataDesc ->
GenState (SMethod r)
genDataFunc :: forall (r :: * -> *).
OOProg r =>
Name -> Name -> DataDesc -> GenState (SMethod r)
genDataFunc Name
nameTitle Name
desc DataDesc
ddef = do
let parms :: [Input]
parms = DataDesc -> [Input]
getInputs DataDesc
ddef
[MS (r (Block r))]
bod <- DataDesc -> StateT DrasilState Identity [MS (r (Block r))]
forall (r :: * -> *). OOProg r => DataDesc -> GenState [MSBlock r]
readData DataDesc
ddef
Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MS (r (Block r))]
-> GenState (SMethod r)
forall (r :: * -> *).
OOProg r =>
Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
publicFunc Name
nameTitle VSType r
forall (r :: * -> *). TypeSym r => VSType r
void Name
desc ((Input -> ParameterChunk) -> [Input] -> [ParameterChunk]
forall a b. (a -> b) -> [a] -> [b]
map Input -> ParameterChunk
forall c. CodeIdea c => c -> ParameterChunk
pcAuto ([Input] -> [ParameterChunk]) -> [Input] -> [ParameterChunk]
forall a b. (a -> b) -> a -> b
$ QuantityDict -> Input
forall c. (Quantity c, MayHaveUnit c) => c -> Input
quantvar QuantityDict
inFileName Input -> [Input] -> [Input]
forall a. a -> [a] -> [a]
: [Input]
parms)
Maybe Name
forall a. Maybe a
Nothing [MS (r (Block r))]
bod
readData :: (OOProg r) => DataDesc -> GenState [MSBlock r]
readData :: forall (r :: * -> *). OOProg r => DataDesc -> GenState [MSBlock r]
readData DataDesc
ddef = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
let localScope :: r (Scope r)
localScope = ScopeType -> r (Scope r)
forall (r :: * -> *). SharedProg r => ScopeType -> r (Scope r)
convScope (ScopeType -> r (Scope r)) -> ScopeType -> r (Scope r)
forall a b. (a -> b) -> a -> b
$ DrasilState -> ScopeType
currentScope DrasilState
g
[[MS (r (Statement r))]]
inD <- (Data -> StateT DrasilState Identity [MS (r (Statement r))])
-> DataDesc -> StateT DrasilState Identity [[MS (r (Statement r))]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (Data
-> r (Scope r)
-> StateT DrasilState Identity [MS (r (Statement r))]
forall (r :: * -> *).
OOProg r =>
Data -> r (Scope r) -> GenState [MSStatement r]
`inData` r (Scope r)
localScope) DataDesc
ddef
VS (r (Value r))
v_filename <- Input -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *). OOProg r => Input -> GenState (SValue r)
mkVal (QuantityDict -> Input
forall c. (Quantity c, MayHaveUnit c) => c -> Input
quantvar QuantityDict
inFileName)
[MSBlock r] -> GenState [MSBlock r]
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return [[MS (r (Statement r))] -> MSBlock r
forall (r :: * -> *). BlockSym r => [MSStatement r] -> MSBlock r
block ([MS (r (Statement r))] -> MSBlock r)
-> [MS (r (Statement r))] -> MSBlock r
forall a b. (a -> b) -> a -> b
$
SVariable r -> r (Scope r) -> MS (r (Statement r))
forall (r :: * -> *).
DeclStatement r =>
SVariable r -> r (Scope r) -> MSStatement r
varDec SVariable r
forall (r :: * -> *). SharedProg r => SVariable r
var_infile r (Scope r)
localScope MS (r (Statement r))
-> [MS (r (Statement r))] -> [MS (r (Statement r))]
forall a. a -> [a] -> [a]
:
(if (Data -> Bool) -> DataDesc -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (\Data
d -> Data -> Bool
isLine Data
d Bool -> Bool -> Bool
|| Data -> Bool
isLines Data
d) DataDesc
ddef then [SVariable r -> r (Scope r) -> MS (r (Statement r))
forall (r :: * -> *).
DeclStatement r =>
SVariable r -> r (Scope r) -> MSStatement r
varDec SVariable r
forall (r :: * -> *). SharedProg r => SVariable r
var_line r (Scope r)
localScope,
Integer -> SVariable r -> r (Scope r) -> MS (r (Statement r))
forall (r :: * -> *).
DeclStatement r =>
Integer -> SVariable r -> r (Scope r) -> MSStatement r
listDec Integer
0 SVariable r
forall (r :: * -> *). SharedProg r => SVariable r
var_linetokens r (Scope r)
localScope ] else []) [MS (r (Statement r))]
-> [MS (r (Statement r))] -> [MS (r (Statement r))]
forall a. [a] -> [a] -> [a]
++
[Integer -> SVariable r -> r (Scope r) -> MS (r (Statement r))
forall (r :: * -> *).
DeclStatement r =>
Integer -> SVariable r -> r (Scope r) -> MSStatement r
listDec Integer
0 SVariable r
forall (r :: * -> *). SharedProg r => SVariable r
var_lines r (Scope r)
localScope | (Data -> Bool) -> DataDesc -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Data -> Bool
isLines DataDesc
ddef] [MS (r (Statement r))]
-> [MS (r (Statement r))] -> [MS (r (Statement r))]
forall a. [a] -> [a] -> [a]
++ SVariable r -> VS (r (Value r)) -> MS (r (Statement r))
forall (r :: * -> *).
IOStatement r =>
SVariable r -> SValue r -> MSStatement r
openFileR SVariable r
forall (r :: * -> *). SharedProg r => SVariable r
var_infile
VS (r (Value r))
v_filename MS (r (Statement r))
-> [MS (r (Statement r))] -> [MS (r (Statement r))]
forall a. a -> [a] -> [a]
: [[MS (r (Statement r))]] -> [MS (r (Statement r))]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[MS (r (Statement r))]]
inD [MS (r (Statement r))]
-> [MS (r (Statement r))] -> [MS (r (Statement r))]
forall a. [a] -> [a] -> [a]
++ [VS (r (Value r)) -> MS (r (Statement r))
forall (r :: * -> *). IOStatement r => SValue r -> MSStatement r
closeFile VS (r (Value r))
forall (r :: * -> *). SharedProg r => SValue r
v_infile]]
where inData :: (OOProg r) => Data -> r (Scope r) -> GenState [MSStatement r]
inData :: forall (r :: * -> *).
OOProg r =>
Data -> r (Scope r) -> GenState [MSStatement r]
inData (Singleton Input
v) r (Scope r)
_ = do
VS (r (Variable r))
vv <- Input -> StateT DrasilState Identity (VS (r (Variable r)))
forall (r :: * -> *). OOProg r => Input -> GenState (SVariable r)
mkVar Input
v
[MSStatement r]
l <- VS (r (Variable r)) -> GenState [MSStatement r]
forall (r :: * -> *).
SharedProg r =>
SVariable r -> GenState [MSStatement r]
maybeLog VS (r (Variable r))
vv
[MSStatement r] -> GenState [MSStatement r]
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return [[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
$ SValue r -> VS (r (Variable r)) -> MSStatement r
forall (r :: * -> *).
IOStatement r =>
SValue r -> SVariable r -> MSStatement r
getFileInput SValue r
forall (r :: * -> *). SharedProg r => SValue r
v_infile VS (r (Variable r))
vv MSStatement r -> [MSStatement r] -> [MSStatement r]
forall a. a -> [a] -> [a]
: [MSStatement r]
l]
inData Data
JunkData r (Scope r)
_ = [MSStatement r] -> GenState [MSStatement r]
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return [SValue r -> MSStatement r
forall (r :: * -> *). IOStatement r => SValue r -> MSStatement r
discardFileLine SValue r
forall (r :: * -> *). SharedProg r => SValue r
v_infile]
inData (Line LinePattern
lp Char
d) r (Scope r)
scp = do
[MSStatement r]
lnI <- Maybe Name
-> LinePattern -> r (Scope r) -> GenState [MSStatement r]
forall (r :: * -> *).
OOProg r =>
Maybe Name
-> LinePattern -> r (Scope r) -> GenState [MSStatement r]
lineData Maybe Name
forall a. Maybe a
Nothing LinePattern
lp r (Scope r)
scp
[MSStatement r]
logs <- LinePattern -> GenState [MSStatement r]
forall (r :: * -> *).
OOProg r =>
LinePattern -> GenState [MSStatement r]
getEntryVarLogs LinePattern
lp
[MSStatement r] -> GenState [MSStatement r]
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return ([MSStatement r] -> GenState [MSStatement r])
-> [MSStatement r] -> GenState [MSStatement r]
forall a b. (a -> b) -> a -> b
$ [SValue r -> VS (r (Variable r)) -> MSStatement r
forall (r :: * -> *).
IOStatement r =>
SValue r -> SVariable r -> MSStatement r
getFileInputLine SValue r
forall (r :: * -> *). SharedProg r => SValue r
v_infile VS (r (Variable r))
forall (r :: * -> *). SharedProg r => SVariable r
var_line,
Char -> VS (r (Variable r)) -> SValue r -> MSStatement r
forall (r :: * -> *).
StringStatement r =>
Char -> SVariable r -> SValue r -> MSStatement r
stringSplit Char
d VS (r (Variable r))
forall (r :: * -> *). SharedProg r => SVariable r
var_linetokens SValue r
forall (r :: * -> *). SharedProg r => SValue r
v_line] [MSStatement r] -> [MSStatement r] -> [MSStatement r]
forall a. [a] -> [a] -> [a]
++ [MSStatement r]
lnI [MSStatement r] -> [MSStatement r] -> [MSStatement r]
forall a. [a] -> [a] -> [a]
++ [MSStatement r]
logs
inData (Lines LinePattern
lp Maybe Integer
ls Char
d) r (Scope r)
scp = do
[MSStatement r]
lnV <- Maybe Name
-> LinePattern -> r (Scope r) -> GenState [MSStatement r]
forall (r :: * -> *).
OOProg r =>
Maybe Name
-> LinePattern -> r (Scope r) -> GenState [MSStatement r]
lineData (Name -> Maybe Name
forall a. a -> Maybe a
Just Name
"_temp") LinePattern
lp r (Scope r)
scp
[MSStatement r]
logs <- LinePattern -> GenState [MSStatement r]
forall (r :: * -> *).
OOProg r =>
LinePattern -> GenState [MSStatement r]
getEntryVarLogs LinePattern
lp
let readLines :: Maybe Integer -> [MSStatement r]
readLines Maybe Integer
Nothing = [SValue r -> VS (r (Variable r)) -> MSStatement r
forall (r :: * -> *).
IOStatement r =>
SValue r -> SVariable r -> MSStatement r
getFileInputAll SValue r
forall (r :: * -> *). SharedProg r => SValue r
v_infile VS (r (Variable r))
forall (r :: * -> *). SharedProg r => SVariable r
var_lines,
VS (r (Variable 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
forRange VS (r (Variable r))
forall (r :: * -> *). SharedProg r => SVariable r
var_i (Integer -> SValue r
forall (r :: * -> *). Literal r => Integer -> SValue r
litInt Integer
0) (SValue r -> SValue r
forall (r :: * -> *). List r => SValue r -> SValue r
listSize SValue r
forall (r :: * -> *). SharedProg r => SValue r
v_lines) (Integer -> SValue r
forall (r :: * -> *). Literal r => Integer -> SValue r
litInt Integer
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
$ Char -> VS (r (Variable r)) -> SValue r -> MSStatement r
forall (r :: * -> *).
StringStatement r =>
Char -> SVariable r -> SValue r -> MSStatement r
stringSplit Char
d VS (r (Variable r))
forall (r :: * -> *). SharedProg r => SVariable r
var_linetokens (
SValue r -> SValue r -> SValue r
forall (r :: * -> *). List r => SValue r -> SValue r -> SValue r
listAccess SValue r
forall (r :: * -> *). SharedProg r => SValue r
v_lines SValue r
forall (r :: * -> *). SharedProg r => SValue r
v_i) MSStatement r -> [MSStatement r] -> [MSStatement r]
forall a. a -> [a] -> [a]
: [MSStatement r]
lnV)]
readLines (Just Integer
numLines) = [VS (r (Variable 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
forRange VS (r (Variable r))
forall (r :: * -> *). SharedProg r => SVariable r
var_i (Integer -> SValue r
forall (r :: * -> *). Literal r => Integer -> SValue r
litInt Integer
0)
(Integer -> SValue r
forall (r :: * -> *). Literal r => Integer -> SValue r
litInt Integer
numLines) (Integer -> SValue r
forall (r :: * -> *). Literal r => Integer -> SValue r
litInt Integer
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 -> VS (r (Variable r)) -> MSStatement r
forall (r :: * -> *).
IOStatement r =>
SValue r -> SVariable r -> MSStatement r
getFileInputLine SValue r
forall (r :: * -> *). SharedProg r => SValue r
v_infile VS (r (Variable r))
forall (r :: * -> *). SharedProg r => SVariable r
var_line,
Char -> VS (r (Variable r)) -> SValue r -> MSStatement r
forall (r :: * -> *).
StringStatement r =>
Char -> SVariable r -> SValue r -> MSStatement r
stringSplit Char
d VS (r (Variable r))
forall (r :: * -> *). SharedProg r => SVariable r
var_linetokens SValue r
forall (r :: * -> *). SharedProg r => SValue r
v_line
] [MSStatement r] -> [MSStatement r] -> [MSStatement r]
forall a. [a] -> [a] -> [a]
++ [MSStatement r]
lnV)]
[MSStatement r] -> GenState [MSStatement r]
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return ([MSStatement r] -> GenState [MSStatement r])
-> [MSStatement r] -> GenState [MSStatement r]
forall a b. (a -> b) -> a -> b
$ Maybe Integer -> [MSStatement r]
readLines Maybe Integer
ls [MSStatement r] -> [MSStatement r] -> [MSStatement r]
forall a. [a] -> [a] -> [a]
++ [MSStatement r]
logs
lineData :: (OOProg r) => Maybe String -> LinePattern -> r (Scope r) ->
GenState [MSStatement r]
lineData :: forall (r :: * -> *).
OOProg r =>
Maybe Name
-> LinePattern -> r (Scope r) -> GenState [MSStatement r]
lineData Maybe Name
s p :: LinePattern
p@(Straight [Input]
_) r (Scope r)
_ = do
[VS (r (Variable r))]
vs <- Maybe Name
-> LinePattern -> StateT DrasilState Identity [VS (r (Variable r))]
forall (r :: * -> *).
OOProg r =>
Maybe Name -> LinePattern -> GenState [SVariable r]
getEntryVars Maybe Name
s LinePattern
p
[MSStatement r] -> GenState [MSStatement r]
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return [[VS (r (Variable r))] -> SValue r -> MSStatement r
forall (r :: * -> *).
StringStatement r =>
[SVariable r] -> SValue r -> MSStatement r
stringListVals [VS (r (Variable r))]
vs SValue r
forall (r :: * -> *). SharedProg r => SValue r
v_linetokens]
lineData Maybe Name
s p :: LinePattern
p@(Repeat [Input]
ds) r (Scope r)
scp = do
[VS (r (Variable r))]
vs <- Maybe Name
-> LinePattern -> StateT DrasilState Identity [VS (r (Variable r))]
forall (r :: * -> *).
OOProg r =>
Maybe Name -> LinePattern -> GenState [SVariable r]
getEntryVars Maybe Name
s LinePattern
p
[StateT DrasilState Identity (MSStatement r)]
-> GenState [MSStatement r]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
forall (m :: * -> *) a. Monad m => [m a] -> m [a]
sequence ([StateT DrasilState Identity (MSStatement r)]
-> GenState [MSStatement r])
-> [StateT DrasilState Identity (MSStatement r)]
-> GenState [MSStatement r]
forall a b. (a -> b) -> a -> b
$ Maybe Name
-> [Input]
-> r (Scope r)
-> [StateT DrasilState Identity (MSStatement r)]
forall (r :: * -> *).
OOProg r =>
Maybe Name -> [Input] -> r (Scope r) -> [GenState (MSStatement r)]
clearTemps Maybe Name
s [Input]
ds r (Scope r)
scp [StateT DrasilState Identity (MSStatement r)]
-> [StateT DrasilState Identity (MSStatement r)]
-> [StateT DrasilState Identity (MSStatement r)]
forall a. [a] -> [a] -> [a]
++ MSStatement r -> StateT DrasilState Identity (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return
([VS (r (Variable r))] -> SValue r -> MSStatement r
forall (r :: * -> *).
StringStatement r =>
[SVariable r] -> SValue r -> MSStatement r
stringListLists [VS (r (Variable r))]
vs SValue r
forall (r :: * -> *). SharedProg r => SValue r
v_linetokens) StateT DrasilState Identity (MSStatement r)
-> [StateT DrasilState Identity (MSStatement r)]
-> [StateT DrasilState Identity (MSStatement r)]
forall a. a -> [a] -> [a]
: Maybe Name
-> [Input] -> [StateT DrasilState Identity (MSStatement r)]
forall (r :: * -> *).
OOProg r =>
Maybe Name -> [Input] -> [GenState (MSStatement r)]
appendTemps Maybe Name
s [Input]
ds
clearTemps :: (OOProg r) => Maybe String -> [DataItem] -> r (Scope r) ->
[GenState (MSStatement r)]
clearTemps :: forall (r :: * -> *).
OOProg r =>
Maybe Name -> [Input] -> r (Scope r) -> [GenState (MSStatement r)]
clearTemps Maybe Name
Nothing [Input]
_ r (Scope r)
_ = []
clearTemps (Just Name
sfx) [Input]
es r (Scope r)
scp = (Input -> GenState (MS (r (Statement r))))
-> [Input] -> [GenState (MS (r (Statement r)))]
forall a b. (a -> b) -> [a] -> [b]
map (\Input
v -> Name -> Input -> r (Scope r) -> GenState (MS (r (Statement r)))
forall (r :: * -> *).
OOProg r =>
Name -> Input -> r (Scope r) -> GenState (MSStatement r)
clearTemp Name
sfx Input
v r (Scope r)
scp) [Input]
es
clearTemp :: (OOProg r) => String -> DataItem -> r (Scope r) ->
GenState (MSStatement r)
clearTemp :: forall (r :: * -> *).
OOProg r =>
Name -> Input -> r (Scope r) -> GenState (MSStatement r)
clearTemp Name
sfx Input
v r (Scope r)
scp = (CodeType -> MS (r (Statement r)))
-> GenState CodeType
-> StateT DrasilState Identity (MS (r (Statement r)))
forall a b.
(a -> b)
-> StateT DrasilState Identity a -> StateT DrasilState Identity b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\CodeType
t -> SVariable r -> r (Scope r) -> [SValue r] -> MS (r (Statement r))
forall (r :: * -> *).
DeclStatement r =>
SVariable r -> r (Scope r) -> [SValue r] -> MSStatement r
listDecDef (Name -> VSType r -> SVariable r
forall (r :: * -> *).
VariableSym r =>
Name -> VSType r -> SVariable r
var (Input -> Name
forall c. CodeIdea c => c -> Name
codeName Input
v Name -> Name -> Name
forall a. [a] -> [a] -> [a]
++ Name
sfx)
(VSType r -> VSType r
forall (r :: * -> *). TypeSym r => VSType r -> VSType r
listInnerType (VSType r -> VSType r) -> VSType r -> VSType r
forall a b. (a -> b) -> a -> b
$ CodeType -> VSType r
forall (r :: * -> *). OOTypeSym r => CodeType -> VSType r
convTypeOO CodeType
t)) r (Scope r)
scp []) (Input -> GenState CodeType
forall c. HasSpace c => c -> GenState CodeType
codeType Input
v)
appendTemps :: (OOProg r) => Maybe String -> [DataItem]
-> [GenState (MSStatement r)]
appendTemps :: forall (r :: * -> *).
OOProg r =>
Maybe Name -> [Input] -> [GenState (MSStatement r)]
appendTemps Maybe Name
Nothing [Input]
_ = []
appendTemps (Just Name
sfx) [Input]
es = (Input -> GenState (MS (r (Statement r))))
-> [Input] -> [GenState (MS (r (Statement r)))]
forall a b. (a -> b) -> [a] -> [b]
map (Name -> Input -> GenState (MS (r (Statement r)))
forall (r :: * -> *).
OOProg r =>
Name -> Input -> GenState (MSStatement r)
appendTemp Name
sfx) [Input]
es
appendTemp :: (OOProg r) => String -> DataItem ->
GenState (MSStatement r)
appendTemp :: forall (r :: * -> *).
OOProg r =>
Name -> Input -> GenState (MSStatement r)
appendTemp Name
sfx Input
v = (CodeType -> MS (r (Statement r)))
-> GenState CodeType
-> StateT DrasilState Identity (MS (r (Statement r)))
forall a b.
(a -> b)
-> StateT DrasilState Identity a -> StateT DrasilState Identity b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\CodeType
t -> SValue r -> MS (r (Statement r))
forall (r :: * -> *). StatementSym r => SValue r -> MSStatement r
valStmt (SValue r -> MS (r (Statement r)))
-> SValue r -> MS (r (Statement r))
forall a b. (a -> b) -> a -> b
$ SValue r -> SValue r -> SValue r
forall (r :: * -> *). List r => SValue r -> SValue r -> SValue r
listAppend
(SVariable r -> SValue r
forall (r :: * -> *). VariableValue r => SVariable r -> SValue r
valueOf (SVariable r -> SValue r) -> SVariable r -> SValue r
forall a b. (a -> b) -> a -> b
$ Name -> VSType r -> SVariable r
forall (r :: * -> *).
VariableSym r =>
Name -> VSType r -> SVariable r
var (Input -> Name
forall c. CodeIdea c => c -> Name
codeName Input
v) (CodeType -> VSType r
forall (r :: * -> *). OOTypeSym r => CodeType -> VSType r
convTypeOO CodeType
t))
(SVariable r -> SValue r
forall (r :: * -> *). VariableValue r => SVariable r -> SValue r
valueOf (SVariable r -> SValue r) -> SVariable r -> SValue r
forall a b. (a -> b) -> a -> b
$ Name -> VSType r -> SVariable r
forall (r :: * -> *).
VariableSym r =>
Name -> VSType r -> SVariable r
var (Input -> Name
forall c. CodeIdea c => c -> Name
codeName Input
v Name -> Name -> Name
forall a. [a] -> [a] -> [a]
++ Name
sfx) (CodeType -> VSType r
forall (r :: * -> *). OOTypeSym r => CodeType -> VSType r
convTypeOO CodeType
t))) (Input -> GenState CodeType
forall c. HasSpace c => c -> GenState CodeType
codeType Input
v)
getEntryVars :: (OOProg r) => Maybe String -> LinePattern ->
GenState [SVariable r]
getEntryVars :: forall (r :: * -> *).
OOProg r =>
Maybe Name -> LinePattern -> GenState [SVariable r]
getEntryVars Maybe Name
s LinePattern
lp = (Input -> StateT DrasilState Identity (VS (r (Variable r))))
-> [Input] -> StateT DrasilState Identity [VS (r (Variable r))]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((Input -> StateT DrasilState Identity (VS (r (Variable r))))
-> (Name
-> Input -> StateT DrasilState Identity (VS (r (Variable r))))
-> Maybe Name
-> Input
-> StateT DrasilState Identity (VS (r (Variable r)))
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Input -> StateT DrasilState Identity (VS (r (Variable r)))
forall (r :: * -> *). OOProg r => Input -> GenState (SVariable r)
mkVar (\Name
st Input
v -> Input -> GenState CodeType
forall c. HasSpace c => c -> GenState CodeType
codeType Input
v GenState CodeType
-> (CodeType -> StateT DrasilState Identity (VS (r (Variable r))))
-> StateT DrasilState Identity (VS (r (Variable r)))
forall a b.
StateT DrasilState Identity a
-> (a -> StateT DrasilState Identity b)
-> StateT DrasilState Identity b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
(Name
-> VS (r (Type r))
-> StateT DrasilState Identity (VS (r (Variable r)))
forall (r :: * -> *).
OOProg r =>
Name -> VSType r -> GenState (SVariable r)
variable (Input -> Name
forall c. CodeIdea c => c -> Name
codeName Input
v Name -> Name -> Name
forall a. [a] -> [a] -> [a]
++ Name
st) (VS (r (Type r))
-> StateT DrasilState Identity (VS (r (Variable r))))
-> (CodeType -> VS (r (Type r)))
-> CodeType
-> StateT DrasilState Identity (VS (r (Variable r)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VS (r (Type r)) -> VS (r (Type r))
forall (r :: * -> *). TypeSym r => VSType r -> VSType r
listInnerType (VS (r (Type r)) -> VS (r (Type r)))
-> (CodeType -> VS (r (Type r))) -> CodeType -> VS (r (Type r))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CodeType -> VS (r (Type r))
forall (r :: * -> *). OOTypeSym r => CodeType -> VSType r
convTypeOO))
Maybe Name
s) (LinePattern -> [Input]
getPatternInputs LinePattern
lp)
getEntryVarLogs :: (OOProg r) => LinePattern -> GenState [MSStatement r]
getEntryVarLogs :: forall (r :: * -> *).
OOProg r =>
LinePattern -> GenState [MSStatement r]
getEntryVarLogs LinePattern
lp = do
[VS (r (Variable r))]
vs <- Maybe Name
-> LinePattern -> StateT DrasilState Identity [VS (r (Variable r))]
forall (r :: * -> *).
OOProg r =>
Maybe Name -> LinePattern -> GenState [SVariable r]
getEntryVars Maybe Name
forall a. Maybe a
Nothing LinePattern
lp
[[MSStatement r]]
logs <- (VS (r (Variable r)) -> GenState [MSStatement r])
-> [VS (r (Variable r))]
-> StateT DrasilState Identity [[MSStatement r]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM VS (r (Variable r)) -> GenState [MSStatement r]
forall (r :: * -> *).
SharedProg r =>
SVariable r -> GenState [MSStatement r]
maybeLog [VS (r (Variable r))]
vs
[MSStatement r] -> GenState [MSStatement r]
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return ([MSStatement r] -> GenState [MSStatement r])
-> [MSStatement r] -> GenState [MSStatement r]
forall a b. (a -> b) -> a -> b
$ [[MSStatement r]] -> [MSStatement r]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[MSStatement r]]
logs
valueProc :: (SharedProg r) => UID -> Name -> VSType r -> GenState (SValue r)
valueProc :: forall (r :: * -> *).
SharedProg r =>
UID -> Name -> VSType r -> GenState (SValue r)
valueProc UID
u Name
s VSType r
t = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
let cs :: CodeSpec
cs = DrasilState -> CodeSpec
codeSpec DrasilState
g
mm :: ConstantMap
mm = CodeSpec
cs CodeSpec -> Getting ConstantMap CodeSpec ConstantMap -> ConstantMap
forall s a. s -> Getting a s a -> a
^. Getting ConstantMap CodeSpec ConstantMap
forall c. HasOldCodeSpec c => Lens' c ConstantMap
Lens' CodeSpec ConstantMap
constMapO
constDef :: Maybe CodeDefinition
constDef = do
CodeDefinition
cd <- UID -> ConstantMap -> Maybe CodeDefinition
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup UID
u ConstantMap
mm
ConstantStructure -> CodeDefinition -> Maybe CodeDefinition
forall {a}. ConstantStructure -> a -> Maybe a
maybeInline (DrasilState -> ConstantStructure
conStruct DrasilState
g) CodeDefinition
cd
maybeInline :: ConstantStructure -> a -> Maybe a
maybeInline ConstantStructure
Inline a
m = a -> Maybe a
forall a. a -> Maybe a
Just a
m
maybeInline ConstantStructure
_ a
_ = Maybe a
forall a. Maybe a
Nothing
cm :: MatchedConceptMap
cm = DrasilState -> MatchedConceptMap
concMatches DrasilState
g
cdCncpt :: Maybe CodeConcept
cdCncpt = UID -> MatchedConceptMap -> Maybe CodeConcept
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup UID
u MatchedConceptMap
cm
SValue r
val <- GenState (SValue r)
-> (CodeDefinition -> GenState (SValue r))
-> Maybe CodeDefinition
-> GenState (SValue r)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (SVariable r -> SValue r
forall (r :: * -> *). VariableValue r => SVariable r -> SValue r
valueOf (SVariable r -> SValue r)
-> StateT DrasilState Identity (SVariable r) -> GenState (SValue r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name -> VSType r -> StateT DrasilState Identity (SVariable r)
forall (r :: * -> *).
SharedProg r =>
Name -> VSType r -> GenState (SVariable r)
variableProc Name
s VSType r
t)
(CodeExpr -> GenState (SValue r)
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc (CodeExpr -> GenState (SValue r))
-> (CodeDefinition -> CodeExpr)
-> CodeDefinition
-> GenState (SValue r)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CodeDefinition
-> Getting CodeExpr CodeDefinition CodeExpr -> CodeExpr
forall s a. s -> Getting a s a -> a
^. Getting CodeExpr CodeDefinition CodeExpr
forall c. DefiningCodeExpr c => Lens' c CodeExpr
Lens' CodeDefinition CodeExpr
codeExpr)) Maybe CodeDefinition
constDef
SValue r -> GenState (SValue r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (SValue r -> GenState (SValue r))
-> SValue r -> GenState (SValue r)
forall a b. (a -> b) -> a -> b
$ SValue r
-> (CodeConcept -> SValue r) -> Maybe CodeConcept -> SValue r
forall b a. b -> (a -> b) -> Maybe a -> b
maybe SValue r
val CodeConcept -> SValue r
forall (r :: * -> *). SharedProg r => CodeConcept -> SValue r
conceptToGOOL Maybe CodeConcept
cdCncpt
variableProc :: (SharedProg r) => Name -> VSType r -> GenState (SVariable r)
variableProc :: forall (r :: * -> *).
SharedProg r =>
Name -> VSType r -> GenState (SVariable r)
variableProc Name
s VSType r
t = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
let cs :: CodeSpec
cs = DrasilState -> CodeSpec
codeSpec DrasilState
g
defFunc :: ConstantRepr -> Name -> VSType r -> SVariable r
defFunc ConstantRepr
Var = Name -> VSType r -> SVariable r
forall (r :: * -> *).
VariableSym r =>
Name -> VSType r -> SVariable r
var
defFunc ConstantRepr
Const = Name -> VSType r -> SVariable r
forall (r :: * -> *).
VariableSym r =>
Name -> VSType r -> SVariable r
constant
if Name
s Name -> [Name] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (Input -> Name) -> [Input] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map Input -> Name
forall c. CodeIdea c => c -> Name
codeName (CodeSpec
cs CodeSpec -> Getting [Input] CodeSpec [Input] -> [Input]
forall s a. s -> Getting a s a -> a
^. Getting [Input] CodeSpec [Input]
forall c. HasOldCodeSpec c => Lens' c [Input]
Lens' CodeSpec [Input]
inputsO)
then Structure -> ConstantRepr -> SVariable r -> GenState (SVariable r)
forall (r :: * -> *).
SharedProg r =>
Structure -> ConstantRepr -> SVariable r -> GenState (SVariable r)
inputVariableProc (DrasilState -> Structure
inStruct DrasilState
g) ConstantRepr
Var (Name -> VSType r -> SVariable r
forall (r :: * -> *).
VariableSym r =>
Name -> VSType r -> SVariable r
var Name
s VSType r
t)
else if Name
s Name -> [Name] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (CodeDefinition -> Name) -> [CodeDefinition] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map CodeDefinition -> Name
forall c. CodeIdea c => c -> Name
codeName (CodeSpec
cs CodeSpec
-> Getting [CodeDefinition] CodeSpec [CodeDefinition]
-> [CodeDefinition]
forall s a. s -> Getting a s a -> a
^. Getting [CodeDefinition] CodeSpec [CodeDefinition]
forall c. HasOldCodeSpec c => Lens' c [CodeDefinition]
Lens' CodeSpec [CodeDefinition]
constantsO)
then ConstantStructure
-> ConstantRepr -> SVariable r -> GenState (SVariable r)
forall (r :: * -> *).
SharedProg r =>
ConstantStructure
-> ConstantRepr -> SVariable r -> GenState (SVariable r)
constVariableProc (DrasilState -> ConstantStructure
conStruct DrasilState
g) (DrasilState -> ConstantRepr
conRepr DrasilState
g)
((ConstantRepr -> Name -> VSType r -> SVariable r
forall {r :: * -> *}.
VariableSym r =>
ConstantRepr -> Name -> VSType r -> SVariable r
defFunc (ConstantRepr -> Name -> VSType r -> SVariable r)
-> ConstantRepr -> Name -> VSType r -> SVariable r
forall a b. (a -> b) -> a -> b
$ DrasilState -> ConstantRepr
conRepr DrasilState
g) Name
s VSType r
t)
else SVariable r -> GenState (SVariable r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVariable r -> GenState (SVariable r))
-> SVariable r -> GenState (SVariable r)
forall a b. (a -> b) -> a -> b
$ Name -> VSType r -> SVariable r
forall (r :: * -> *).
VariableSym r =>
Name -> VSType r -> SVariable r
var Name
s VSType r
t
inputVariableProc :: (SharedProg r) => Structure -> ConstantRepr -> SVariable r ->
GenState (SVariable r)
inputVariableProc :: forall (r :: * -> *).
SharedProg r =>
Structure -> ConstantRepr -> SVariable r -> GenState (SVariable r)
inputVariableProc Structure
Unbundled ConstantRepr
_ SVariable r
v = SVariable r -> StateT DrasilState Identity (SVariable r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return SVariable r
v
inputVariableProc Structure
Bundled ConstantRepr
_ SVariable r
_ = Name -> StateT DrasilState Identity (SVariable r)
forall a. HasCallStack => Name -> a
error Name
"inputVariableProc: Procedural renderers do not support bundled inputs"
constVariableProc :: (SharedProg r) => ConstantStructure -> ConstantRepr ->
SVariable r -> GenState (SVariable r)
constVariableProc :: forall (r :: * -> *).
SharedProg r =>
ConstantStructure
-> ConstantRepr -> SVariable r -> GenState (SVariable r)
constVariableProc (Store Structure
Unbundled) ConstantRepr
_ SVariable r
v = SVariable r -> StateT DrasilState Identity (SVariable r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return SVariable r
v
constVariableProc (Store Structure
Bundled) ConstantRepr
_ SVariable r
_ = Name -> StateT DrasilState Identity (SVariable r)
forall a. HasCallStack => Name -> a
error Name
"constVariableProc: Procedural renderers do not support bundled constants"
constVariableProc ConstantStructure
WithInputs ConstantRepr
cr SVariable r
v = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
Structure
-> ConstantRepr
-> SVariable r
-> StateT DrasilState Identity (SVariable r)
forall (r :: * -> *).
SharedProg r =>
Structure -> ConstantRepr -> SVariable r -> GenState (SVariable r)
inputVariableProc (DrasilState -> Structure
inStruct DrasilState
g) ConstantRepr
cr SVariable r
v
constVariableProc ConstantStructure
Inline ConstantRepr
_ SVariable r
_ = Name -> StateT DrasilState Identity (SVariable r)
forall a. HasCallStack => Name -> a
error (Name -> StateT DrasilState Identity (SVariable r))
-> Name -> StateT DrasilState Identity (SVariable r)
forall a b. (a -> b) -> a -> b
$ Name
"mkVar called on a constant, but user " Name -> Name -> Name
forall a. [a] -> [a] -> [a]
++
Name
"chose to Inline constants. Generator has a bug."
mkValProc :: (SharedProg r) => CodeVarChunk -> GenState (SValue r)
mkValProc :: forall (r :: * -> *). SharedProg r => Input -> GenState (SValue r)
mkValProc Input
v = do
CodeType
t <- Input -> GenState CodeType
forall c. HasSpace c => c -> GenState CodeType
codeType Input
v
let toGOOLVal :: Maybe a -> GenState (SValue r)
toGOOLVal Maybe a
Nothing = UID -> Name -> VSType r -> GenState (SValue r)
forall (r :: * -> *).
SharedProg r =>
UID -> Name -> VSType r -> GenState (SValue r)
valueProc (Input
v Input -> Getting UID Input UID -> UID
forall s a. s -> Getting a s a -> a
^. Getting UID Input UID
forall c. HasUID c => Getter c UID
Getter Input UID
uid) (Input -> Name
forall c. CodeIdea c => c -> Name
codeName Input
v) (CodeType -> VSType r
forall (r :: * -> *). TypeSym r => CodeType -> VSType r
convType CodeType
t)
toGOOLVal (Just a
_) = Name -> GenState (SValue r)
forall a. HasCallStack => Name -> a
error Name
"mkValProc: Procedural renderers do not support objects"
Maybe CodeChunk -> GenState (SValue r)
forall {r :: * -> *} {a}.
SharedProg r =>
Maybe a -> GenState (SValue r)
toGOOLVal (Input
v Input
-> Getting (Maybe CodeChunk) Input (Maybe CodeChunk)
-> Maybe CodeChunk
forall s a. s -> Getting a s a -> a
^. Getting (Maybe CodeChunk) Input (Maybe CodeChunk)
Lens' Input (Maybe CodeChunk)
obv)
mkVarProc :: (SharedProg r) => CodeVarChunk -> GenState (SVariable r)
mkVarProc :: forall (r :: * -> *).
SharedProg r =>
Input -> GenState (SVariable r)
mkVarProc Input
v = do
CodeType
t <- Input -> GenState CodeType
forall c. HasSpace c => c -> GenState CodeType
codeType Input
v
let toGOOLVar :: Maybe a -> GenState (SVariable r)
toGOOLVar Maybe a
Nothing = Name -> VSType r -> GenState (SVariable r)
forall (r :: * -> *).
SharedProg r =>
Name -> VSType r -> GenState (SVariable r)
variableProc (Input -> Name
forall c. CodeIdea c => c -> Name
codeName Input
v) (CodeType -> VSType r
forall (r :: * -> *). TypeSym r => CodeType -> VSType r
convType CodeType
t)
toGOOLVar (Just a
_) = Name -> GenState (SVariable r)
forall a. HasCallStack => Name -> a
error Name
"mkVarProc: Procedural renderers do not support objects"
Maybe CodeChunk -> GenState (SVariable r)
forall {r :: * -> *} {a}.
SharedProg r =>
Maybe a -> GenState (SVariable r)
toGOOLVar (Input
v Input
-> Getting (Maybe CodeChunk) Input (Maybe CodeChunk)
-> Maybe CodeChunk
forall s a. s -> Getting a s a -> a
^. Getting (Maybe CodeChunk) Input (Maybe CodeChunk)
Lens' Input (Maybe CodeChunk)
obv)
genModDefProc :: (ProcProg r) => Mod -> GenState (Proc.SFile r)
genModDefProc :: forall (r :: * -> *). ProcProg r => Mod -> GenState (SFile r)
genModDefProc (Mod Name
n Name
desc [Name]
is [Class]
cs [Func]
fs) = case [Class]
cs of
[] -> Name
-> Name
-> [Name]
-> [GenState (Maybe (SMethod r))]
-> GenState (SFile r)
forall (r :: * -> *).
ProcProg r =>
Name
-> Name
-> [Name]
-> [GenState (Maybe (SMethod r))]
-> GenState (SFile r)
genModuleWithImportsProc Name
n Name
desc [Name]
is
((Func -> GenState (Maybe (SMethod r)))
-> [Func] -> [GenState (Maybe (SMethod r))]
forall a b. (a -> b) -> [a] -> [b]
map ((SMethod r -> Maybe (SMethod r))
-> StateT DrasilState Identity (SMethod r)
-> GenState (Maybe (SMethod r))
forall a b.
(a -> b)
-> StateT DrasilState Identity a -> StateT DrasilState Identity b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SMethod r -> Maybe (SMethod r)
forall a. a -> Maybe a
Just (StateT DrasilState Identity (SMethod r)
-> GenState (Maybe (SMethod r)))
-> (Func -> StateT DrasilState Identity (SMethod r))
-> Func
-> GenState (Maybe (SMethod r))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> StateT DrasilState Identity (SMethod r))
-> [StateVariable]
-> Func
-> StateT DrasilState Identity (SMethod r)
forall (r :: * -> *).
SharedProg r =>
(Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r))
-> [StateVariable] -> Func -> GenState (SMethod r)
genFuncProc Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> StateT DrasilState Identity (SMethod r)
forall (r :: * -> *).
SharedProg r =>
Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
publicFuncProc []) [Func]
fs)
[Class]
_ -> Name -> GenState (SFile r)
forall a. HasCallStack => Name -> a
error Name
"genModDefProc: Procedural renderers do not support classes"
mkParamProc :: (SharedProg r) => ParameterChunk -> GenState (MSParameter r)
mkParamProc :: forall (r :: * -> *).
SharedProg r =>
ParameterChunk -> GenState (MSParameter r)
mkParamProc ParameterChunk
p = do
VS (r (Variable r))
v <- Input -> StateT DrasilState Identity (VS (r (Variable r)))
forall (r :: * -> *).
SharedProg r =>
Input -> GenState (SVariable r)
mkVarProc (ParameterChunk -> Input
forall c. (Quantity c, MayHaveUnit c) => c -> Input
quantvar ParameterChunk
p)
MSParameter r -> GenState (MSParameter r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (MSParameter r -> GenState (MSParameter r))
-> MSParameter r -> GenState (MSParameter r)
forall a b. (a -> b) -> a -> b
$ PassBy -> VS (r (Variable r)) -> MSParameter r
forall {r :: * -> *}.
ParameterSym r =>
PassBy -> VS (r (Variable r)) -> MS (r (Parameter r))
paramFunc (ParameterChunk -> PassBy
passBy ParameterChunk
p) VS (r (Variable r))
v
where paramFunc :: PassBy -> SVariable r -> MSParameter r
paramFunc PassBy
Ref = SVariable r -> MSParameter r
forall (r :: * -> *).
ParameterSym r =>
SVariable r -> MSParameter r
pointerParam
paramFunc PassBy
Val = SVariable r -> MSParameter r
forall (r :: * -> *).
ParameterSym r =>
SVariable r -> MSParameter r
param
publicFuncProc :: (SharedProg r) => Label -> VSType r -> Description ->
[ParameterChunk] -> Maybe Description -> [MSBlock r] ->
GenState (SMethod r)
publicFuncProc :: forall (r :: * -> *).
SharedProg r =>
Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
publicFuncProc Name
n VSType r
t Name
desc [ParameterChunk]
ps Maybe Name
r [MSBlock r]
b = do
(DrasilState -> DrasilState) -> StateT DrasilState Identity ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\DrasilState
st -> DrasilState
st {currentScope = Local})
([MSParameter r] -> MSBody r -> SMethod r)
-> Name
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
forall (r :: * -> *).
SharedProg r =>
([MSParameter r] -> MSBody r -> SMethod r)
-> Name
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
genMethodProc (Name
-> r (Visibility r)
-> VSType r
-> [MSParameter r]
-> MSBody r
-> SMethod r
forall (r :: * -> *).
MethodSym r =>
Name
-> r (Visibility r)
-> VSType r
-> [MSParameter r]
-> MSBody r
-> SMethod r
function Name
n r (Visibility r)
forall (r :: * -> *). VisibilitySym r => r (Visibility r)
public VSType r
t) Name
n Name
desc [ParameterChunk]
ps Maybe Name
r [MSBlock r]
b
privateFuncProc :: (SharedProg r) => Label -> VSType r -> Description ->
[ParameterChunk] -> Maybe Description -> [MSBlock r] ->
GenState (SMethod r)
privateFuncProc :: forall (r :: * -> *).
SharedProg r =>
Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
privateFuncProc Name
n VSType r
t Name
desc [ParameterChunk]
ps Maybe Name
r [MSBlock r]
b = do
(DrasilState -> DrasilState) -> StateT DrasilState Identity ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\DrasilState
st -> DrasilState
st {currentScope = Local})
([MSParameter r] -> MSBody r -> SMethod r)
-> Name
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
forall (r :: * -> *).
SharedProg r =>
([MSParameter r] -> MSBody r -> SMethod r)
-> Name
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
genMethodProc (Name
-> r (Visibility r)
-> VSType r
-> [MSParameter r]
-> MSBody r
-> SMethod r
forall (r :: * -> *).
MethodSym r =>
Name
-> r (Visibility r)
-> VSType r
-> [MSParameter r]
-> MSBody r
-> SMethod r
function Name
n r (Visibility r)
forall (r :: * -> *). VisibilitySym r => r (Visibility r)
private VSType r
t) Name
n Name
desc [ParameterChunk]
ps Maybe Name
r [MSBlock r]
b
genMethodProc :: (SharedProg r) => ([MSParameter r] -> MSBody r -> SMethod r) ->
Label -> Description -> [ParameterChunk] -> Maybe Description -> [MSBlock r]
-> GenState (SMethod r)
genMethodProc :: forall (r :: * -> *).
SharedProg r =>
([MSParameter r] -> MSBody r -> SMethod r)
-> Name
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
genMethodProc [MSParameter r] -> MSBody r -> SMethod r
f Name
n Name
desc [ParameterChunk]
p Maybe Name
r [MSBlock r]
b = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
[VS (r (Variable r))]
vars <- (ParameterChunk
-> StateT DrasilState Identity (VS (r (Variable r))))
-> [ParameterChunk]
-> StateT DrasilState Identity [VS (r (Variable r))]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (Input -> StateT DrasilState Identity (VS (r (Variable r)))
forall (r :: * -> *).
SharedProg r =>
Input -> GenState (SVariable r)
mkVarProc (Input -> StateT DrasilState Identity (VS (r (Variable r))))
-> (ParameterChunk -> Input)
-> ParameterChunk
-> StateT DrasilState Identity (VS (r (Variable r)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParameterChunk -> Input
forall c. (Quantity c, MayHaveUnit c) => c -> Input
quantvar) [ParameterChunk]
p
[MSParameter r]
ps <- (ParameterChunk -> StateT DrasilState Identity (MSParameter r))
-> [ParameterChunk] -> StateT DrasilState Identity [MSParameter r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ParameterChunk -> StateT DrasilState Identity (MSParameter r)
forall (r :: * -> *).
SharedProg r =>
ParameterChunk -> GenState (MSParameter r)
mkParamProc [ParameterChunk]
p
MSBody r
bod <- Name
-> [VS (r (Variable r))]
-> [MSBlock r]
-> StateT DrasilState Identity (MSBody r)
forall (r :: * -> *).
SharedProg r =>
Name -> [SVariable r] -> [MSBlock r] -> GenState (MSBody r)
logBody Name
n [VS (r (Variable r))]
vars [MSBlock r]
b
let fn :: SMethod r
fn = [MSParameter r] -> MSBody r -> SMethod r
f [MSParameter r]
ps MSBody r
bod
[Name]
pComms <- (ParameterChunk -> GenState Name)
-> [ParameterChunk] -> StateT DrasilState Identity [Name]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ParameterChunk -> GenState Name
forall c. CodeIdea c => c -> GenState Name
getComment [ParameterChunk]
p
SMethod r -> GenState (SMethod r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (SMethod r -> GenState (SMethod r))
-> SMethod r -> GenState (SMethod r)
forall a b. (a -> b) -> a -> b
$ if Comments
CommentFunc Comments -> [Comments] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` DrasilState -> [Comments]
commented DrasilState
g
then Name -> [Name] -> Maybe Name -> SMethod r -> SMethod r
forall (r :: * -> *).
MethodSym r =>
Name -> [Name] -> Maybe Name -> SMethod r -> SMethod r
docFunc Name
desc [Name]
pComms Maybe Name
r SMethod r
fn else SMethod r
fn
genFuncProc :: (SharedProg r) => (Name -> VSType r -> Description -> [ParameterChunk]
-> Maybe Description -> [MSBlock r] -> GenState (SMethod r)) ->
[StateVariable] -> Func -> GenState (SMethod r)
genFuncProc :: forall (r :: * -> *).
SharedProg r =>
(Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r))
-> [StateVariable] -> Func -> GenState (SMethod r)
genFuncProc Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
f [StateVariable]
svs (FDef (FuncDef Name
n Name
desc [ParameterChunk]
parms Space
o Maybe Name
rd [FuncStmt]
s)) = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
(DrasilState -> DrasilState) -> StateT DrasilState Identity ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\DrasilState
st -> DrasilState
st {currentScope = Local})
[MS (r (Statement r))]
stmts <- (FuncStmt -> StateT DrasilState Identity (MS (r (Statement r))))
-> [FuncStmt] -> StateT DrasilState Identity [MS (r (Statement r))]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FuncStmt -> StateT DrasilState Identity (MS (r (Statement r)))
forall (r :: * -> *).
SharedProg r =>
FuncStmt -> GenState (MSStatement r)
convStmtProc [FuncStmt]
s
[VS (r (Variable r))]
vars <- (Input -> StateT DrasilState Identity (VS (r (Variable r))))
-> [Input] -> StateT DrasilState Identity [VS (r (Variable r))]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Input -> StateT DrasilState Identity (VS (r (Variable r)))
forall (r :: * -> *).
SharedProg r =>
Input -> GenState (SVariable r)
mkVarProc (ChunkDB -> [FuncStmt] -> [Input]
fstdecl (DrasilState -> CodeSpec
codeSpec DrasilState
g CodeSpec -> Getting ChunkDB CodeSpec ChunkDB -> ChunkDB
forall s a. s -> Getting a s a -> a
^. Getting ChunkDB CodeSpec ChunkDB
forall c. HasOldCodeSpec c => Lens' c ChunkDB
Lens' CodeSpec ChunkDB
sysinfodbO) [FuncStmt]
s
[Input] -> [Input] -> [Input]
forall a. Eq a => [a] -> [a] -> [a]
\\ ((ParameterChunk -> Input) -> [ParameterChunk] -> [Input]
forall a b. (a -> b) -> [a] -> [b]
map ParameterChunk -> Input
forall c. (Quantity c, MayHaveUnit c) => c -> Input
quantvar [ParameterChunk]
parms [Input] -> [Input] -> [Input]
forall a. [a] -> [a] -> [a]
++ (StateVariable -> Input) -> [StateVariable] -> [Input]
forall a b. (a -> b) -> [a] -> [b]
map StateVariable -> Input
stVar [StateVariable]
svs))
CodeType
t <- Space -> GenState CodeType
spaceCodeType Space
o
Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
f Name
n (CodeType -> VSType r
forall (r :: * -> *). TypeSym r => CodeType -> VSType r
convType CodeType
t) Name
desc [ParameterChunk]
parms Maybe Name
rd [[MS (r (Statement r))] -> MSBlock r
forall (r :: * -> *). BlockSym r => [MSStatement r] -> MSBlock r
block ([MS (r (Statement r))] -> MSBlock r)
-> [MS (r (Statement r))] -> MSBlock r
forall a b. (a -> b) -> a -> b
$ (VS (r (Variable r)) -> MS (r (Statement r)))
-> [VS (r (Variable r))] -> [MS (r (Statement r))]
forall a b. (a -> b) -> [a] -> [b]
map (VS (r (Variable r)) -> r (Scope r) -> MS (r (Statement r))
forall (r :: * -> *).
DeclStatement r =>
SVariable r -> r (Scope r) -> MSStatement r
`varDec` r (Scope r)
forall (r :: * -> *). ScopeSym r => r (Scope r)
local) [VS (r (Variable r))]
vars, [MS (r (Statement r))] -> MSBlock r
forall (r :: * -> *). BlockSym r => [MSStatement r] -> MSBlock r
block [MS (r (Statement r))]
stmts]
genFuncProc Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
_ [StateVariable]
_ (FDef (CtorDef {})) = Name -> GenState (SMethod r)
forall a. HasCallStack => Name -> a
error Name
"genFuncProc: Procedural renderers do not support constructors"
genFuncProc Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
_ [StateVariable]
_ (FData (FuncData Name
n Name
desc DataDesc
ddef)) = Name -> Name -> DataDesc -> GenState (SMethod r)
forall (r :: * -> *).
SharedProg r =>
Name -> Name -> DataDesc -> GenState (SMethod r)
genDataFuncProc Name
n Name
desc DataDesc
ddef
genModFuncsProc :: (SharedProg r) => Mod -> [GenState (SMethod r)]
genModFuncsProc :: forall (r :: * -> *). SharedProg r => Mod -> [GenState (SMethod r)]
genModFuncsProc (Mod Name
_ Name
_ [Name]
_ [Class]
_ [Func]
fs) = (Func -> GenState (MS (r (Method r))))
-> [Func] -> [GenState (MS (r (Method r)))]
forall a b. (a -> b) -> [a] -> [b]
map ((Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (MS (r (Method r))))
-> [StateVariable] -> Func -> GenState (MS (r (Method r)))
forall (r :: * -> *).
SharedProg r =>
(Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r))
-> [StateVariable] -> Func -> GenState (SMethod r)
genFuncProc Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (MS (r (Method r)))
forall (r :: * -> *).
SharedProg r =>
Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
publicFuncProc []) [Func]
fs
readDataProc :: (SharedProg r) => DataDesc -> GenState [MSBlock r]
readDataProc :: forall (r :: * -> *).
SharedProg r =>
DataDesc -> GenState [MSBlock r]
readDataProc DataDesc
ddef = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
let localScope :: r (Scope r)
localScope = ScopeType -> r (Scope r)
forall (r :: * -> *). SharedProg r => ScopeType -> r (Scope r)
convScope (ScopeType -> r (Scope r)) -> ScopeType -> r (Scope r)
forall a b. (a -> b) -> a -> b
$ DrasilState -> ScopeType
currentScope DrasilState
g
[[MS (r (Statement r))]]
inD <- (Data -> StateT DrasilState Identity [MS (r (Statement r))])
-> DataDesc -> StateT DrasilState Identity [[MS (r (Statement r))]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (Data
-> r (Scope r)
-> StateT DrasilState Identity [MS (r (Statement r))]
forall (r :: * -> *).
SharedProg r =>
Data -> r (Scope r) -> GenState [MSStatement r]
`inData` r (Scope r)
localScope) DataDesc
ddef
VS (r (Value r))
v_filename <- Input -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *). SharedProg r => Input -> GenState (SValue r)
mkValProc (QuantityDict -> Input
forall c. (Quantity c, MayHaveUnit c) => c -> Input
quantvar QuantityDict
inFileName)
[MSBlock r] -> GenState [MSBlock r]
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return [[MS (r (Statement r))] -> MSBlock r
forall (r :: * -> *). BlockSym r => [MSStatement r] -> MSBlock r
block ([MS (r (Statement r))] -> MSBlock r)
-> [MS (r (Statement r))] -> MSBlock r
forall a b. (a -> b) -> a -> b
$
SVariable r -> r (Scope r) -> MS (r (Statement r))
forall (r :: * -> *).
DeclStatement r =>
SVariable r -> r (Scope r) -> MSStatement r
varDec SVariable r
forall (r :: * -> *). SharedProg r => SVariable r
var_infile r (Scope r)
localScope MS (r (Statement r))
-> [MS (r (Statement r))] -> [MS (r (Statement r))]
forall a. a -> [a] -> [a]
:
(if (Data -> Bool) -> DataDesc -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (\Data
d -> Data -> Bool
isLine Data
d Bool -> Bool -> Bool
|| Data -> Bool
isLines Data
d) DataDesc
ddef then [SVariable r -> r (Scope r) -> MS (r (Statement r))
forall (r :: * -> *).
DeclStatement r =>
SVariable r -> r (Scope r) -> MSStatement r
varDec SVariable r
forall (r :: * -> *). SharedProg r => SVariable r
var_line r (Scope r)
localScope,
Integer -> SVariable r -> r (Scope r) -> MS (r (Statement r))
forall (r :: * -> *).
DeclStatement r =>
Integer -> SVariable r -> r (Scope r) -> MSStatement r
listDec Integer
0 SVariable r
forall (r :: * -> *). SharedProg r => SVariable r
var_linetokens r (Scope r)
localScope] else []) [MS (r (Statement r))]
-> [MS (r (Statement r))] -> [MS (r (Statement r))]
forall a. [a] -> [a] -> [a]
++
[Integer -> SVariable r -> r (Scope r) -> MS (r (Statement r))
forall (r :: * -> *).
DeclStatement r =>
Integer -> SVariable r -> r (Scope r) -> MSStatement r
listDec Integer
0 SVariable r
forall (r :: * -> *). SharedProg r => SVariable r
var_lines r (Scope r)
localScope | (Data -> Bool) -> DataDesc -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Data -> Bool
isLines DataDesc
ddef] [MS (r (Statement r))]
-> [MS (r (Statement r))] -> [MS (r (Statement r))]
forall a. [a] -> [a] -> [a]
++ SVariable r -> VS (r (Value r)) -> MS (r (Statement r))
forall (r :: * -> *).
IOStatement r =>
SVariable r -> SValue r -> MSStatement r
openFileR SVariable r
forall (r :: * -> *). SharedProg r => SVariable r
var_infile
VS (r (Value r))
v_filename MS (r (Statement r))
-> [MS (r (Statement r))] -> [MS (r (Statement r))]
forall a. a -> [a] -> [a]
: [[MS (r (Statement r))]] -> [MS (r (Statement r))]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[MS (r (Statement r))]]
inD [MS (r (Statement r))]
-> [MS (r (Statement r))] -> [MS (r (Statement r))]
forall a. [a] -> [a] -> [a]
++ [VS (r (Value r)) -> MS (r (Statement r))
forall (r :: * -> *). IOStatement r => SValue r -> MSStatement r
closeFile VS (r (Value r))
forall (r :: * -> *). SharedProg r => SValue r
v_infile]]
where inData :: (SharedProg r) => Data -> r (Scope r) -> GenState [MSStatement r]
inData :: forall (r :: * -> *).
SharedProg r =>
Data -> r (Scope r) -> GenState [MSStatement r]
inData (Singleton Input
v) r (Scope r)
_ = do
VS (r (Variable r))
vv <- Input -> StateT DrasilState Identity (VS (r (Variable r)))
forall (r :: * -> *).
SharedProg r =>
Input -> GenState (SVariable r)
mkVarProc Input
v
[MSStatement r]
l <- VS (r (Variable r)) -> GenState [MSStatement r]
forall (r :: * -> *).
SharedProg r =>
SVariable r -> GenState [MSStatement r]
maybeLog VS (r (Variable r))
vv
[MSStatement r] -> GenState [MSStatement r]
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return [[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
$ SValue r -> VS (r (Variable r)) -> MSStatement r
forall (r :: * -> *).
IOStatement r =>
SValue r -> SVariable r -> MSStatement r
getFileInput SValue r
forall (r :: * -> *). SharedProg r => SValue r
v_infile VS (r (Variable r))
vv MSStatement r -> [MSStatement r] -> [MSStatement r]
forall a. a -> [a] -> [a]
: [MSStatement r]
l]
inData Data
JunkData r (Scope r)
_ = [MSStatement r] -> GenState [MSStatement r]
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return [SValue r -> MSStatement r
forall (r :: * -> *). IOStatement r => SValue r -> MSStatement r
discardFileLine SValue r
forall (r :: * -> *). SharedProg r => SValue r
v_infile]
inData (Line LinePattern
lp Char
d) r (Scope r)
scp = do
[MSStatement r]
lnI <- Maybe Name
-> LinePattern -> r (Scope r) -> GenState [MSStatement r]
forall (r :: * -> *).
SharedProg r =>
Maybe Name
-> LinePattern -> r (Scope r) -> GenState [MSStatement r]
lineData Maybe Name
forall a. Maybe a
Nothing LinePattern
lp r (Scope r)
scp
[MSStatement r]
logs <- LinePattern -> GenState [MSStatement r]
forall (r :: * -> *).
SharedProg r =>
LinePattern -> GenState [MSStatement r]
getEntryVarLogsProc LinePattern
lp
[MSStatement r] -> GenState [MSStatement r]
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return ([MSStatement r] -> GenState [MSStatement r])
-> [MSStatement r] -> GenState [MSStatement r]
forall a b. (a -> b) -> a -> b
$ [SValue r -> VS (r (Variable r)) -> MSStatement r
forall (r :: * -> *).
IOStatement r =>
SValue r -> SVariable r -> MSStatement r
getFileInputLine SValue r
forall (r :: * -> *). SharedProg r => SValue r
v_infile VS (r (Variable r))
forall (r :: * -> *). SharedProg r => SVariable r
var_line,
Char -> VS (r (Variable r)) -> SValue r -> MSStatement r
forall (r :: * -> *).
StringStatement r =>
Char -> SVariable r -> SValue r -> MSStatement r
stringSplit Char
d VS (r (Variable r))
forall (r :: * -> *). SharedProg r => SVariable r
var_linetokens SValue r
forall (r :: * -> *). SharedProg r => SValue r
v_line] [MSStatement r] -> [MSStatement r] -> [MSStatement r]
forall a. [a] -> [a] -> [a]
++ [MSStatement r]
lnI [MSStatement r] -> [MSStatement r] -> [MSStatement r]
forall a. [a] -> [a] -> [a]
++ [MSStatement r]
logs
inData (Lines LinePattern
lp Maybe Integer
ls Char
d) r (Scope r)
scp = do
[MSStatement r]
lnV <- Maybe Name
-> LinePattern -> r (Scope r) -> GenState [MSStatement r]
forall (r :: * -> *).
SharedProg r =>
Maybe Name
-> LinePattern -> r (Scope r) -> GenState [MSStatement r]
lineData (Name -> Maybe Name
forall a. a -> Maybe a
Just Name
"_temp") LinePattern
lp r (Scope r)
scp
[MSStatement r]
logs <- LinePattern -> GenState [MSStatement r]
forall (r :: * -> *).
SharedProg r =>
LinePattern -> GenState [MSStatement r]
getEntryVarLogsProc LinePattern
lp
let readLines :: Maybe Integer -> [MSStatement r]
readLines Maybe Integer
Nothing = [SValue r -> VS (r (Variable r)) -> MSStatement r
forall (r :: * -> *).
IOStatement r =>
SValue r -> SVariable r -> MSStatement r
getFileInputAll SValue r
forall (r :: * -> *). SharedProg r => SValue r
v_infile VS (r (Variable r))
forall (r :: * -> *). SharedProg r => SVariable r
var_lines,
VS (r (Variable 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
forRange VS (r (Variable r))
forall (r :: * -> *). SharedProg r => SVariable r
var_i (Integer -> SValue r
forall (r :: * -> *). Literal r => Integer -> SValue r
litInt Integer
0) (SValue r -> SValue r
forall (r :: * -> *). List r => SValue r -> SValue r
listSize SValue r
forall (r :: * -> *). SharedProg r => SValue r
v_lines) (Integer -> SValue r
forall (r :: * -> *). Literal r => Integer -> SValue r
litInt Integer
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
$ Char -> VS (r (Variable r)) -> SValue r -> MSStatement r
forall (r :: * -> *).
StringStatement r =>
Char -> SVariable r -> SValue r -> MSStatement r
stringSplit Char
d VS (r (Variable r))
forall (r :: * -> *). SharedProg r => SVariable r
var_linetokens (
SValue r -> SValue r -> SValue r
forall (r :: * -> *). List r => SValue r -> SValue r -> SValue r
listAccess SValue r
forall (r :: * -> *). SharedProg r => SValue r
v_lines SValue r
forall (r :: * -> *). SharedProg r => SValue r
v_i) MSStatement r -> [MSStatement r] -> [MSStatement r]
forall a. a -> [a] -> [a]
: [MSStatement r]
lnV)]
readLines (Just Integer
numLines) = [VS (r (Variable 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
forRange VS (r (Variable r))
forall (r :: * -> *). SharedProg r => SVariable r
var_i (Integer -> SValue r
forall (r :: * -> *). Literal r => Integer -> SValue r
litInt Integer
0)
(Integer -> SValue r
forall (r :: * -> *). Literal r => Integer -> SValue r
litInt Integer
numLines) (Integer -> SValue r
forall (r :: * -> *). Literal r => Integer -> SValue r
litInt Integer
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 -> VS (r (Variable r)) -> MSStatement r
forall (r :: * -> *).
IOStatement r =>
SValue r -> SVariable r -> MSStatement r
getFileInputLine SValue r
forall (r :: * -> *). SharedProg r => SValue r
v_infile VS (r (Variable r))
forall (r :: * -> *). SharedProg r => SVariable r
var_line,
Char -> VS (r (Variable r)) -> SValue r -> MSStatement r
forall (r :: * -> *).
StringStatement r =>
Char -> SVariable r -> SValue r -> MSStatement r
stringSplit Char
d VS (r (Variable r))
forall (r :: * -> *). SharedProg r => SVariable r
var_linetokens SValue r
forall (r :: * -> *). SharedProg r => SValue r
v_line
] [MSStatement r] -> [MSStatement r] -> [MSStatement r]
forall a. [a] -> [a] -> [a]
++ [MSStatement r]
lnV)]
[MSStatement r] -> GenState [MSStatement r]
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return ([MSStatement r] -> GenState [MSStatement r])
-> [MSStatement r] -> GenState [MSStatement r]
forall a b. (a -> b) -> a -> b
$ Maybe Integer -> [MSStatement r]
readLines Maybe Integer
ls [MSStatement r] -> [MSStatement r] -> [MSStatement r]
forall a. [a] -> [a] -> [a]
++ [MSStatement r]
logs
lineData :: (SharedProg r) => Maybe String -> LinePattern -> r (Scope r) ->
GenState [MSStatement r]
lineData :: forall (r :: * -> *).
SharedProg r =>
Maybe Name
-> LinePattern -> r (Scope r) -> GenState [MSStatement r]
lineData Maybe Name
s p :: LinePattern
p@(Straight [Input]
_) r (Scope r)
_ = do
[VS (r (Variable r))]
vs <- Maybe Name
-> LinePattern -> StateT DrasilState Identity [VS (r (Variable r))]
forall (r :: * -> *).
SharedProg r =>
Maybe Name -> LinePattern -> GenState [SVariable r]
getEntryVarsProc Maybe Name
s LinePattern
p
[MSStatement r] -> GenState [MSStatement r]
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return [[VS (r (Variable r))] -> SValue r -> MSStatement r
forall (r :: * -> *).
StringStatement r =>
[SVariable r] -> SValue r -> MSStatement r
stringListVals [VS (r (Variable r))]
vs SValue r
forall (r :: * -> *). SharedProg r => SValue r
v_linetokens]
lineData Maybe Name
s p :: LinePattern
p@(Repeat [Input]
ds) r (Scope r)
scp = do
[VS (r (Variable r))]
vs <- Maybe Name
-> LinePattern -> StateT DrasilState Identity [VS (r (Variable r))]
forall (r :: * -> *).
SharedProg r =>
Maybe Name -> LinePattern -> GenState [SVariable r]
getEntryVarsProc Maybe Name
s LinePattern
p
[StateT DrasilState Identity (MSStatement r)]
-> GenState [MSStatement r]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
forall (m :: * -> *) a. Monad m => [m a] -> m [a]
sequence ([StateT DrasilState Identity (MSStatement r)]
-> GenState [MSStatement r])
-> [StateT DrasilState Identity (MSStatement r)]
-> GenState [MSStatement r]
forall a b. (a -> b) -> a -> b
$ Maybe Name
-> [Input]
-> r (Scope r)
-> [StateT DrasilState Identity (MSStatement r)]
forall (r :: * -> *).
SharedProg r =>
Maybe Name -> [Input] -> r (Scope r) -> [GenState (MSStatement r)]
clearTemps Maybe Name
s [Input]
ds r (Scope r)
scp [StateT DrasilState Identity (MSStatement r)]
-> [StateT DrasilState Identity (MSStatement r)]
-> [StateT DrasilState Identity (MSStatement r)]
forall a. [a] -> [a] -> [a]
++ MSStatement r -> StateT DrasilState Identity (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return
([VS (r (Variable r))] -> SValue r -> MSStatement r
forall (r :: * -> *).
StringStatement r =>
[SVariable r] -> SValue r -> MSStatement r
stringListLists [VS (r (Variable r))]
vs SValue r
forall (r :: * -> *). SharedProg r => SValue r
v_linetokens) StateT DrasilState Identity (MSStatement r)
-> [StateT DrasilState Identity (MSStatement r)]
-> [StateT DrasilState Identity (MSStatement r)]
forall a. a -> [a] -> [a]
: Maybe Name
-> [Input] -> [StateT DrasilState Identity (MSStatement r)]
forall (r :: * -> *).
SharedProg r =>
Maybe Name -> [Input] -> [GenState (MSStatement r)]
appendTemps Maybe Name
s [Input]
ds
clearTemps :: (SharedProg r) => Maybe String -> [DataItem] -> r (Scope r) ->
[GenState (MSStatement r)]
clearTemps :: forall (r :: * -> *).
SharedProg r =>
Maybe Name -> [Input] -> r (Scope r) -> [GenState (MSStatement r)]
clearTemps Maybe Name
Nothing [Input]
_ r (Scope r)
_ = []
clearTemps (Just Name
sfx) [Input]
es r (Scope r)
scp = (Input -> GenState (MS (r (Statement r))))
-> [Input] -> [GenState (MS (r (Statement r)))]
forall a b. (a -> b) -> [a] -> [b]
map (\Input
v -> Name -> Input -> r (Scope r) -> GenState (MS (r (Statement r)))
forall (r :: * -> *).
SharedProg r =>
Name -> Input -> r (Scope r) -> GenState (MSStatement r)
clearTemp Name
sfx Input
v r (Scope r)
scp) [Input]
es
clearTemp :: (SharedProg r) => String -> DataItem -> r (Scope r) ->
GenState (MSStatement r)
clearTemp :: forall (r :: * -> *).
SharedProg r =>
Name -> Input -> r (Scope r) -> GenState (MSStatement r)
clearTemp Name
sfx Input
v r (Scope r)
scp = (CodeType -> MS (r (Statement r)))
-> GenState CodeType
-> StateT DrasilState Identity (MS (r (Statement r)))
forall a b.
(a -> b)
-> StateT DrasilState Identity a -> StateT DrasilState Identity b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\CodeType
t -> SVariable r -> r (Scope r) -> [SValue r] -> MS (r (Statement r))
forall (r :: * -> *).
DeclStatement r =>
SVariable r -> r (Scope r) -> [SValue r] -> MSStatement r
listDecDef (Name -> VSType r -> SVariable r
forall (r :: * -> *).
VariableSym r =>
Name -> VSType r -> SVariable r
var (Input -> Name
forall c. CodeIdea c => c -> Name
codeName Input
v Name -> Name -> Name
forall a. [a] -> [a] -> [a]
++ Name
sfx)
(VSType r -> VSType r
forall (r :: * -> *). TypeSym r => VSType r -> VSType r
listInnerType (VSType r -> VSType r) -> VSType r -> VSType r
forall a b. (a -> b) -> a -> b
$ CodeType -> VSType r
forall (r :: * -> *). TypeSym r => CodeType -> VSType r
convType CodeType
t)) r (Scope r)
scp []) (Input -> GenState CodeType
forall c. HasSpace c => c -> GenState CodeType
codeType Input
v)
appendTemps :: (SharedProg r) => Maybe String -> [DataItem]
-> [GenState (MSStatement r)]
appendTemps :: forall (r :: * -> *).
SharedProg r =>
Maybe Name -> [Input] -> [GenState (MSStatement r)]
appendTemps Maybe Name
Nothing [Input]
_ = []
appendTemps (Just Name
sfx) [Input]
es = (Input -> GenState (MS (r (Statement r))))
-> [Input] -> [GenState (MS (r (Statement r)))]
forall a b. (a -> b) -> [a] -> [b]
map (Name -> Input -> GenState (MS (r (Statement r)))
forall (r :: * -> *).
SharedProg r =>
Name -> Input -> GenState (MSStatement r)
appendTemp Name
sfx) [Input]
es
appendTemp :: (SharedProg r) => String -> DataItem ->
GenState (MSStatement r)
appendTemp :: forall (r :: * -> *).
SharedProg r =>
Name -> Input -> GenState (MSStatement r)
appendTemp Name
sfx Input
v = (CodeType -> MS (r (Statement r)))
-> GenState CodeType
-> StateT DrasilState Identity (MS (r (Statement r)))
forall a b.
(a -> b)
-> StateT DrasilState Identity a -> StateT DrasilState Identity b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\CodeType
t -> SValue r -> MS (r (Statement r))
forall (r :: * -> *). StatementSym r => SValue r -> MSStatement r
valStmt (SValue r -> MS (r (Statement r)))
-> SValue r -> MS (r (Statement r))
forall a b. (a -> b) -> a -> b
$ SValue r -> SValue r -> SValue r
forall (r :: * -> *). List r => SValue r -> SValue r -> SValue r
listAppend
(SVariable r -> SValue r
forall (r :: * -> *). VariableValue r => SVariable r -> SValue r
valueOf (SVariable r -> SValue r) -> SVariable r -> SValue r
forall a b. (a -> b) -> a -> b
$ Name -> VSType r -> SVariable r
forall (r :: * -> *).
VariableSym r =>
Name -> VSType r -> SVariable r
var (Input -> Name
forall c. CodeIdea c => c -> Name
codeName Input
v) (CodeType -> VSType r
forall (r :: * -> *). TypeSym r => CodeType -> VSType r
convType CodeType
t))
(SVariable r -> SValue r
forall (r :: * -> *). VariableValue r => SVariable r -> SValue r
valueOf (SVariable r -> SValue r) -> SVariable r -> SValue r
forall a b. (a -> b) -> a -> b
$ Name -> VSType r -> SVariable r
forall (r :: * -> *).
VariableSym r =>
Name -> VSType r -> SVariable r
var (Input -> Name
forall c. CodeIdea c => c -> Name
codeName Input
v Name -> Name -> Name
forall a. [a] -> [a] -> [a]
++ Name
sfx) (CodeType -> VSType r
forall (r :: * -> *). TypeSym r => CodeType -> VSType r
convType CodeType
t))) (Input -> GenState CodeType
forall c. HasSpace c => c -> GenState CodeType
codeType Input
v)
getEntryVarsProc :: (SharedProg r) => Maybe String -> LinePattern ->
GenState [SVariable r]
getEntryVarsProc :: forall (r :: * -> *).
SharedProg r =>
Maybe Name -> LinePattern -> GenState [SVariable r]
getEntryVarsProc Maybe Name
s LinePattern
lp = (Input -> StateT DrasilState Identity (VS (r (Variable r))))
-> [Input] -> StateT DrasilState Identity [VS (r (Variable r))]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((Input -> StateT DrasilState Identity (VS (r (Variable r))))
-> (Name
-> Input -> StateT DrasilState Identity (VS (r (Variable r))))
-> Maybe Name
-> Input
-> StateT DrasilState Identity (VS (r (Variable r)))
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Input -> StateT DrasilState Identity (VS (r (Variable r)))
forall (r :: * -> *).
SharedProg r =>
Input -> GenState (SVariable r)
mkVarProc (\Name
st Input
v -> Input -> GenState CodeType
forall c. HasSpace c => c -> GenState CodeType
codeType Input
v GenState CodeType
-> (CodeType -> StateT DrasilState Identity (VS (r (Variable r))))
-> StateT DrasilState Identity (VS (r (Variable r)))
forall a b.
StateT DrasilState Identity a
-> (a -> StateT DrasilState Identity b)
-> StateT DrasilState Identity b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
(Name
-> VS (r (Type r))
-> StateT DrasilState Identity (VS (r (Variable r)))
forall (r :: * -> *).
SharedProg r =>
Name -> VSType r -> GenState (SVariable r)
variableProc (Input -> Name
forall c. CodeIdea c => c -> Name
codeName Input
v Name -> Name -> Name
forall a. [a] -> [a] -> [a]
++ Name
st) (VS (r (Type r))
-> StateT DrasilState Identity (VS (r (Variable r))))
-> (CodeType -> VS (r (Type r)))
-> CodeType
-> StateT DrasilState Identity (VS (r (Variable r)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VS (r (Type r)) -> VS (r (Type r))
forall (r :: * -> *). TypeSym r => VSType r -> VSType r
listInnerType (VS (r (Type r)) -> VS (r (Type r)))
-> (CodeType -> VS (r (Type r))) -> CodeType -> VS (r (Type r))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CodeType -> VS (r (Type r))
forall (r :: * -> *). TypeSym r => CodeType -> VSType r
convType))
Maybe Name
s) (LinePattern -> [Input]
getPatternInputs LinePattern
lp)
getEntryVarLogsProc :: (SharedProg r) => LinePattern -> GenState [MSStatement r]
getEntryVarLogsProc :: forall (r :: * -> *).
SharedProg r =>
LinePattern -> GenState [MSStatement r]
getEntryVarLogsProc LinePattern
lp = do
[VS (r (Variable r))]
vs <- Maybe Name
-> LinePattern -> StateT DrasilState Identity [VS (r (Variable r))]
forall (r :: * -> *).
SharedProg r =>
Maybe Name -> LinePattern -> GenState [SVariable r]
getEntryVarsProc Maybe Name
forall a. Maybe a
Nothing LinePattern
lp
[[MSStatement r]]
logs <- (VS (r (Variable r)) -> GenState [MSStatement r])
-> [VS (r (Variable r))]
-> StateT DrasilState Identity [[MSStatement r]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM VS (r (Variable r)) -> GenState [MSStatement r]
forall (r :: * -> *).
SharedProg r =>
SVariable r -> GenState [MSStatement r]
maybeLog [VS (r (Variable r))]
vs
[MSStatement r] -> GenState [MSStatement r]
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return ([MSStatement r] -> GenState [MSStatement r])
-> [MSStatement r] -> GenState [MSStatement r]
forall a b. (a -> b) -> a -> b
$ [[MSStatement r]] -> [MSStatement r]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[MSStatement r]]
logs
convExprProc :: (SharedProg r) => CodeExpr -> GenState (SValue r)
convExprProc :: forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc (Lit (Dbl Double
d)) = do
CodeType
sm <- Space -> GenState CodeType
spaceCodeType Space
Real
let getLiteral :: CodeType -> SValue r
getLiteral CodeType
Double = Double -> SValue r
forall (r :: * -> *). Literal r => Double -> SValue r
litDouble Double
d
getLiteral CodeType
Float = Float -> SValue r
forall (r :: * -> *). Literal r => Float -> SValue r
litFloat (Double -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
d)
getLiteral CodeType
_ = Name -> SValue r
forall a. HasCallStack => Name -> a
error Name
"convExprProc: Real space matched to invalid CodeType; should be Double or Float"
SValue r -> GenState (SValue r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (SValue r -> GenState (SValue r))
-> SValue r -> GenState (SValue r)
forall a b. (a -> b) -> a -> b
$ CodeType -> SValue r
forall {r :: * -> *}. Literal r => CodeType -> SValue r
getLiteral CodeType
sm
convExprProc (Lit (ExactDbl Integer
d)) = CodeExpr -> GenState (SValue r)
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc (CodeExpr -> GenState (SValue r))
-> CodeExpr -> GenState (SValue r)
forall a b. (a -> b) -> a -> b
$ Literal -> CodeExpr
Lit (Literal -> CodeExpr) -> (Double -> Literal) -> Double -> CodeExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> Literal
Dbl (Double -> CodeExpr) -> Double -> CodeExpr
forall a b. (a -> b) -> a -> b
$ Integer -> Double
forall a. Num a => Integer -> a
fromInteger Integer
d
convExprProc (Lit (Int Integer
i)) = SValue r -> GenState (SValue r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (SValue r -> GenState (SValue r))
-> SValue r -> GenState (SValue r)
forall a b. (a -> b) -> a -> b
$ Integer -> SValue r
forall (r :: * -> *). Literal r => Integer -> SValue r
litInt Integer
i
convExprProc (Lit (Str Name
s)) = SValue r -> GenState (SValue r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (SValue r -> GenState (SValue r))
-> SValue r -> GenState (SValue r)
forall a b. (a -> b) -> a -> b
$ Name -> SValue r
forall (r :: * -> *). Literal r => Name -> SValue r
litString Name
s
convExprProc (Lit (Perc Integer
a Integer
b)) = do
CodeType
sm <- Space -> GenState CodeType
spaceCodeType Space
Rational
let getLiteral :: CodeType -> Double -> SValue r
getLiteral CodeType
Double = Double -> SValue r
forall (r :: * -> *). Literal r => Double -> SValue r
litDouble
getLiteral CodeType
Float = Float -> SValue r
forall (r :: * -> *). Literal r => Float -> SValue r
litFloat (Float -> SValue r) -> (Double -> Float) -> Double -> SValue r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac
getLiteral CodeType
_ = Name -> Double -> SValue r
forall a. HasCallStack => Name -> a
error Name
"convExprProc: Rational space matched to invalid CodeType; should be Double or Float"
SValue r -> GenState (SValue r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (SValue r -> GenState (SValue r))
-> SValue r -> GenState (SValue r)
forall a b. (a -> b) -> a -> b
$ CodeType -> Double -> SValue r
forall {r :: * -> *}. Literal r => CodeType -> Double -> SValue r
getLiteral CodeType
sm (Integer -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
a Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ (Double
10 Double -> Double -> Double
forall a. Floating a => a -> a -> a
** Integer -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
b))
convExprProc (AssocA AssocArithOper
Add [CodeExpr]
l) = (SValue r -> SValue r -> SValue r) -> [SValue r] -> SValue r
forall a. (a -> a -> a) -> [a] -> a
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldl1 SValue r -> SValue r -> SValue r
forall (r :: * -> *).
NumericExpression r =>
SValue r -> SValue r -> SValue r
(#+) ([SValue r] -> SValue r)
-> StateT DrasilState Identity [SValue r] -> GenState (SValue r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (CodeExpr -> GenState (SValue r))
-> [CodeExpr] -> StateT DrasilState Identity [SValue r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM CodeExpr -> GenState (SValue r)
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc [CodeExpr]
l
convExprProc (AssocA AssocArithOper
Mul [CodeExpr]
l) = (SValue r -> SValue r -> SValue r) -> [SValue r] -> SValue r
forall a. (a -> a -> a) -> [a] -> a
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldl1 SValue r -> SValue r -> SValue r
forall (r :: * -> *).
NumericExpression r =>
SValue r -> SValue r -> SValue r
(#*) ([SValue r] -> SValue r)
-> StateT DrasilState Identity [SValue r] -> GenState (SValue r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (CodeExpr -> GenState (SValue r))
-> [CodeExpr] -> StateT DrasilState Identity [SValue r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM CodeExpr -> GenState (SValue r)
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc [CodeExpr]
l
convExprProc (AssocB AssocBoolOper
And [CodeExpr]
l) = (SValue r -> SValue r -> SValue r) -> [SValue r] -> SValue r
forall a. (a -> a -> a) -> [a] -> a
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldl1 SValue r -> SValue r -> SValue r
forall (r :: * -> *).
BooleanExpression r =>
SValue r -> SValue r -> SValue r
(?&&) ([SValue r] -> SValue r)
-> StateT DrasilState Identity [SValue r] -> GenState (SValue r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (CodeExpr -> GenState (SValue r))
-> [CodeExpr] -> StateT DrasilState Identity [SValue r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM CodeExpr -> GenState (SValue r)
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc [CodeExpr]
l
convExprProc (AssocB AssocBoolOper
Or [CodeExpr]
l) = (SValue r -> SValue r -> SValue r) -> [SValue r] -> SValue r
forall a. (a -> a -> a) -> [a] -> a
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldl1 SValue r -> SValue r -> SValue r
forall (r :: * -> *).
BooleanExpression r =>
SValue r -> SValue r -> SValue r
(?||) ([SValue r] -> SValue r)
-> StateT DrasilState Identity [SValue r] -> GenState (SValue r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (CodeExpr -> GenState (SValue r))
-> [CodeExpr] -> StateT DrasilState Identity [SValue r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM CodeExpr -> GenState (SValue r)
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc [CodeExpr]
l
convExprProc (AssocC AssocConcatOper
SUnion [CodeExpr]
l) = (SValue r -> SValue r -> SValue r) -> [SValue r] -> SValue r
forall a. (a -> a -> a) -> [a] -> a
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldl1 SValue r -> SValue r -> SValue r
forall (r :: * -> *).
NumericExpression r =>
SValue r -> SValue r -> SValue r
(#+) ([SValue r] -> SValue r)
-> StateT DrasilState Identity [SValue r] -> GenState (SValue r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (CodeExpr -> GenState (SValue r))
-> [CodeExpr] -> StateT DrasilState Identity [SValue r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM CodeExpr -> GenState (SValue r)
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc [CodeExpr]
l
convExprProc (C UID
c) = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
let v :: Input
v = QuantityDict -> Input
forall c. (Quantity c, MayHaveUnit c) => c -> Input
quantvar (DrasilState -> UID -> QuantityDict
lookupC DrasilState
g UID
c)
Input -> GenState (SValue r)
forall (r :: * -> *). SharedProg r => Input -> GenState (SValue r)
mkValProc Input
v
convExprProc (FCall UID
c [CodeExpr]
x [(UID, CodeExpr)]
ns) = UID
-> [CodeExpr]
-> [(UID, CodeExpr)]
-> (Name
-> Name
-> VSType r
-> [SValue r]
-> NamedArgs r
-> GenState (SValue r))
-> (Name
-> Name -> VSType r -> [SValue r] -> NamedArgs r -> SValue r)
-> GenState (SValue r)
forall (r :: * -> *).
SharedProg r =>
UID
-> [CodeExpr]
-> [(UID, CodeExpr)]
-> (Name
-> Name
-> VSType r
-> [SValue r]
-> NamedArgs r
-> GenState (SValue r))
-> (Name
-> Name -> VSType r -> [SValue r] -> NamedArgs r -> SValue r)
-> GenState (SValue r)
convCallProc UID
c [CodeExpr]
x [(UID, CodeExpr)]
ns Name
-> Name
-> VSType r
-> [SValue r]
-> NamedArgs r
-> GenState (SValue r)
forall (r :: * -> *).
SharedProg r =>
Name
-> Name
-> VSType r
-> [SValue r]
-> NamedArgs r
-> GenState (SValue r)
fAppProc Name -> Name -> VSType r -> [SValue r] -> NamedArgs r -> SValue r
forall (r :: * -> *). ValueExpression r => Name -> MixedCall r
libFuncAppMixedArgs
convExprProc (New {}) = Name -> GenState (SValue r)
forall a. HasCallStack => Name -> a
error Name
"convExprProc: Procedural renderers do not support object creation"
convExprProc (Message {}) = Name -> GenState (SValue r)
forall a. HasCallStack => Name -> a
error Name
"convExprProc: Procedural renderers do not support methods"
convExprProc (Field UID
_ UID
_) = Name -> GenState (SValue r)
forall a. HasCallStack => Name -> a
error Name
"convExprProc: Procedural renderers do not support object field access"
convExprProc (UnaryOp UFunc
o CodeExpr
u) = (SValue r -> SValue r)
-> GenState (SValue r) -> GenState (SValue r)
forall a b.
(a -> b)
-> StateT DrasilState Identity a -> StateT DrasilState Identity b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (UFunc -> SValue r -> SValue r
forall (r :: * -> *). SharedProg r => UFunc -> SValue r -> SValue r
unop UFunc
o) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
u)
convExprProc (UnaryOpB UFuncB
o CodeExpr
u) = (SValue r -> SValue r)
-> GenState (SValue r) -> GenState (SValue r)
forall a b.
(a -> b)
-> StateT DrasilState Identity a -> StateT DrasilState Identity b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (UFuncB -> SValue r -> SValue r
forall (r :: * -> *).
SharedProg r =>
UFuncB -> SValue r -> SValue r
unopB UFuncB
o) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
u)
convExprProc (UnaryOpVV UFuncVV
o CodeExpr
u) = (SValue r -> SValue r)
-> GenState (SValue r) -> GenState (SValue r)
forall a b.
(a -> b)
-> StateT DrasilState Identity a -> StateT DrasilState Identity b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (UFuncVV -> SValue r -> SValue r
forall (r :: * -> *).
SharedProg r =>
UFuncVV -> SValue r -> SValue r
unopVV UFuncVV
o) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
u)
convExprProc (UnaryOpVN UFuncVN
o CodeExpr
u) = (SValue r -> SValue r)
-> GenState (SValue r) -> GenState (SValue r)
forall a b.
(a -> b)
-> StateT DrasilState Identity a -> StateT DrasilState Identity b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (UFuncVN -> SValue r -> SValue r
forall (r :: * -> *).
SharedProg r =>
UFuncVN -> SValue r -> SValue r
unopVN UFuncVN
o) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
u)
convExprProc (ArithBinaryOp ArithBinOp
Frac (Lit (Int Integer
a)) (Lit (Int Integer
b))) = do
CodeType
sm <- Space -> GenState CodeType
spaceCodeType Space
Rational
let getLiteral :: CodeType -> SValue r
getLiteral CodeType
Double = Double -> SValue r
forall (r :: * -> *). Literal r => Double -> SValue r
litDouble (Integer -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
a) SValue r -> SValue r -> SValue r
forall (r :: * -> *).
NumericExpression r =>
SValue r -> SValue r -> SValue r
#/ Double -> SValue r
forall (r :: * -> *). Literal r => Double -> SValue r
litDouble (Integer -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
b)
getLiteral CodeType
Float = Float -> SValue r
forall (r :: * -> *). Literal r => Float -> SValue r
litFloat (Integer -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
a) SValue r -> SValue r -> SValue r
forall (r :: * -> *).
NumericExpression r =>
SValue r -> SValue r -> SValue r
#/ Float -> SValue r
forall (r :: * -> *). Literal r => Float -> SValue r
litFloat (Integer -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
b)
getLiteral CodeType
_ = Name -> SValue r
forall a. HasCallStack => Name -> a
error Name
"convExprProc: Rational space matched to invalid CodeType; should be Double or Float"
SValue r -> GenState (SValue r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (SValue r -> GenState (SValue r))
-> SValue r -> GenState (SValue r)
forall a b. (a -> b) -> a -> b
$ CodeType -> SValue r
forall {r :: * -> *}.
(NumericExpression r, Literal r) =>
CodeType -> SValue r
getLiteral CodeType
sm
convExprProc (ArithBinaryOp ArithBinOp
o CodeExpr
a CodeExpr
b) = (SValue r -> SValue r -> SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 (ArithBinOp -> SValue r -> SValue r -> SValue r
forall (r :: * -> *).
SharedProg r =>
ArithBinOp -> SValue r -> SValue r -> SValue r
arithBfunc ArithBinOp
o) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
a) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
b)
convExprProc (BoolBinaryOp BoolBinOp
o CodeExpr
a CodeExpr
b) = (SValue r -> SValue r -> SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 (BoolBinOp -> SValue r -> SValue r -> SValue r
forall (r :: * -> *). BoolBinOp -> SValue r -> SValue r -> SValue r
boolBfunc BoolBinOp
o) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
a) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
b)
convExprProc (LABinaryOp LABinOp
o CodeExpr
a CodeExpr
b) = (SValue r -> SValue r -> SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 (LABinOp -> SValue r -> SValue r -> SValue r
forall (r :: * -> *).
SharedProg r =>
LABinOp -> SValue r -> SValue r -> SValue r
laBfunc LABinOp
o) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
a) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
b)
convExprProc (EqBinaryOp EqBinOp
o CodeExpr
a CodeExpr
b) = (SValue r -> SValue r -> SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 (EqBinOp -> SValue r -> SValue r -> SValue r
forall (r :: * -> *).
SharedProg r =>
EqBinOp -> SValue r -> SValue r -> SValue r
eqBfunc EqBinOp
o) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
a) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
b)
convExprProc (OrdBinaryOp OrdBinOp
o CodeExpr
a CodeExpr
b) = (SValue r -> SValue r -> SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 (OrdBinOp -> SValue r -> SValue r -> SValue r
forall (r :: * -> *).
SharedProg r =>
OrdBinOp -> SValue r -> SValue r -> SValue r
ordBfunc OrdBinOp
o) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
a) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
b)
convExprProc (VVVBinaryOp VVVBinOp
o CodeExpr
a CodeExpr
b) = (SValue r -> SValue r -> SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 (VVVBinOp -> SValue r -> SValue r -> SValue r
forall (r :: * -> *). VVVBinOp -> SValue r -> SValue r -> SValue r
vecVecVecBfunc VVVBinOp
o) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
a) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
b)
convExprProc (VVNBinaryOp VVNBinOp
o CodeExpr
a CodeExpr
b) = (SValue r -> SValue r -> SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 (VVNBinOp -> SValue r -> SValue r -> SValue r
forall (r :: * -> *). VVNBinOp -> SValue r -> SValue r -> SValue r
vecVecNumBfunc VVNBinOp
o) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
a) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
b)
convExprProc (NVVBinaryOp NVVBinOp
o CodeExpr
a CodeExpr
b) = (SValue r -> SValue r -> SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 (NVVBinOp -> SValue r -> SValue r -> SValue r
forall (r :: * -> *). NVVBinOp -> SValue r -> SValue r -> SValue r
numVecVecBfunc NVVBinOp
o) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
a) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
b)
convExprProc (ESSBinaryOp ESSBinOp
o CodeExpr
a CodeExpr
b) = (SValue r -> SValue r -> SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 (ESSBinOp -> SValue r -> SValue r -> SValue r
forall (r :: * -> *).
SharedProg r =>
ESSBinOp -> SValue r -> SValue r -> SValue r
elementSetSetBfunc ESSBinOp
o) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
a) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
b)
convExprProc (ESBBinaryOp ESBBinOp
o CodeExpr
a CodeExpr
b) = (SValue r -> SValue r -> SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
-> GenState (SValue r)
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 (ESBBinOp -> SValue r -> SValue r -> SValue r
forall (r :: * -> *).
SharedProg r =>
ESBBinOp -> SValue r -> SValue r -> SValue r
elementSetBoolBfunc ESBBinOp
o) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
a) (CodeExpr -> GenState (SValue r)
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
b)
convExprProc (Case Completeness
c [(CodeExpr, CodeExpr)]
l) = [(CodeExpr, CodeExpr)] -> GenState (SValue r)
forall {r :: * -> *}.
SharedProg r =>
[(CodeExpr, CodeExpr)]
-> StateT DrasilState Identity (VS (r (Value r)))
doit [(CodeExpr, CodeExpr)]
l
where
doit :: [(CodeExpr, CodeExpr)]
-> StateT DrasilState Identity (VS (r (Value r)))
doit [] = Name -> StateT DrasilState Identity (VS (r (Value r)))
forall a. HasCallStack => Name -> a
error Name
"should never happen"
doit [(CodeExpr
e,CodeExpr
_)] = CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
e
doit ((CodeExpr
e,CodeExpr
cond):[(CodeExpr, CodeExpr)]
xs) = (VS (r (Value r))
-> VS (r (Value r)) -> VS (r (Value r)) -> VS (r (Value r)))
-> StateT DrasilState Identity (VS (r (Value r)))
-> StateT DrasilState Identity (VS (r (Value r)))
-> StateT DrasilState Identity (VS (r (Value r)))
-> StateT DrasilState Identity (VS (r (Value r)))
forall (m :: * -> *) a1 a2 a3 r.
Monad m =>
(a1 -> a2 -> a3 -> r) -> m a1 -> m a2 -> m a3 -> m r
liftM3 VS (r (Value r))
-> VS (r (Value r)) -> VS (r (Value r)) -> VS (r (Value r))
forall (r :: * -> *).
ValueExpression r =>
SValue r -> SValue r -> SValue r -> SValue r
inlineIf (CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
cond) (CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
e)
(CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc (Completeness -> [(CodeExpr, CodeExpr)] -> CodeExpr
Case Completeness
c [(CodeExpr, CodeExpr)]
xs))
convExprProc (Matrix [[CodeExpr]
l]) = do
[SValue r]
ar <- (CodeExpr -> GenState (SValue r))
-> [CodeExpr] -> StateT DrasilState Identity [SValue r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM CodeExpr -> GenState (SValue r)
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc [CodeExpr]
l
SValue r -> GenState (SValue r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (SValue r -> GenState (SValue r))
-> SValue r -> GenState (SValue r)
forall a b. (a -> b) -> a -> b
$ VSType r -> [SValue r] -> SValue r
forall (r :: * -> *).
Literal r =>
VSType r -> [SValue r] -> SValue r
litArray ((r (Value r) -> r (Type r)) -> SValue r -> VSType r
forall a b.
(a -> b)
-> StateT ValueState Identity a -> StateT ValueState Identity b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap r (Value r) -> r (Type r)
forall (r :: * -> *). ValueSym r => r (Value r) -> r (Type r)
valueType ([SValue r] -> SValue r
forall a. HasCallStack => [a] -> a
head [SValue r]
ar)) [SValue r]
ar
convExprProc Matrix{} = Name -> GenState (SValue r)
forall a. HasCallStack => Name -> a
error Name
"convExprProc: Matrix"
convExprProc (S.Set Space
s [CodeExpr]
l) = do
[SValue r]
ar <- (CodeExpr -> GenState (SValue r))
-> [CodeExpr] -> StateT DrasilState Identity [SValue r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM CodeExpr -> GenState (SValue r)
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc [CodeExpr]
l
CodeType
sm <- Space -> GenState CodeType
spaceCodeType Space
s
SValue r -> GenState (SValue r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (SValue r -> GenState (SValue r))
-> SValue r -> GenState (SValue r)
forall a b. (a -> b) -> a -> b
$ VSType r -> [SValue r] -> SValue r
forall (r :: * -> *).
Literal r =>
VSType r -> [SValue r] -> SValue r
litSet (CodeType -> VSType r
forall (r :: * -> *). TypeSym r => CodeType -> VSType r
convType CodeType
sm) [SValue r]
ar
convExprProc (Variable Name
s (S.Set Space
l [CodeExpr]
_)) = do
CodeType
sm <- Space -> GenState CodeType
spaceCodeType Space
l
let varSet :: SVariable r
varSet = Name -> VSType r -> SVariable r
forall (r :: * -> *).
VariableSym r =>
Name -> VSType r -> SVariable r
var Name
s (VSType r -> VSType r
forall (r :: * -> *). TypeSym r => VSType r -> VSType r
setType (VSType r -> VSType r) -> VSType r -> VSType r
forall a b. (a -> b) -> a -> b
$ CodeType -> VSType r
forall (r :: * -> *). TypeSym r => CodeType -> VSType r
convType CodeType
sm)
SValue r -> GenState (SValue r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (SValue r -> GenState (SValue r))
-> SValue r -> GenState (SValue r)
forall a b. (a -> b) -> a -> b
$ SVariable r -> SValue r
forall (r :: * -> *). VariableValue r => SVariable r -> SValue r
valueOf SVariable r
varSet
convExprProc (Variable Name
_ CodeExpr
_) = Name -> GenState (SValue r)
forall a. HasCallStack => Name -> a
error Name
"convExpr: Variable"
convExprProc Operator{} = Name -> GenState (SValue r)
forall a. HasCallStack => Name -> a
error Name
"convExprProc: Operator"
convExprProc (RealI UID
c RealInterval CodeExpr CodeExpr
ri) = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
CodeExpr -> GenState (SValue r)
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc (CodeExpr -> GenState (SValue r))
-> CodeExpr -> GenState (SValue r)
forall a b. (a -> b) -> a -> b
$ QuantityDict -> RealInterval CodeExpr CodeExpr -> CodeExpr
forall c.
(HasUID c, HasSymbol c) =>
c -> RealInterval CodeExpr CodeExpr -> CodeExpr
renderRealInt (DrasilState -> UID -> QuantityDict
lookupC DrasilState
g UID
c) RealInterval CodeExpr CodeExpr
ri
convCallProc :: (SharedProg r) => UID -> [CodeExpr] -> [(UID, CodeExpr)] ->
(Name -> Name -> VSType r -> [SValue r] -> NamedArgs r ->
GenState (SValue r)) -> (Name -> Name -> VSType r -> [SValue r]
-> NamedArgs r -> SValue r) -> GenState (SValue r)
convCallProc :: forall (r :: * -> *).
SharedProg r =>
UID
-> [CodeExpr]
-> [(UID, CodeExpr)]
-> (Name
-> Name
-> VSType r
-> [SValue r]
-> NamedArgs r
-> GenState (SValue r))
-> (Name
-> Name -> VSType r -> [SValue r] -> NamedArgs r -> SValue r)
-> GenState (SValue r)
convCallProc UID
c [CodeExpr]
x [(UID, CodeExpr)]
ns Name
-> Name
-> VSType r
-> [SValue r]
-> NamedArgs r
-> GenState (SValue r)
f Name -> Name -> VSType r -> [SValue r] -> NamedArgs r -> SValue r
libf = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
let info :: ChunkDB
info = DrasilState -> CodeSpec
codeSpec DrasilState
g CodeSpec -> Getting ChunkDB CodeSpec ChunkDB -> ChunkDB
forall s a. s -> Getting a s a -> a
^. Getting ChunkDB CodeSpec ChunkDB
forall c. HasOldCodeSpec c => Lens' c ChunkDB
Lens' CodeSpec ChunkDB
sysinfodbO
mem :: Map Name Name
mem = DrasilState -> Map Name Name
eMap DrasilState
g
lem :: Map Name Name
lem = DrasilState -> Map Name Name
libEMap DrasilState
g
funcCd :: CodeFuncChunk
funcCd = QuantityDict -> CodeFuncChunk
forall c. (Quantity c, MayHaveUnit c) => c -> CodeFuncChunk
quantfunc (ChunkDB -> UID -> QuantityDict
symbResolve ChunkDB
info UID
c)
funcNm :: Name
funcNm = CodeFuncChunk -> Name
forall c. CodeIdea c => c -> Name
codeName CodeFuncChunk
funcCd
CodeType
funcTp <- CodeFuncChunk -> GenState CodeType
forall c. HasSpace c => c -> GenState CodeType
codeType CodeFuncChunk
funcCd
[SValue r]
args <- (CodeExpr -> GenState (SValue r))
-> [CodeExpr] -> StateT DrasilState Identity [SValue r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM CodeExpr -> GenState (SValue r)
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc [CodeExpr]
x
[VS (r (Variable r))]
nms <- ((UID, CodeExpr)
-> StateT DrasilState Identity (VS (r (Variable r))))
-> [(UID, CodeExpr)]
-> StateT DrasilState Identity [VS (r (Variable r))]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (Input -> StateT DrasilState Identity (VS (r (Variable r)))
forall (r :: * -> *).
SharedProg r =>
Input -> GenState (SVariable r)
mkVarProc (Input -> StateT DrasilState Identity (VS (r (Variable r))))
-> ((UID, CodeExpr) -> Input)
-> (UID, CodeExpr)
-> StateT DrasilState Identity (VS (r (Variable r)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QuantityDict -> Input
forall c. (Quantity c, MayHaveUnit c) => c -> Input
quantvar (QuantityDict -> Input)
-> ((UID, CodeExpr) -> QuantityDict) -> (UID, CodeExpr) -> Input
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ChunkDB -> UID -> QuantityDict
symbResolve ChunkDB
info (UID -> QuantityDict)
-> ((UID, CodeExpr) -> UID) -> (UID, CodeExpr) -> QuantityDict
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (UID, CodeExpr) -> UID
forall a b. (a, b) -> a
fst) [(UID, CodeExpr)]
ns
[SValue r]
nargs <- ((UID, CodeExpr) -> GenState (SValue r))
-> [(UID, CodeExpr)] -> StateT DrasilState Identity [SValue r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (CodeExpr -> GenState (SValue r)
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc (CodeExpr -> GenState (SValue r))
-> ((UID, CodeExpr) -> CodeExpr)
-> (UID, CodeExpr)
-> GenState (SValue r)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (UID, CodeExpr) -> CodeExpr
forall a b. (a, b) -> b
snd) [(UID, CodeExpr)]
ns
GenState (SValue r)
-> (Name -> GenState (SValue r))
-> Maybe Name
-> GenState (SValue r)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (GenState (SValue r)
-> (Name -> GenState (SValue r))
-> Maybe Name
-> GenState (SValue r)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Name -> GenState (SValue r)
forall a. HasCallStack => Name -> a
error (Name -> GenState (SValue r)) -> Name -> GenState (SValue r)
forall a b. (a -> b) -> a -> b
$ Name
"Call to non-existent function " Name -> Name -> Name
forall a. [a] -> [a] -> [a]
++ Name
funcNm)
(\Name
m -> SValue r -> GenState (SValue r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (SValue r -> GenState (SValue r))
-> SValue r -> GenState (SValue r)
forall a b. (a -> b) -> a -> b
$ Name -> Name -> VSType r -> [SValue r] -> NamedArgs r -> SValue r
libf Name
m Name
funcNm (CodeType -> VSType r
forall (r :: * -> *). TypeSym r => CodeType -> VSType r
convType CodeType
funcTp) [SValue r]
args ([VS (r (Variable r))] -> [SValue r] -> NamedArgs r
forall a b. [a] -> [b] -> [(a, b)]
zip [VS (r (Variable r))]
nms [SValue r]
nargs))
(Name -> Map Name Name -> Maybe Name
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Name
funcNm Map Name Name
lem))
(\Name
m -> Name
-> Name
-> VSType r
-> [SValue r]
-> NamedArgs r
-> GenState (SValue r)
f Name
m Name
funcNm (CodeType -> VSType r
forall (r :: * -> *). TypeSym r => CodeType -> VSType r
convType CodeType
funcTp) [SValue r]
args ([VS (r (Variable r))] -> [SValue r] -> NamedArgs r
forall a b. [a] -> [b] -> [(a, b)]
zip [VS (r (Variable r))]
nms [SValue r]
nargs))
(Name -> Map Name Name -> Maybe Name
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Name
funcNm Map Name Name
mem)
convStmtProc :: (SharedProg r) => FuncStmt -> GenState (MSStatement r)
convStmtProc :: forall (r :: * -> *).
SharedProg r =>
FuncStmt -> GenState (MSStatement r)
convStmtProc (FAsg Input
v (Matrix [[CodeExpr]
es])) = do
[VS (r (Value r))]
els <- (CodeExpr -> StateT DrasilState Identity (VS (r (Value r))))
-> [CodeExpr] -> StateT DrasilState Identity [VS (r (Value r))]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc [CodeExpr]
es
StateT ValueState Identity (r (Variable r))
v' <- Input
-> StateT
DrasilState Identity (StateT ValueState Identity (r (Variable r)))
forall (r :: * -> *).
SharedProg r =>
Input -> GenState (SVariable r)
mkVarProc Input
v
CodeType
t <- Input -> GenState CodeType
forall c. HasSpace c => c -> GenState CodeType
codeType Input
v
let listFunc :: CodeType -> VSType r -> [SValue r] -> SValue r
listFunc (C.List CodeType
_) = VSType r -> [SValue r] -> SValue r
forall (r :: * -> *).
Literal r =>
VSType r -> [SValue r] -> SValue r
litList
listFunc (C.Array CodeType
_) = VSType r -> [SValue r] -> SValue r
forall (r :: * -> *).
Literal r =>
VSType r -> [SValue r] -> SValue r
litArray
listFunc CodeType
_ = Name -> VSType r -> [SValue r] -> SValue r
forall a. HasCallStack => Name -> a
error Name
"Type mismatch between variable and value in assignment FuncStmt"
[MSStatement r]
l <- StateT ValueState Identity (r (Variable r))
-> StateT DrasilState Identity [MSStatement r]
forall (r :: * -> *).
SharedProg r =>
SVariable r -> GenState [MSStatement r]
maybeLog StateT ValueState Identity (r (Variable r))
v'
MSStatement r -> GenState (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (MSStatement r -> GenState (MSStatement r))
-> MSStatement r -> GenState (MSStatement r)
forall a b. (a -> b) -> a -> b
$ [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
$ StateT ValueState Identity (r (Variable r))
-> VS (r (Value r)) -> MSStatement r
forall (r :: * -> *).
AssignStatement r =>
SVariable r -> SValue r -> MSStatement r
assign StateT ValueState Identity (r (Variable r))
v' (CodeType
-> VS (r (Type r)) -> [VS (r (Value r))] -> VS (r (Value r))
forall {r :: * -> *}.
Literal r =>
CodeType -> VSType r -> [SValue r] -> SValue r
listFunc CodeType
t (VS (r (Type r)) -> VS (r (Type r))
forall (r :: * -> *). TypeSym r => VSType r -> VSType r
listInnerType (VS (r (Type r)) -> VS (r (Type r)))
-> VS (r (Type r)) -> VS (r (Type r))
forall a b. (a -> b) -> a -> b
$ (r (Variable r) -> r (Type r))
-> StateT ValueState Identity (r (Variable r)) -> VS (r (Type r))
forall a b.
(a -> b)
-> StateT ValueState Identity a -> StateT ValueState Identity b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap r (Variable r) -> r (Type r)
forall (r :: * -> *).
VariableElim r =>
r (Variable r) -> r (Type r)
variableType StateT ValueState Identity (r (Variable r))
v')
[VS (r (Value r))]
els) MSStatement r -> [MSStatement r] -> [MSStatement r]
forall a. a -> [a] -> [a]
: [MSStatement r]
l
convStmtProc (FAsg Input
v CodeExpr
e) = do
VS (r (Value r))
e' <- CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
e
StateT ValueState Identity (r (Variable r))
v' <- Input
-> StateT
DrasilState Identity (StateT ValueState Identity (r (Variable r)))
forall (r :: * -> *).
SharedProg r =>
Input -> GenState (SVariable r)
mkVarProc Input
v
[MSStatement r]
l <- StateT ValueState Identity (r (Variable r))
-> StateT DrasilState Identity [MSStatement r]
forall (r :: * -> *).
SharedProg r =>
SVariable r -> GenState [MSStatement r]
maybeLog StateT ValueState Identity (r (Variable r))
v'
MSStatement r -> GenState (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (MSStatement r -> GenState (MSStatement r))
-> MSStatement r -> GenState (MSStatement r)
forall a b. (a -> b) -> a -> b
$ [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
$ StateT ValueState Identity (r (Variable r))
-> VS (r (Value r)) -> MSStatement r
forall (r :: * -> *).
AssignStatement r =>
SVariable r -> SValue r -> MSStatement r
assign StateT ValueState Identity (r (Variable r))
v' VS (r (Value r))
e' MSStatement r -> [MSStatement r] -> [MSStatement r]
forall a. a -> [a] -> [a]
: [MSStatement r]
l
convStmtProc (FAsgIndex Input
v Integer
i CodeExpr
e) = do
VS (r (Value r))
e' <- CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
e
StateT ValueState Identity (r (Variable r))
v' <- Input
-> StateT
DrasilState Identity (StateT ValueState Identity (r (Variable r)))
forall (r :: * -> *).
SharedProg r =>
Input -> GenState (SVariable r)
mkVarProc Input
v
CodeType
t <- Input -> GenState CodeType
forall c. HasSpace c => c -> GenState CodeType
codeType Input
v
let asgFunc :: CodeType -> MSStatement r
asgFunc (C.List CodeType
_) = VS (r (Value r)) -> MSStatement r
forall (r :: * -> *). StatementSym r => SValue r -> MSStatement r
valStmt (VS (r (Value r)) -> MSStatement r)
-> VS (r (Value r)) -> MSStatement r
forall a b. (a -> b) -> a -> b
$ VS (r (Value r))
-> VS (r (Value r)) -> VS (r (Value r)) -> VS (r (Value r))
forall (r :: * -> *).
List r =>
SValue r -> SValue r -> SValue r -> SValue r
listSet (StateT ValueState Identity (r (Variable r)) -> VS (r (Value r))
forall (r :: * -> *). VariableValue r => SVariable r -> SValue r
valueOf StateT ValueState Identity (r (Variable r))
v') (Integer -> VS (r (Value r))
forall (r :: * -> *). Literal r => Integer -> SValue r
litInt Integer
i) VS (r (Value r))
e'
asgFunc (C.Array CodeType
_) = StateT ValueState Identity (r (Variable r))
-> VS (r (Value r)) -> MSStatement r
forall (r :: * -> *).
AssignStatement r =>
SVariable r -> SValue r -> MSStatement r
assign (Integer
-> StateT ValueState Identity (r (Variable r))
-> StateT ValueState Identity (r (Variable r))
forall (r :: * -> *).
VariableSym r =>
Integer -> SVariable r -> SVariable r
arrayElem Integer
i StateT ValueState Identity (r (Variable r))
v') VS (r (Value r))
e'
asgFunc CodeType
_ = Name -> MSStatement r
forall a. HasCallStack => Name -> a
error Name
"FAsgIndex used with non-indexed value"
vi :: StateT ValueState Identity (r (Variable r))
vi = Integer
-> StateT ValueState Identity (r (Variable r))
-> StateT ValueState Identity (r (Variable r))
forall (r :: * -> *).
VariableSym r =>
Integer -> SVariable r -> SVariable r
arrayElem Integer
i StateT ValueState Identity (r (Variable r))
v'
[MSStatement r]
l <- StateT ValueState Identity (r (Variable r))
-> StateT DrasilState Identity [MSStatement r]
forall (r :: * -> *).
SharedProg r =>
SVariable r -> GenState [MSStatement r]
maybeLog StateT ValueState Identity (r (Variable r))
vi
MSStatement r -> GenState (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (MSStatement r -> GenState (MSStatement r))
-> MSStatement r -> GenState (MSStatement r)
forall a b. (a -> b) -> a -> b
$ [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
asgFunc CodeType
t MSStatement r -> [MSStatement r] -> [MSStatement r]
forall a. a -> [a] -> [a]
: [MSStatement r]
l
convStmtProc (FFor Input
v CodeExpr
start CodeExpr
end CodeExpr
step [FuncStmt]
st) = do
[MSStatement r]
stmts <- (FuncStmt -> GenState (MSStatement r))
-> [FuncStmt] -> StateT DrasilState Identity [MSStatement r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FuncStmt -> GenState (MSStatement r)
forall (r :: * -> *).
SharedProg r =>
FuncStmt -> GenState (MSStatement r)
convStmtProc [FuncStmt]
st
StateT ValueState Identity (r (Variable r))
vari <- Input
-> StateT
DrasilState Identity (StateT ValueState Identity (r (Variable r)))
forall (r :: * -> *).
SharedProg r =>
Input -> GenState (SVariable r)
mkVarProc Input
v
VS (r (Value r))
start' <- CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
start
VS (r (Value r))
end' <- CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
end
VS (r (Value r))
step' <- CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
step
MSStatement r -> GenState (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (MSStatement r -> GenState (MSStatement r))
-> MSStatement r -> GenState (MSStatement r)
forall a b. (a -> b) -> a -> b
$ StateT ValueState Identity (r (Variable r))
-> VS (r (Value r))
-> VS (r (Value r))
-> VS (r (Value r))
-> MSBody r
-> MSStatement r
forall (r :: * -> *).
ControlStatement r =>
SVariable r
-> SValue r -> SValue r -> SValue r -> MSBody r -> MSStatement r
forRange StateT ValueState Identity (r (Variable r))
vari VS (r (Value r))
start' VS (r (Value r))
end' VS (r (Value r))
step' ([MSStatement r] -> MSBody r
forall (r :: * -> *). BodySym r => [MSStatement r] -> MSBody r
bodyStatements [MSStatement r]
stmts)
convStmtProc (FForEach Input
v CodeExpr
e [FuncStmt]
st) = do
[MSStatement r]
stmts <- (FuncStmt -> GenState (MSStatement r))
-> [FuncStmt] -> StateT DrasilState Identity [MSStatement r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FuncStmt -> GenState (MSStatement r)
forall (r :: * -> *).
SharedProg r =>
FuncStmt -> GenState (MSStatement r)
convStmtProc [FuncStmt]
st
StateT ValueState Identity (r (Variable r))
vari <- Input
-> StateT
DrasilState Identity (StateT ValueState Identity (r (Variable r)))
forall (r :: * -> *).
SharedProg r =>
Input -> GenState (SVariable r)
mkVarProc Input
v
VS (r (Value r))
e' <- CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
e
MSStatement r -> GenState (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (MSStatement r -> GenState (MSStatement r))
-> MSStatement r -> GenState (MSStatement r)
forall a b. (a -> b) -> a -> b
$ StateT ValueState Identity (r (Variable r))
-> VS (r (Value r)) -> MSBody r -> MSStatement r
forall (r :: * -> *).
ControlStatement r =>
SVariable r -> SValue r -> MSBody r -> MSStatement r
forEach StateT ValueState Identity (r (Variable r))
vari VS (r (Value r))
e' ([MSStatement r] -> MSBody r
forall (r :: * -> *). BodySym r => [MSStatement r] -> MSBody r
bodyStatements [MSStatement r]
stmts)
convStmtProc (FWhile CodeExpr
e [FuncStmt]
st) = do
[MSStatement r]
stmts <- (FuncStmt -> GenState (MSStatement r))
-> [FuncStmt] -> StateT DrasilState Identity [MSStatement r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FuncStmt -> GenState (MSStatement r)
forall (r :: * -> *).
SharedProg r =>
FuncStmt -> GenState (MSStatement r)
convStmtProc [FuncStmt]
st
VS (r (Value r))
e' <- CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
e
MSStatement r -> GenState (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (MSStatement r -> GenState (MSStatement r))
-> MSStatement r -> GenState (MSStatement r)
forall a b. (a -> b) -> a -> b
$ VS (r (Value r)) -> MSBody r -> MSStatement r
forall (r :: * -> *).
ControlStatement r =>
SValue r -> MSBody r -> MSStatement r
while VS (r (Value r))
e' ([MSStatement r] -> MSBody r
forall (r :: * -> *). BodySym r => [MSStatement r] -> MSBody r
bodyStatements [MSStatement r]
stmts)
convStmtProc (FCond CodeExpr
e [FuncStmt]
tSt []) = do
[MSStatement r]
stmts <- (FuncStmt -> GenState (MSStatement r))
-> [FuncStmt] -> StateT DrasilState Identity [MSStatement r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FuncStmt -> GenState (MSStatement r)
forall (r :: * -> *).
SharedProg r =>
FuncStmt -> GenState (MSStatement r)
convStmtProc [FuncStmt]
tSt
VS (r (Value r))
e' <- CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
e
MSStatement r -> GenState (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (MSStatement r -> GenState (MSStatement r))
-> MSStatement r -> GenState (MSStatement r)
forall a b. (a -> b) -> a -> b
$ [(VS (r (Value r)), MSBody r)] -> MSStatement r
forall (r :: * -> *).
ControlStatement r =>
[(SValue r, MSBody r)] -> MSStatement r
ifNoElse [(VS (r (Value r))
e', [MSStatement r] -> MSBody r
forall (r :: * -> *). BodySym r => [MSStatement r] -> MSBody r
bodyStatements [MSStatement r]
stmts)]
convStmtProc (FCond CodeExpr
e [FuncStmt]
tSt [FuncStmt]
eSt) = do
[MSStatement r]
stmt1 <- (FuncStmt -> GenState (MSStatement r))
-> [FuncStmt] -> StateT DrasilState Identity [MSStatement r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FuncStmt -> GenState (MSStatement r)
forall (r :: * -> *).
SharedProg r =>
FuncStmt -> GenState (MSStatement r)
convStmtProc [FuncStmt]
tSt
[MSStatement r]
stmt2 <- (FuncStmt -> GenState (MSStatement r))
-> [FuncStmt] -> StateT DrasilState Identity [MSStatement r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FuncStmt -> GenState (MSStatement r)
forall (r :: * -> *).
SharedProg r =>
FuncStmt -> GenState (MSStatement r)
convStmtProc [FuncStmt]
eSt
VS (r (Value r))
e' <- CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
e
MSStatement r -> GenState (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (MSStatement r -> GenState (MSStatement r))
-> MSStatement r -> GenState (MSStatement r)
forall a b. (a -> b) -> a -> b
$ [(VS (r (Value r)), MSBody r)] -> MSBody r -> MSStatement r
forall (r :: * -> *).
ControlStatement r =>
[(SValue r, MSBody r)] -> MSBody r -> MSStatement r
ifCond [(VS (r (Value r))
e', [MSStatement r] -> MSBody r
forall (r :: * -> *). BodySym r => [MSStatement r] -> MSBody r
bodyStatements [MSStatement r]
stmt1)] ([MSStatement r] -> MSBody r
forall (r :: * -> *). BodySym r => [MSStatement r] -> MSBody r
bodyStatements [MSStatement r]
stmt2)
convStmtProc (FRet CodeExpr
e) = do
VS (r (Value r))
e' <- CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
e
MSStatement r -> GenState (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (MSStatement r -> GenState (MSStatement r))
-> MSStatement r -> GenState (MSStatement r)
forall a b. (a -> b) -> a -> b
$ VS (r (Value r)) -> MSStatement r
forall (r :: * -> *).
ControlStatement r =>
SValue r -> MSStatement r
returnStmt VS (r (Value r))
e'
convStmtProc (FThrow Name
s) = MSStatement r -> GenState (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (MSStatement r -> GenState (MSStatement r))
-> MSStatement r -> GenState (MSStatement r)
forall a b. (a -> b) -> a -> b
$ Name -> MSStatement r
forall (r :: * -> *). ControlStatement r => Name -> MSStatement r
throw Name
s
convStmtProc (FTry [FuncStmt]
t [FuncStmt]
c) = do
[MSStatement r]
stmt1 <- (FuncStmt -> GenState (MSStatement r))
-> [FuncStmt] -> StateT DrasilState Identity [MSStatement r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FuncStmt -> GenState (MSStatement r)
forall (r :: * -> *).
SharedProg r =>
FuncStmt -> GenState (MSStatement r)
convStmtProc [FuncStmt]
t
[MSStatement r]
stmt2 <- (FuncStmt -> GenState (MSStatement r))
-> [FuncStmt] -> StateT DrasilState Identity [MSStatement r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FuncStmt -> GenState (MSStatement r)
forall (r :: * -> *).
SharedProg r =>
FuncStmt -> GenState (MSStatement r)
convStmtProc [FuncStmt]
c
MSStatement r -> GenState (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (MSStatement r -> GenState (MSStatement r))
-> MSStatement r -> GenState (MSStatement r)
forall a b. (a -> b) -> a -> b
$ MSBody r -> MSBody r -> MSStatement r
forall (r :: * -> *).
ControlStatement r =>
MSBody r -> MSBody r -> MSStatement r
tryCatch ([MSStatement r] -> MSBody r
forall (r :: * -> *). BodySym r => [MSStatement r] -> MSBody r
bodyStatements [MSStatement r]
stmt1) ([MSStatement r] -> MSBody r
forall (r :: * -> *). BodySym r => [MSStatement r] -> MSBody r
bodyStatements [MSStatement r]
stmt2)
convStmtProc FuncStmt
FContinue = MSStatement r -> GenState (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return MSStatement r
forall (r :: * -> *). ControlStatement r => MSStatement r
continue
convStmtProc (FDecDef Input
v (Matrix [[]])) = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
let scp :: r (Scope r)
scp = ScopeType -> r (Scope r)
forall (r :: * -> *). SharedProg r => ScopeType -> r (Scope r)
convScope (ScopeType -> r (Scope r)) -> ScopeType -> r (Scope r)
forall a b. (a -> b) -> a -> b
$ DrasilState -> ScopeType
currentScope DrasilState
g
StateT ValueState Identity (r (Variable r))
vari <- Input
-> StateT
DrasilState Identity (StateT ValueState Identity (r (Variable r)))
forall (r :: * -> *).
SharedProg r =>
Input -> GenState (SVariable r)
mkVarProc Input
v
let convDec :: CodeType -> r (Scope r) -> MSStatement r
convDec (C.List CodeType
_) = Integer
-> StateT ValueState Identity (r (Variable r))
-> r (Scope r)
-> MSStatement r
forall (r :: * -> *).
DeclStatement r =>
Integer -> SVariable r -> r (Scope r) -> MSStatement r
listDec Integer
0 StateT ValueState Identity (r (Variable r))
vari
convDec (C.Array CodeType
_) = Integer
-> StateT ValueState Identity (r (Variable r))
-> r (Scope r)
-> MSStatement r
forall (r :: * -> *).
DeclStatement r =>
Integer -> SVariable r -> r (Scope r) -> MSStatement r
arrayDec Integer
0 StateT ValueState Identity (r (Variable r))
vari
convDec CodeType
_ = StateT ValueState Identity (r (Variable r))
-> r (Scope r) -> MSStatement r
forall (r :: * -> *).
DeclStatement r =>
SVariable r -> r (Scope r) -> MSStatement r
varDec StateT ValueState Identity (r (Variable r))
vari
(CodeType -> MSStatement r)
-> GenState CodeType -> GenState (MSStatement r)
forall a b.
(a -> b)
-> StateT DrasilState Identity a -> StateT DrasilState Identity b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (CodeType -> r (Scope r) -> MSStatement r
`convDec` r (Scope r)
scp) (Input -> GenState CodeType
forall c. HasSpace c => c -> GenState CodeType
codeType Input
v)
convStmtProc (FDecDef Input
v CodeExpr
e) = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
let scp :: r (Scope r)
scp = ScopeType -> r (Scope r)
forall (r :: * -> *). SharedProg r => ScopeType -> r (Scope r)
convScope (ScopeType -> r (Scope r)) -> ScopeType -> r (Scope r)
forall a b. (a -> b) -> a -> b
$ DrasilState -> ScopeType
currentScope DrasilState
g
StateT ValueState Identity (r (Variable r))
v' <- Input
-> StateT
DrasilState Identity (StateT ValueState Identity (r (Variable r)))
forall (r :: * -> *).
SharedProg r =>
Input -> GenState (SVariable r)
mkVarProc Input
v
[MSStatement r]
l <- StateT ValueState Identity (r (Variable r))
-> StateT DrasilState Identity [MSStatement r]
forall (r :: * -> *).
SharedProg r =>
SVariable r -> GenState [MSStatement r]
maybeLog StateT ValueState Identity (r (Variable r))
v'
CodeType
t <- Input -> GenState CodeType
forall c. HasSpace c => c -> GenState CodeType
codeType Input
v
let convDecDef :: CodeExpr -> GenState (MSStatement r)
convDecDef (Matrix [[CodeExpr]
lst]) = do
let contDecDef :: CodeType
-> SVariable r -> r (Scope r) -> [SValue r] -> MSStatement r
contDecDef (C.List CodeType
_) = SVariable r -> r (Scope r) -> [SValue r] -> MSStatement r
forall (r :: * -> *).
DeclStatement r =>
SVariable r -> r (Scope r) -> [SValue r] -> MSStatement r
listDecDef
contDecDef (C.Array CodeType
_) = SVariable r -> r (Scope r) -> [SValue r] -> MSStatement r
forall (r :: * -> *).
DeclStatement r =>
SVariable r -> r (Scope r) -> [SValue r] -> MSStatement r
arrayDecDef
contDecDef CodeType
_ = Name -> SVariable r -> r (Scope r) -> [SValue r] -> MSStatement r
forall a. HasCallStack => Name -> a
error Name
"Type mismatch between variable and value in declare-define FuncStmt"
[VS (r (Value r))]
e' <- (CodeExpr -> StateT DrasilState Identity (VS (r (Value r))))
-> [CodeExpr] -> StateT DrasilState Identity [VS (r (Value r))]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc [CodeExpr]
lst
MSStatement r -> GenState (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (MSStatement r -> GenState (MSStatement r))
-> MSStatement r -> GenState (MSStatement r)
forall a b. (a -> b) -> a -> b
$ CodeType
-> StateT ValueState Identity (r (Variable r))
-> r (Scope r)
-> [VS (r (Value r))]
-> MSStatement r
forall {r :: * -> *}.
DeclStatement r =>
CodeType
-> SVariable r -> r (Scope r) -> [SValue r] -> MSStatement r
contDecDef CodeType
t StateT ValueState Identity (r (Variable r))
v' r (Scope r)
scp [VS (r (Value r))]
e'
convDecDef CodeExpr
_ = do
VS (r (Value r))
e' <- CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
e
MSStatement r -> GenState (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (MSStatement r -> GenState (MSStatement r))
-> MSStatement r -> GenState (MSStatement r)
forall a b. (a -> b) -> a -> b
$ StateT ValueState Identity (r (Variable r))
-> r (Scope r) -> VS (r (Value r)) -> MSStatement r
forall (r :: * -> *).
DeclStatement r =>
SVariable r -> r (Scope r) -> SValue r -> MSStatement r
varDecDef StateT ValueState Identity (r (Variable r))
v' r (Scope r)
scp VS (r (Value r))
e'
MSStatement r
dd <- CodeExpr -> GenState (MSStatement r)
convDecDef CodeExpr
e
MSStatement r -> GenState (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (MSStatement r -> GenState (MSStatement r))
-> MSStatement r -> GenState (MSStatement r)
forall a b. (a -> b) -> a -> b
$ [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
$ MSStatement r
dd MSStatement r -> [MSStatement r] -> [MSStatement r]
forall a. a -> [a] -> [a]
: [MSStatement r]
l
convStmtProc (FFuncDef CodeFuncChunk
f [ParameterChunk]
ps [FuncStmt]
sts) = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
let scp :: r (Scope r)
scp = ScopeType -> r (Scope r)
forall (r :: * -> *). SharedProg r => ScopeType -> r (Scope r)
convScope (ScopeType -> r (Scope r)) -> ScopeType -> r (Scope r)
forall a b. (a -> b) -> a -> b
$ DrasilState -> ScopeType
currentScope DrasilState
g
StateT ValueState Identity (r (Variable r))
f' <- Input
-> StateT
DrasilState Identity (StateT ValueState Identity (r (Variable r)))
forall (r :: * -> *).
SharedProg r =>
Input -> GenState (SVariable r)
mkVarProc (CodeFuncChunk -> Input
forall c. (Quantity c, MayHaveUnit c) => c -> Input
quantvar CodeFuncChunk
f)
[StateT ValueState Identity (r (Variable r))]
pms <- (ParameterChunk
-> StateT
DrasilState Identity (StateT ValueState Identity (r (Variable r))))
-> [ParameterChunk]
-> StateT
DrasilState Identity [StateT ValueState Identity (r (Variable r))]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (Input
-> StateT
DrasilState Identity (StateT ValueState Identity (r (Variable r)))
forall (r :: * -> *).
SharedProg r =>
Input -> GenState (SVariable r)
mkVarProc (Input
-> StateT
DrasilState Identity (StateT ValueState Identity (r (Variable r))))
-> (ParameterChunk -> Input)
-> ParameterChunk
-> StateT
DrasilState Identity (StateT ValueState Identity (r (Variable r)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParameterChunk -> Input
forall c. (Quantity c, MayHaveUnit c) => c -> Input
quantvar) [ParameterChunk]
ps
[MSStatement r]
b <- (FuncStmt -> GenState (MSStatement r))
-> [FuncStmt] -> StateT DrasilState Identity [MSStatement r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FuncStmt -> GenState (MSStatement r)
forall (r :: * -> *).
SharedProg r =>
FuncStmt -> GenState (MSStatement r)
convStmtProc [FuncStmt]
sts
MSStatement r -> GenState (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (MSStatement r -> GenState (MSStatement r))
-> MSStatement r -> GenState (MSStatement r)
forall a b. (a -> b) -> a -> b
$ StateT ValueState Identity (r (Variable r))
-> r (Scope r)
-> [StateT ValueState Identity (r (Variable r))]
-> MSBody r
-> MSStatement r
forall (r :: * -> *).
DeclStatement r =>
SVariable r
-> r (Scope r) -> [SVariable r] -> MSBody r -> MSStatement r
funcDecDef StateT ValueState Identity (r (Variable r))
f' r (Scope r)
scp [StateT ValueState Identity (r (Variable r))]
pms ([MSStatement r] -> MSBody r
forall (r :: * -> *). BodySym r => [MSStatement r] -> MSBody r
bodyStatements [MSStatement r]
b)
convStmtProc (FVal CodeExpr
e) = do
VS (r (Value r))
e' <- CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
e
MSStatement r -> GenState (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (MSStatement r -> GenState (MSStatement r))
-> MSStatement r -> GenState (MSStatement r)
forall a b. (a -> b) -> a -> b
$ VS (r (Value r)) -> MSStatement r
forall (r :: * -> *). StatementSym r => SValue r -> MSStatement r
valStmt VS (r (Value r))
e'
convStmtProc (FMulti [FuncStmt]
ss) = do
[MSStatement r]
stmts <- (FuncStmt -> GenState (MSStatement r))
-> [FuncStmt] -> StateT DrasilState Identity [MSStatement r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FuncStmt -> GenState (MSStatement r)
forall (r :: * -> *).
SharedProg r =>
FuncStmt -> GenState (MSStatement r)
convStmtProc [FuncStmt]
ss
MSStatement r -> GenState (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (MSStatement r -> GenState (MSStatement r))
-> MSStatement r -> GenState (MSStatement r)
forall a b. (a -> b) -> a -> b
$ [MSStatement r] -> MSStatement r
forall (r :: * -> *).
StatementSym r =>
[MSStatement r] -> MSStatement r
multi [MSStatement r]
stmts
convStmtProc (FAppend CodeExpr
a CodeExpr
b) = do
VS (r (Value r))
a' <- CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
a
VS (r (Value r))
b' <- CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *).
SharedProg r =>
CodeExpr -> GenState (SValue r)
convExprProc CodeExpr
b
MSStatement r -> GenState (MSStatement r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (MSStatement r -> GenState (MSStatement r))
-> MSStatement r -> GenState (MSStatement r)
forall a b. (a -> b) -> a -> b
$ VS (r (Value r)) -> MSStatement r
forall (r :: * -> *). StatementSym r => SValue r -> MSStatement r
valStmt (VS (r (Value r)) -> MSStatement r)
-> VS (r (Value r)) -> MSStatement r
forall a b. (a -> b) -> a -> b
$ VS (r (Value r)) -> VS (r (Value r)) -> VS (r (Value r))
forall (r :: * -> *). List r => SValue r -> SValue r -> SValue r
listAppend VS (r (Value r))
a' VS (r (Value r))
b'
genDataFuncProc :: (SharedProg r) => Name -> Description -> DataDesc ->
GenState (SMethod r)
genDataFuncProc :: forall (r :: * -> *).
SharedProg r =>
Name -> Name -> DataDesc -> GenState (SMethod r)
genDataFuncProc Name
nameTitle Name
desc DataDesc
ddef = do
let parms :: [Input]
parms = DataDesc -> [Input]
getInputs DataDesc
ddef
[MS (r (Block r))]
bod <- DataDesc -> StateT DrasilState Identity [MS (r (Block r))]
forall (r :: * -> *).
SharedProg r =>
DataDesc -> GenState [MSBlock r]
readDataProc DataDesc
ddef
Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MS (r (Block r))]
-> GenState (SMethod r)
forall (r :: * -> *).
SharedProg r =>
Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
publicFuncProc Name
nameTitle VSType r
forall (r :: * -> *). TypeSym r => VSType r
void Name
desc ((Input -> ParameterChunk) -> [Input] -> [ParameterChunk]
forall a b. (a -> b) -> [a] -> [b]
map Input -> ParameterChunk
forall c. CodeIdea c => c -> ParameterChunk
pcAuto ([Input] -> [ParameterChunk]) -> [Input] -> [ParameterChunk]
forall a b. (a -> b) -> a -> b
$ QuantityDict -> Input
forall c. (Quantity c, MayHaveUnit c) => c -> Input
quantvar QuantityDict
inFileName Input -> [Input] -> [Input]
forall a. a -> [a] -> [a]
: [Input]
parms)
Maybe Name
forall a. Maybe a
Nothing [MS (r (Block r))]
bod
publicInOutFuncProc :: (SharedProg r) => Label -> Description -> [CodeVarChunk] ->
[CodeVarChunk] -> [MSBlock r] -> GenState (SMethod r)
publicInOutFuncProc :: forall (r :: * -> *).
SharedProg r =>
Name
-> Name
-> [Input]
-> [Input]
-> [MSBlock r]
-> GenState (SMethod r)
publicInOutFuncProc Name
n = ([SVariable r]
-> [SVariable r]
-> [SVariable r]
-> MSBody r
-> StateT MethodState Identity (r (Method r)))
-> (Name
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> MSBody r
-> StateT MethodState Identity (r (Method r)))
-> Name
-> Name
-> [Input]
-> [Input]
-> [StateT MethodState Identity (r (Block r))]
-> StateT
DrasilState Identity (StateT MethodState Identity (r (Method r)))
forall (r :: * -> *).
SharedProg r =>
([SVariable r]
-> [SVariable r] -> [SVariable r] -> MSBody r -> SMethod r)
-> (Name
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> MSBody r
-> SMethod r)
-> Name
-> Name
-> [Input]
-> [Input]
-> [MSBlock r]
-> GenState (SMethod r)
genInOutFuncProc (Name
-> r (Visibility r)
-> [SVariable r]
-> [SVariable r]
-> [SVariable r]
-> MSBody r
-> StateT MethodState Identity (r (Method r))
forall (r :: * -> *).
MethodSym r =>
Name -> r (Visibility r) -> InOutFunc r
inOutFunc Name
n r (Visibility r)
forall (r :: * -> *). VisibilitySym r => r (Visibility r)
public) (Name
-> r (Visibility r)
-> Name
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> MSBody r
-> StateT MethodState Identity (r (Method r))
forall (r :: * -> *).
MethodSym r =>
Name -> r (Visibility r) -> DocInOutFunc r
docInOutFunc Name
n r (Visibility r)
forall (r :: * -> *). VisibilitySym r => r (Visibility r)
public) Name
n
privateInOutFuncProc :: (SharedProg r) => Label -> Description -> [CodeVarChunk] ->
[CodeVarChunk] -> [MSBlock r] -> GenState (SMethod r)
privateInOutFuncProc :: forall (r :: * -> *).
SharedProg r =>
Name
-> Name
-> [Input]
-> [Input]
-> [MSBlock r]
-> GenState (SMethod r)
privateInOutFuncProc Name
n = ([SVariable r]
-> [SVariable r]
-> [SVariable r]
-> MSBody r
-> StateT MethodState Identity (r (Method r)))
-> (Name
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> MSBody r
-> StateT MethodState Identity (r (Method r)))
-> Name
-> Name
-> [Input]
-> [Input]
-> [StateT MethodState Identity (r (Block r))]
-> StateT
DrasilState Identity (StateT MethodState Identity (r (Method r)))
forall (r :: * -> *).
SharedProg r =>
([SVariable r]
-> [SVariable r] -> [SVariable r] -> MSBody r -> SMethod r)
-> (Name
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> MSBody r
-> SMethod r)
-> Name
-> Name
-> [Input]
-> [Input]
-> [MSBlock r]
-> GenState (SMethod r)
genInOutFuncProc (Name
-> r (Visibility r)
-> [SVariable r]
-> [SVariable r]
-> [SVariable r]
-> MSBody r
-> StateT MethodState Identity (r (Method r))
forall (r :: * -> *).
MethodSym r =>
Name -> r (Visibility r) -> InOutFunc r
inOutFunc Name
n r (Visibility r)
forall (r :: * -> *). VisibilitySym r => r (Visibility r)
private) (Name
-> r (Visibility r)
-> Name
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> MSBody r
-> StateT MethodState Identity (r (Method r))
forall (r :: * -> *).
MethodSym r =>
Name -> r (Visibility r) -> DocInOutFunc r
docInOutFunc Name
n r (Visibility r)
forall (r :: * -> *). VisibilitySym r => r (Visibility r)
private) Name
n
genInOutFuncProc :: (SharedProg r) => ([SVariable r] -> [SVariable r] ->
[SVariable r] -> MSBody r -> SMethod r) ->
(String -> [(String, SVariable r)] -> [(String, SVariable r)] ->
[(String, SVariable r)] -> MSBody r -> SMethod r)
-> Label -> Description -> [CodeVarChunk] -> [CodeVarChunk] ->
[MSBlock r] -> GenState (SMethod r)
genInOutFuncProc :: forall (r :: * -> *).
SharedProg r =>
([SVariable r]
-> [SVariable r] -> [SVariable r] -> MSBody r -> SMethod r)
-> (Name
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> MSBody r
-> SMethod r)
-> Name
-> Name
-> [Input]
-> [Input]
-> [MSBlock r]
-> GenState (SMethod r)
genInOutFuncProc [SVariable r]
-> [SVariable r] -> [SVariable r] -> MSBody r -> SMethod r
f Name
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> MSBody r
-> SMethod r
docf Name
n Name
desc [Input]
ins' [Input]
outs' [MSBlock r]
b = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
(DrasilState -> DrasilState) -> StateT DrasilState Identity ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\DrasilState
st -> DrasilState
st {currentScope = Local})
let ins :: [Input]
ins = [Input]
ins' [Input] -> [Input] -> [Input]
forall a. Eq a => [a] -> [a] -> [a]
\\ [Input]
outs'
outs :: [Input]
outs = [Input]
outs' [Input] -> [Input] -> [Input]
forall a. Eq a => [a] -> [a] -> [a]
\\ [Input]
ins'
both :: [Input]
both = [Input]
ins' [Input] -> [Input] -> [Input]
forall a. Eq a => [a] -> [a] -> [a]
`intersect` [Input]
outs'
[SVariable r]
inVs <- (Input -> StateT DrasilState Identity (SVariable r))
-> [Input] -> StateT DrasilState Identity [SVariable r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Input -> StateT DrasilState Identity (SVariable r)
forall (r :: * -> *).
SharedProg r =>
Input -> GenState (SVariable r)
mkVarProc [Input]
ins
[SVariable r]
outVs <- (Input -> StateT DrasilState Identity (SVariable r))
-> [Input] -> StateT DrasilState Identity [SVariable r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Input -> StateT DrasilState Identity (SVariable r)
forall (r :: * -> *).
SharedProg r =>
Input -> GenState (SVariable r)
mkVarProc [Input]
outs
[SVariable r]
bothVs <- (Input -> StateT DrasilState Identity (SVariable r))
-> [Input] -> StateT DrasilState Identity [SVariable r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Input -> StateT DrasilState Identity (SVariable r)
forall (r :: * -> *).
SharedProg r =>
Input -> GenState (SVariable r)
mkVarProc [Input]
both
MSBody r
bod <- Name
-> [SVariable r]
-> [MSBlock r]
-> StateT DrasilState Identity (MSBody r)
forall (r :: * -> *).
SharedProg r =>
Name -> [SVariable r] -> [MSBlock r] -> GenState (MSBody r)
logBody Name
n ([SVariable r]
bothVs [SVariable r] -> [SVariable r] -> [SVariable r]
forall a. [a] -> [a] -> [a]
++ [SVariable r]
inVs) [MSBlock r]
b
[Name]
pComms <- (Input -> GenState Name)
-> [Input] -> StateT DrasilState Identity [Name]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Input -> GenState Name
forall c. CodeIdea c => c -> GenState Name
getComment [Input]
ins
[Name]
oComms <- (Input -> GenState Name)
-> [Input] -> StateT DrasilState Identity [Name]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Input -> GenState Name
forall c. CodeIdea c => c -> GenState Name
getComment [Input]
outs
[Name]
bComms <- (Input -> GenState Name)
-> [Input] -> StateT DrasilState Identity [Name]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Input -> GenState Name
forall c. CodeIdea c => c -> GenState Name
getComment [Input]
both
SMethod r -> GenState (SMethod r)
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (SMethod r -> GenState (SMethod r))
-> SMethod r -> GenState (SMethod r)
forall a b. (a -> b) -> a -> b
$ if Comments
CommentFunc Comments -> [Comments] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` DrasilState -> [Comments]
commented DrasilState
g
then Name
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> MSBody r
-> SMethod r
docf Name
desc ([Name] -> [SVariable r] -> [(Name, SVariable r)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Name]
pComms [SVariable r]
inVs) ([Name] -> [SVariable r] -> [(Name, SVariable r)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Name]
oComms [SVariable r]
outVs) ([Name] -> [SVariable r] -> [(Name, SVariable r)]
forall a b. [a] -> [b] -> [(a, b)]
zip
[Name]
bComms [SVariable r]
bothVs) MSBody r
bod else [SVariable r]
-> [SVariable r] -> [SVariable r] -> MSBody r -> SMethod r
f [SVariable r]
inVs [SVariable r]
outVs [SVariable r]
bothVs MSBody r
bod
l_line, l_lines, l_linetokens, l_infile, l_i :: Label
var_line, var_lines, var_linetokens, var_infile, var_i ::
(SharedProg r) => SVariable r
v_line, v_lines, v_linetokens, v_infile, v_i ::
(SharedProg r) => SValue r
l_line :: Name
l_line = Name
"line"
var_line :: forall (r :: * -> *). SharedProg r => SVariable r
var_line = Name -> VSType r -> StateT ValueState Identity (r (Variable r))
forall (r :: * -> *).
VariableSym r =>
Name -> VSType r -> SVariable r
var Name
l_line VSType r
forall (r :: * -> *). TypeSym r => VSType r
string
v_line :: forall (r :: * -> *). SharedProg r => SValue r
v_line = SVariable r -> StateT ValueState Identity (r (Value r))
forall (r :: * -> *). VariableValue r => SVariable r -> SValue r
valueOf SVariable r
forall (r :: * -> *). SharedProg r => SVariable r
var_line
l_lines :: Name
l_lines = Name
"lines"
var_lines :: forall (r :: * -> *). SharedProg r => SVariable r
var_lines = Name -> VSType r -> StateT ValueState Identity (r (Variable r))
forall (r :: * -> *).
VariableSym r =>
Name -> VSType r -> SVariable r
var Name
l_lines (VSType r -> VSType r
forall (r :: * -> *). TypeSym r => VSType r -> VSType r
listType VSType r
forall (r :: * -> *). TypeSym r => VSType r
string)
v_lines :: forall (r :: * -> *). SharedProg r => SValue r
v_lines = SVariable r -> StateT ValueState Identity (r (Value r))
forall (r :: * -> *). VariableValue r => SVariable r -> SValue r
valueOf SVariable r
forall (r :: * -> *). SharedProg r => SVariable r
var_lines
l_linetokens :: Name
l_linetokens = Name
"linetokens"
var_linetokens :: forall (r :: * -> *). SharedProg r => SVariable r
var_linetokens = Name -> VSType r -> StateT ValueState Identity (r (Variable r))
forall (r :: * -> *).
VariableSym r =>
Name -> VSType r -> SVariable r
var Name
l_linetokens (VSType r -> VSType r
forall (r :: * -> *). TypeSym r => VSType r -> VSType r
listType VSType r
forall (r :: * -> *). TypeSym r => VSType r
string)
v_linetokens :: forall (r :: * -> *). SharedProg r => SValue r
v_linetokens = SVariable r -> StateT ValueState Identity (r (Value r))
forall (r :: * -> *). VariableValue r => SVariable r -> SValue r
valueOf SVariable r
forall (r :: * -> *). SharedProg r => SVariable r
var_linetokens
l_infile :: Name
l_infile = Name
"infile"
var_infile :: forall (r :: * -> *). SharedProg r => SVariable r
var_infile = Name -> VSType r -> StateT ValueState Identity (r (Variable r))
forall (r :: * -> *).
VariableSym r =>
Name -> VSType r -> SVariable r
var Name
l_infile VSType r
forall (r :: * -> *). TypeSym r => VSType r
infile
v_infile :: forall (r :: * -> *). SharedProg r => SValue r
v_infile = SVariable r -> StateT ValueState Identity (r (Value r))
forall (r :: * -> *). VariableValue r => SVariable r -> SValue r
valueOf SVariable r
forall (r :: * -> *). SharedProg r => SVariable r
var_infile
l_i :: Name
l_i = Name
"i"
var_i :: forall (r :: * -> *). SharedProg r => SVariable r
var_i = Name -> VSType r -> StateT ValueState Identity (r (Variable r))
forall (r :: * -> *).
VariableSym r =>
Name -> VSType r -> SVariable r
var Name
l_i VSType r
forall (r :: * -> *). TypeSym r => VSType r
int
v_i :: forall (r :: * -> *). SharedProg r => SValue r
v_i = SVariable r -> StateT ValueState Identity (r (Value r))
forall (r :: * -> *). VariableValue r => SVariable r -> SValue r
valueOf SVariable r
forall (r :: * -> *). SharedProg r => SVariable r
var_i