{-# LANGUAGE PostfixOperators, Rank2Types #-}
{-# OPTIONS_GHC -Wno-redundant-constraints #-}
module Language.Drasil.Code.Imperative.Import (codeType, spaceCodeType,
publicFunc, privateMethod, publicInOutFunc, privateInOutMethod,
genConstructor, mkVar, mkVal, convExpr, convStmt, genModDef, genModFuncs,
genModClasses, readData, renderC
) where
import Language.Drasil (HasSymbol, HasUID(..), HasSpace(..),
Space(..), RealInterval(..), UID, Constraint(..), Inclusive (..))
import Database.Drasil (symbResolve)
import Language.Drasil.CodeExpr (sy, ($<), ($>), ($<=), ($>=), ($&&))
import Language.Drasil.Code.Expr.Development (CodeExpr(..), ArithBinOp(..),
AssocArithOper(..), AssocBoolOper(..), BoolBinOp(..), EqBinOp(..),
LABinOp(..), OrdBinOp(..), UFunc(..), UFuncB(..), UFuncVV(..), UFuncVN(..),
VVNBinOp(..), VVVBinOp(..))
import Language.Drasil.Code.Imperative.Comments (getComment)
import Language.Drasil.Code.Imperative.ConceptMatch (conceptToGOOL)
import Language.Drasil.Code.Imperative.GenerateGOOL (auxClass, fApp, ctorCall,
genModuleWithImports, primaryClass)
import Language.Drasil.Code.Imperative.Helpers (lookupC)
import Language.Drasil.Code.Imperative.Logging (maybeLog, logBody)
import Language.Drasil.Code.Imperative.DrasilState (GenState, DrasilState(..))
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(..))
import Language.Drasil.CodeSpec (CodeSpec(..))
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 GOOL.Drasil (Label, SFile, MSBody, MSBlock, VSType, SVariable, SValue,
MSStatement, MSParameter, SMethod, CSStateVar, SClass, NamedArgs,
Initializers, OOProg, PermanenceSym(..), bodyStatements, BlockSym(..),
TypeSym(..), VariableSym(..), VariableElim(..), ($->), ValueSym(..),
Literal(..), VariableValue(..), NumericExpression(..), BooleanExpression(..),
Comparison(..), ValueExpression(..), objMethodCallMixedArgs, List(..),
StatementSym(..), AssignStatement(..), DeclStatement(..), IOStatement(..),
StringStatement(..), ControlStatement(..), ifNoElse, ScopeSym(..),
ParameterSym(..), MethodSym(..), pubDVar, privDVar, nonInitConstructor,
convType, ScopeTag(..), CodeType(..), onStateValue)
import qualified GOOL.Drasil as C (CodeType(List, Array))
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)
import Control.Lens ((^.))
codeType :: (HasSpace c) => c -> GenState CodeType
codeType :: c -> GenState CodeType
codeType c :: 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 => Lens' c Space
typ)
spaceCodeType :: Space -> GenState CodeType
spaceCodeType :: Space -> GenState CodeType
spaceCodeType s :: 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 :: UID -> Name -> VSType r -> GenState (SValue r)
value u :: UID
u s :: Name
s t :: 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 -> ConstantMap
constMap CodeSpec
cs
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 Inline m :: a
m = a -> Maybe a
forall a. a -> Maybe a
Just a
m
maybeInline _ _ = 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
codeExpr)) Maybe CodeDefinition
constDef
SValue r -> GenState (SValue r)
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 :: * -> *). OOProg r => CodeConcept -> SValue r
conceptToGOOL Maybe CodeConcept
cdCncpt
variable :: (OOProg r) => Name -> VSType r -> GenState (SVariable r)
variable :: Name -> VSType r -> GenState (SVariable r)
variable s :: Name
s t :: 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 -> VS (r (Type r)) -> VS (r (Variable r))
defFunc Var = Name -> VS (r (Type r)) -> VS (r (Variable r))
forall (r :: * -> *).
VariableSym r =>
Name -> VSType r -> SVariable r
var
defFunc Const = Name -> VS (r (Type r)) -> VS (r (Variable r))
forall (r :: * -> *).
VariableSym r =>
Name -> VSType r -> SVariable r
staticVar
if Name
s Name -> [Name] -> 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 -> [Input]
inputs CodeSpec
cs)
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 (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 -> [CodeDefinition]
constants (CodeSpec -> [CodeDefinition]) -> CodeSpec -> [CodeDefinition]
forall a b. (a -> b) -> a -> b
$ DrasilState -> CodeSpec
codeSpec DrasilState
g)
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 :: * -> *).
VariableSym r =>
ConstantRepr -> Name -> VS (r (Type r)) -> VS (r (Variable 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 (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 :: Structure -> ConstantRepr -> SVariable r -> GenState (SVariable r)
inputVariable Unbundled _ v :: SVariable r
v = SVariable r -> GenState (SVariable r)
forall (m :: * -> *) a. Monad m => a -> m a
return SVariable r
v
inputVariable Bundled Var v :: SVariable r
v = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
let inClsName :: Name
inClsName = "InputParameters"
SVariable r
ip <- Input -> GenState (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 -> GenState (SVariable r)
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
$ 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 :: * -> *). VariableSym r => SVariable r -> SVariable r
objVarSelf SVariable r
v else SVariable r
ip SVariable r -> SVariable r -> SVariable r
forall (r :: * -> *).
VariableSym r =>
SVariable r -> SVariable r -> SVariable r
$-> SVariable r
v
inputVariable Bundled Const v :: SVariable r
v = do
SVariable r
ip <- Input -> GenState (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 -> GenState (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 :: ConstantStructure
-> ConstantRepr -> SVariable r -> GenState (SVariable r)
constVariable (Store Unbundled) _ v :: SVariable r
v = SVariable r -> GenState (SVariable r)
forall (m :: * -> *) a. Monad m => a -> m a
return SVariable r
v
constVariable (Store Bundled) Var v :: SVariable r
v = do
SVariable r
cs <- Input -> GenState (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 -> GenState (SVariable r)
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
cs SVariable r -> SVariable r -> SVariable r
forall (r :: * -> *).
VariableSym r =>
SVariable r -> SVariable r -> SVariable r
$-> SVariable r
v
constVariable (Store Bundled) Const v :: SVariable r
v = do
SVariable r
cs <- Input -> GenState (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 -> GenState (SVariable r)
forall (r :: * -> *).
OOProg r =>
SVariable r -> SVariable r -> GenState (SVariable r)
classVariable SVariable r
cs SVariable r
v
constVariable WithInputs cr :: ConstantRepr
cr v :: SVariable r
v = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
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
cr SVariable r
v
constVariable Inline _ _ = Name -> GenState (SVariable r)
forall a. HasCallStack => Name -> a
error (Name -> GenState (SVariable r)) -> Name -> GenState (SVariable r)
forall a b. (a -> b) -> a -> b
$ "mkVar called on a constant, but user " Name -> Name -> Name
forall a. [a] -> [a] -> [a]
++
"chose to Inline constants. Generator has a bug."
classVariable :: (OOProg r) => SVariable r -> SVariable r ->
GenState (SVariable r)
classVariable :: SVariable r -> SVariable r -> GenState (SVariable r)
classVariable c :: SVariable r
c v :: SVariable r
v = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
let checkCurrent :: Name
-> VS (r (Type r)) -> VS (r (Variable r)) -> VS (r (Variable r))
checkCurrent m :: Name
m = if DrasilState -> Name
currentModule DrasilState
g Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
== Name
m then VS (r (Type r)) -> VS (r (Variable r)) -> VS (r (Variable r))
forall (r :: * -> *).
VariableSym r =>
VSType r -> SVariable r -> SVariable r
classVar else VS (r (Type r)) -> VS (r (Variable r)) -> VS (r (Variable r))
forall (r :: * -> *).
VariableSym r =>
VSType r -> SVariable r -> SVariable r
extClassVar
SVariable r -> GenState (SVariable r)
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
$ "Variable " Name -> Name -> Name
forall a. [a] -> [a] -> [a]
++ Name
nm Name -> Name -> Name
forall a. [a] -> [a] -> [a]
++ " missing from export map")
Name -> State ValueState (r (Type r)) -> SVariable r -> SVariable r
forall (r :: * -> *).
VariableSym r =>
Name
-> VS (r (Type r)) -> VS (r (Variable r)) -> VS (r (Variable 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 :: Input -> GenState (SValue r)
mkVal v :: Input
v = do
CodeType
t <- Input -> GenState CodeType
forall c. HasSpace c => c -> GenState CodeType
codeType Input
v
let toGOOLVal :: Maybe c -> StateT DrasilState Identity (VS (r (Value r)))
toGOOLVal Nothing = UID
-> Name
-> VSType r
-> StateT DrasilState Identity (VS (r (Value 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 => Lens' c 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 o :: c
o) = do
CodeType
ot <- c -> GenState CodeType
forall c. HasSpace c => c -> GenState CodeType
codeType c
o
VS (r (Value r)) -> StateT DrasilState Identity (VS (r (Value r)))
forall (m :: * -> *) a. Monad m => a -> m a
return (VS (r (Value r))
-> StateT DrasilState Identity (VS (r (Value r))))
-> VS (r (Value r))
-> StateT DrasilState Identity (VS (r (Value r)))
forall a b. (a -> b) -> a -> b
$ SVariable r -> VS (r (Value r))
forall (r :: * -> *). VariableValue r => SVariable r -> SValue r
valueOf (SVariable r -> VS (r (Value r)))
-> SVariable r -> VS (r (Value r))
forall a b. (a -> b) -> a -> b
$ SVariable r -> SVariable r -> SVariable r
forall (r :: * -> *).
VariableSym 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 :: * -> *). TypeSym r => CodeType -> VSType r
convType 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 :: * -> *). TypeSym r => CodeType -> VSType r
convType CodeType
t))
Maybe CodeChunk -> GenState (SValue r)
forall (r :: * -> *) c.
(OOProg r, HasSpace c, CodeIdea c) =>
Maybe c -> StateT DrasilState Identity (VS (r (Value 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 :: Input -> GenState (SVariable r)
mkVar v :: Input
v = do
CodeType
t <- Input -> GenState CodeType
forall c. HasSpace c => c -> GenState CodeType
codeType Input
v
let toGOOLVar :: Maybe c -> StateT DrasilState Identity (VS (r (Variable r)))
toGOOLVar Nothing = Name
-> VSType 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) (CodeType -> VSType r
forall (r :: * -> *). TypeSym r => CodeType -> VSType r
convType CodeType
t)
toGOOLVar (Just o :: c
o) = do
CodeType
ot <- c -> GenState CodeType
forall c. HasSpace c => c -> GenState CodeType
codeType c
o
VS (r (Variable r))
-> StateT DrasilState Identity (VS (r (Variable r)))
forall (m :: * -> *) a. Monad m => a -> m a
return (VS (r (Variable r))
-> StateT DrasilState Identity (VS (r (Variable r))))
-> VS (r (Variable r))
-> StateT DrasilState Identity (VS (r (Variable r)))
forall a b. (a -> b) -> a -> b
$ VS (r (Variable r)) -> VS (r (Variable r)) -> VS (r (Variable r))
forall (r :: * -> *).
VariableSym r =>
SVariable r -> SVariable r -> SVariable r
objVar (Name -> VSType r -> VS (r (Variable 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 :: * -> *). TypeSym r => CodeType -> VSType r
convType CodeType
ot))
(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
v) (CodeType -> VSType r
forall (r :: * -> *). TypeSym r => CodeType -> VSType r
convType CodeType
t))
Maybe CodeChunk -> GenState (SVariable r)
forall (r :: * -> *) c.
(OOProg r, HasSpace c, CodeIdea c) =>
Maybe c -> StateT DrasilState Identity (VS (r (Variable 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 :: ParameterChunk -> GenState (MSParameter r)
mkParam p :: ParameterChunk
p = do
VS (r (Variable r))
v <- Input -> GenState (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 (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 Ref = VS (r (Variable r)) -> MS (r (Parameter r))
forall (r :: * -> *).
ParameterSym r =>
SVariable r -> MSParameter r
pointerParam
paramFunc 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 :: Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
publicFunc n :: Name
n t :: VSType r
t = ([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 (Scope r)
-> VSType r
-> [MSParameter r]
-> MSBody r
-> SMethod r
forall (r :: * -> *).
MethodSym r =>
Name
-> r (Scope r)
-> VSType r
-> [MSParameter r]
-> MSBody r
-> SMethod r
function Name
n r (Scope r)
forall (r :: * -> *). ScopeSym r => r (Scope r)
public VSType r
t) Name
n
publicMethod :: (OOProg r) => Label -> VSType r -> Description ->
[ParameterChunk] -> Maybe Description -> [MSBlock r] ->
GenState (SMethod r)
publicMethod :: Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
publicMethod n :: Name
n t :: VSType r
t = ([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 (Scope r)
-> r (Permanence r)
-> VSType r
-> [MSParameter r]
-> MSBody r
-> SMethod r
forall (r :: * -> *).
MethodSym r =>
Name
-> r (Scope r)
-> r (Permanence r)
-> VSType r
-> [MSParameter r]
-> MSBody r
-> SMethod r
method Name
n r (Scope r)
forall (r :: * -> *). ScopeSym r => r (Scope 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 :: Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
privateMethod n :: Name
n t :: VSType r
t = ([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 (Scope r)
-> r (Permanence r)
-> VSType r
-> [MSParameter r]
-> MSBody r
-> SMethod r
forall (r :: * -> *).
MethodSym r =>
Name
-> r (Scope r)
-> r (Permanence r)
-> VSType r
-> [MSParameter r]
-> MSBody r
-> SMethod r
method Name
n r (Scope r)
forall (r :: * -> *). ScopeSym r => r (Scope 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 :: Name
-> Name
-> [Input]
-> [Input]
-> [MSBlock r]
-> GenState (SMethod r)
publicInOutFunc n :: Name
n = ([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)
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 (Scope r)
-> [SVariable r]
-> [SVariable r]
-> [SVariable r]
-> MSBody r
-> SMethod r
forall (r :: * -> *).
MethodSym r =>
Name -> r (Scope r) -> InOutFunc r
inOutFunc Name
n r (Scope r)
forall (r :: * -> *). ScopeSym r => r (Scope r)
public) (Name
-> r (Scope r)
-> Name
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> MSBody r
-> SMethod r
forall (r :: * -> *).
MethodSym r =>
Name -> r (Scope r) -> DocInOutFunc r
docInOutFunc Name
n r (Scope r)
forall (r :: * -> *). ScopeSym r => r (Scope r)
public) Name
n
privateInOutMethod :: (OOProg r) => Label -> Description -> [CodeVarChunk] ->
[CodeVarChunk] -> [MSBlock r] -> GenState (SMethod r)
privateInOutMethod :: Name
-> Name
-> [Input]
-> [Input]
-> [MSBlock r]
-> GenState (SMethod r)
privateInOutMethod n :: Name
n = ([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)
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 (Scope r)
-> r (Permanence r)
-> [SVariable r]
-> [SVariable r]
-> [SVariable r]
-> MSBody r
-> SMethod r
forall (r :: * -> *).
MethodSym r =>
Name -> r (Scope r) -> r (Permanence r) -> InOutFunc r
inOutMethod Name
n r (Scope r)
forall (r :: * -> *). ScopeSym r => r (Scope r)
private r (Permanence r)
forall (r :: * -> *). PermanenceSym r => r (Permanence r)
dynamic) (Name
-> r (Scope r)
-> r (Permanence r)
-> Name
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> MSBody r
-> SMethod r
forall (r :: * -> *).
MethodSym r =>
Name -> r (Scope r) -> r (Permanence r) -> DocInOutFunc r
docInOutMethod Name
n r (Scope r)
forall (r :: * -> *). ScopeSym r => r (Scope 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 :: Name
-> Name -> [ParameterChunk] -> [MSBlock r] -> GenState (SMethod r)
genConstructor n :: Name
n desc :: Name
desc p :: [ParameterChunk]
p = ([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 :: * -> *).
MethodSym 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 :: Name
-> Name
-> [ParameterChunk]
-> Initializers r
-> [MSBlock r]
-> GenState (SMethod r)
genInitConstructor n :: Name
n desc :: Name
desc p :: [ParameterChunk]
p is :: Initializers r
is = ([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] -> Initializers r -> MSBody r -> SMethod r
forall (r :: * -> *).
MethodSym 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 :: ([MSParameter r] -> MSBody r -> SMethod r)
-> Name
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
genMethod f :: [MSParameter r] -> MSBody r -> SMethod r
f n :: Name
n desc :: Name
desc p :: [ParameterChunk]
p r :: Maybe Name
r b :: [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)
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)
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] -> GenState (MSBody r)
forall (r :: * -> *).
OOProg 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 -> StateT DrasilState Identity Name)
-> [ParameterChunk] -> StateT DrasilState Identity [Name]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ParameterChunk -> StateT DrasilState Identity Name
forall c. CodeIdea c => c -> StateT DrasilState Identity Name
getComment [ParameterChunk]
p
SMethod r -> GenState (SMethod r)
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 (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 :: ([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 f :: [SVariable r]
-> [SVariable r] -> [SVariable r] -> MSBody r -> SMethod r
f docf :: Name
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> [(Name, SVariable r)]
-> MSBody r
-> SMethod r
docf n :: Name
n desc :: Name
desc ins' :: [Input]
ins' outs' :: [Input]
outs' b :: [MSBlock r]
b = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
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)
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)
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)
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] -> GenState (MSBody r)
forall (r :: * -> *).
OOProg 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 -> StateT DrasilState Identity Name)
-> [Input] -> StateT DrasilState Identity [Name]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Input -> StateT DrasilState Identity Name
forall c. CodeIdea c => c -> StateT DrasilState Identity Name
getComment [Input]
ins
[Name]
oComms <- (Input -> StateT DrasilState Identity Name)
-> [Input] -> StateT DrasilState Identity [Name]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Input -> StateT DrasilState Identity Name
forall c. CodeIdea c => c -> StateT DrasilState Identity Name
getComment [Input]
outs
[Name]
bComms <- (Input -> StateT DrasilState Identity Name)
-> [Input] -> StateT DrasilState Identity [Name]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Input -> StateT DrasilState Identity Name
forall c. CodeIdea c => c -> StateT DrasilState Identity Name
getComment [Input]
both
SMethod r -> GenState (SMethod r)
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 (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 :: CodeExpr -> GenState (SValue r)
convExpr (Lit (Dbl d :: Double
d)) = do
CodeType
sm <- Space -> GenState CodeType
spaceCodeType Space
Real
let getLiteral :: CodeType -> StateT ValueState Identity (r (Value r))
getLiteral Double = Double -> StateT ValueState Identity (r (Value r))
forall (r :: * -> *). Literal r => Double -> SValue r
litDouble Double
d
getLiteral Float = Float -> StateT ValueState Identity (r (Value r))
forall (r :: * -> *). Literal r => Float -> SValue r
litFloat (Double -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
d)
getLiteral _ = Name -> StateT ValueState Identity (r (Value r))
forall a. HasCallStack => Name -> a
error "convExpr: Real space matched to invalid CodeType; should be Double or Float"
SValue r -> GenState (SValue r)
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 -> StateT ValueState Identity (r (Value r))
getLiteral CodeType
sm
convExpr (Lit (ExactDbl d :: 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 i :: Integer
i)) = SValue r -> GenState (SValue r)
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 s :: Name
s)) = SValue r -> GenState (SValue r)
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 a :: Integer
a b :: Integer
b)) = do
CodeType
sm <- Space -> GenState CodeType
spaceCodeType Space
Rational
let getLiteral :: CodeType -> Double -> VS (r (Value r))
getLiteral Double = Double -> VS (r (Value r))
forall (r :: * -> *). Literal r => Double -> SValue r
litDouble
getLiteral Float = Float -> VS (r (Value r))
forall (r :: * -> *). Literal r => Float -> SValue r
litFloat (Float -> VS (r (Value r)))
-> (Double -> Float) -> Double -> VS (r (Value r))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac
getLiteral _ = Name -> Double -> VS (r (Value r))
forall a. HasCallStack => Name -> a
error "convExpr: Rational space matched to invalid CodeType; should be Double or Float"
SValue r -> GenState (SValue r)
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 -> VS (r (Value 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
/ (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 AddI l :: [CodeExpr]
l) = (SValue r -> SValue r -> SValue r) -> [SValue r] -> SValue r
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)
mapM CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr [CodeExpr]
l
convExpr (AssocA AddRe l :: [CodeExpr]
l) = (SValue r -> SValue r -> SValue r) -> [SValue r] -> SValue r
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)
mapM CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr [CodeExpr]
l
convExpr (AssocA MulI l :: [CodeExpr]
l) = (SValue r -> SValue r -> SValue r) -> [SValue r] -> SValue r
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)
mapM CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr [CodeExpr]
l
convExpr (AssocA MulRe l :: [CodeExpr]
l) = (SValue r -> SValue r -> SValue r) -> [SValue r] -> SValue r
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)
mapM CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr [CodeExpr]
l
convExpr (AssocB And l :: [CodeExpr]
l) = (SValue r -> SValue r -> SValue r) -> [SValue r] -> SValue r
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)
mapM CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr [CodeExpr]
l
convExpr (AssocB Or l :: [CodeExpr]
l) = (SValue r -> SValue r -> SValue r) -> [SValue r] -> SValue r
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)
mapM CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr [CodeExpr]
l
convExpr (C 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 c :: UID
c x :: [CodeExpr]
x ns :: [(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 c :: UID
c x :: [CodeExpr]
x ns :: [(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 (\m :: Name
m _ -> 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)
(\m :: Name
m _ -> Name -> VSType r -> [SValue r] -> NamedArgs r -> SValue r
forall (r :: * -> *). ValueExpression r => MixedCall r
libNewObjMixedArgs Name
m)
convExpr (Message a :: UID
a m :: UID
m x :: [CodeExpr]
x ns :: [(UID, CodeExpr)]
ns) = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
let info :: ChunkDB
info = CodeSpec -> ChunkDB
sysinfodb (CodeSpec -> ChunkDB) -> CodeSpec -> ChunkDB
forall a b. (a -> b) -> a -> b
$ DrasilState -> CodeSpec
codeSpec DrasilState
g
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
(\_ n :: Name
n t :: VSType r
t ps :: [SValue r]
ps nas :: NamedArgs r
nas -> SValue r -> GenState (SValue r)
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))
(\_ n :: Name
n t :: 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 o :: UID
o f :: 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 -> GenState (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 (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 o :: UFunc
o u :: CodeExpr
u) = (SValue r -> SValue r)
-> GenState (SValue r) -> GenState (SValue r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (UFunc -> SValue r -> SValue r
forall (r :: * -> *). OOProg 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 o :: UFuncB
o u :: CodeExpr
u) = (SValue r -> SValue r)
-> GenState (SValue r) -> GenState (SValue r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (UFuncB -> SValue r -> SValue r
forall (r :: * -> *). OOProg 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 o :: UFuncVV
o u :: CodeExpr
u) = (SValue r -> SValue r)
-> GenState (SValue r) -> GenState (SValue r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (UFuncVV -> SValue r -> SValue r
forall (r :: * -> *). OOProg 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 o :: UFuncVN
o u :: CodeExpr
u) = (SValue r -> SValue r)
-> GenState (SValue r) -> GenState (SValue r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (UFuncVN -> SValue r -> SValue r
forall (r :: * -> *). OOProg 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 Frac (Lit (Int a :: Integer
a)) (Lit (Int b :: Integer
b))) = do
CodeType
sm <- Space -> GenState CodeType
spaceCodeType Space
Rational
let getLiteral :: CodeType -> StateT ValueState Identity (r (Value r))
getLiteral Double = Double -> StateT ValueState Identity (r (Value r))
forall (r :: * -> *). Literal r => Double -> SValue r
litDouble (Integer -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
a) StateT ValueState Identity (r (Value r))
-> StateT ValueState Identity (r (Value r))
-> StateT ValueState Identity (r (Value r))
forall (r :: * -> *).
NumericExpression r =>
SValue r -> SValue r -> SValue r
#/ Double -> StateT ValueState Identity (r (Value r))
forall (r :: * -> *). Literal r => Double -> SValue r
litDouble (Integer -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
b)
getLiteral Float = Float -> StateT ValueState Identity (r (Value r))
forall (r :: * -> *). Literal r => Float -> SValue r
litFloat (Integer -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
a) StateT ValueState Identity (r (Value r))
-> StateT ValueState Identity (r (Value r))
-> StateT ValueState Identity (r (Value r))
forall (r :: * -> *).
NumericExpression r =>
SValue r -> SValue r -> SValue r
#/ Float -> StateT ValueState Identity (r (Value r))
forall (r :: * -> *). Literal r => Float -> SValue r
litFloat (Integer -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
b)
getLiteral _ = Name -> StateT ValueState Identity (r (Value r))
forall a. HasCallStack => Name -> a
error "convExpr: Rational space matched to invalid CodeType; should be Double or Float"
SValue r -> GenState (SValue r)
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 -> StateT ValueState Identity (r (Value r))
getLiteral CodeType
sm
convExpr (ArithBinaryOp o :: ArithBinOp
o a :: CodeExpr
a b :: 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 :: * -> *).
OOProg 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 o :: BoolBinOp
o a :: CodeExpr
a b :: 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 o :: LABinOp
o a :: CodeExpr
a b :: 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 :: * -> *).
OOProg 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 o :: EqBinOp
o a :: CodeExpr
a b :: 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 :: * -> *).
OOProg 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 o :: OrdBinOp
o a :: CodeExpr
a b :: 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 :: * -> *).
OOProg 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 o :: VVVBinOp
o a :: CodeExpr
a b :: 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 o :: VVNBinOp
o a :: CodeExpr
a b :: 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 (Case c :: Completeness
c l :: [(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 "should never happen"
doit [(e :: CodeExpr
e,_)] = CodeExpr -> StateT DrasilState Identity (VS (r (Value r)))
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr CodeExpr
e
doit ((e :: CodeExpr
e,cond :: CodeExpr
cond):xs :: [(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 [l :: [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)
mapM CodeExpr -> GenState (SValue r)
forall (r :: * -> *). OOProg r => CodeExpr -> GenState (SValue r)
convExpr [CodeExpr]
l
SValue r -> GenState (SValue r)
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 (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. [a] -> a
head [SValue r]
ar)) [SValue r]
ar
convExpr Matrix{} = Name -> GenState (SValue r)
forall a. HasCallStack => Name -> a
error "convExpr: Matrix"
convExpr Operator{} = Name -> GenState (SValue r)
forall a. HasCallStack => Name -> a
error "convExpr: Operator"
convExpr (RealI c :: UID
c ri :: 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 :: 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 c :: UID
c x :: [CodeExpr]
x ns :: [(UID, CodeExpr)]
ns f :: Name
-> Name
-> VSType r
-> [SValue r]
-> NamedArgs r
-> GenState (SValue r)
f libf :: 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 = CodeSpec -> ChunkDB
sysinfodb (CodeSpec -> ChunkDB) -> CodeSpec -> ChunkDB
forall a b. (a -> b) -> a -> b
$ DrasilState -> CodeSpec
codeSpec DrasilState
g
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)
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)
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)
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
$ "Call to non-existent function " Name -> Name -> Name
forall a. [a] -> [a] -> [a]
++ Name
funcNm)
(\m :: Name
m -> SValue r -> GenState (SValue r)
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))
(\m :: 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)
renderC :: (HasUID c, HasSymbol c) => c -> Constraint CodeExpr -> CodeExpr
renderC :: c -> Constraint CodeExpr -> CodeExpr
renderC s :: c
s (Range _ rr :: 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
renderRealInt :: (HasUID c, HasSymbol c) => c -> RealInterval CodeExpr CodeExpr -> CodeExpr
renderRealInt :: c -> RealInterval CodeExpr CodeExpr -> CodeExpr
renderRealInt s :: c
s (Bounded (Inc, a :: CodeExpr
a) (Inc, b :: CodeExpr
b)) = (CodeExpr
a CodeExpr -> CodeExpr -> CodeExpr
forall r. ExprC r => r -> r -> r
$<= 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 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 s :: c
s (Bounded (Inc, a :: CodeExpr
a) (Exc, b :: CodeExpr
b)) = (CodeExpr
a CodeExpr -> CodeExpr -> CodeExpr
forall r. ExprC r => r -> r -> r
$<= 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 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 s :: c
s (Bounded (Exc, a :: CodeExpr
a) (Inc, b :: CodeExpr
b)) = (CodeExpr
a CodeExpr -> CodeExpr -> CodeExpr
forall r. ExprC r => r -> r -> r
$< 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 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 s :: c
s (Bounded (Exc, a :: CodeExpr
a) (Exc, b :: CodeExpr
b)) = (CodeExpr
a CodeExpr -> CodeExpr -> CodeExpr
forall r. ExprC r => r -> r -> r
$< 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 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 s :: c
s (UpTo (Inc, a :: CodeExpr
a)) = 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 s :: c
s (UpTo (Exc, a :: CodeExpr
a)) = 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 s :: c
s (UpFrom (Inc, a :: CodeExpr
a)) = 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 s :: c
s (UpFrom (Exc, a :: CodeExpr
a)) = 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
unop :: (OOProg r) => UFunc -> (SValue r -> SValue r)
unop :: UFunc -> SValue r -> SValue r
unop Sqrt = SValue r -> SValue r
forall (r :: * -> *). NumericExpression r => SValue r -> SValue r
(#/^)
unop Log = SValue r -> SValue r
forall (r :: * -> *). NumericExpression r => SValue r -> SValue r
log
unop Ln = SValue r -> SValue r
forall (r :: * -> *). NumericExpression r => SValue r -> SValue r
ln
unop Abs = SValue r -> SValue r
forall (r :: * -> *). NumericExpression r => SValue r -> SValue r
(#|)
unop Exp = SValue r -> SValue r
forall (r :: * -> *). NumericExpression r => SValue r -> SValue r
exp
unop Sin = SValue r -> SValue r
forall (r :: * -> *). NumericExpression r => SValue r -> SValue r
sin
unop Cos = SValue r -> SValue r
forall (r :: * -> *). NumericExpression r => SValue r -> SValue r
cos
unop Tan = SValue r -> SValue r
forall (r :: * -> *). NumericExpression r => SValue r -> SValue r
tan
unop Csc = SValue r -> SValue r
forall (r :: * -> *). NumericExpression r => SValue r -> SValue r
csc
unop Sec = SValue r -> SValue r
forall (r :: * -> *). NumericExpression r => SValue r -> SValue r
sec
unop Cot = SValue r -> SValue r
forall (r :: * -> *). NumericExpression r => SValue r -> SValue r
cot
unop Arcsin = SValue r -> SValue r
forall (r :: * -> *). NumericExpression r => SValue r -> SValue r
arcsin
unop Arccos = SValue r -> SValue r
forall (r :: * -> *). NumericExpression r => SValue r -> SValue r
arccos
unop Arctan = SValue r -> SValue r
forall (r :: * -> *). NumericExpression r => SValue r -> SValue r
arctan
unop Neg = SValue r -> SValue r
forall (r :: * -> *). NumericExpression r => SValue r -> SValue r
(#~)
unopB :: (OOProg r) => UFuncB -> (SValue r -> SValue r)
unopB :: UFuncB -> SValue r -> SValue r
unopB Not = SValue r -> SValue r
forall (r :: * -> *). BooleanExpression r => SValue r -> SValue r
(?!)
unopVN :: (OOProg r) => UFuncVN -> (SValue r -> SValue r)
unopVN :: UFuncVN -> SValue r -> SValue r
unopVN Dim = SValue r -> SValue r
forall (r :: * -> *). List r => SValue r -> SValue r
listSize
unopVN Norm = Name -> SValue r -> SValue r
forall a. HasCallStack => Name -> a
error "unop: Norm not implemented"
unopVV :: (OOProg r) => UFuncVV -> (SValue r -> SValue r)
unopVV :: UFuncVV -> SValue r -> SValue r
unopVV NegV = Name -> SValue r -> SValue r
forall a. HasCallStack => Name -> a
error "unop: Negation on Vectors not implemented"
arithBfunc :: (OOProg r) => ArithBinOp -> (SValue r -> SValue r -> SValue r)
arithBfunc :: ArithBinOp -> SValue r -> SValue r -> SValue r
arithBfunc Pow = SValue r -> SValue r -> SValue r
forall (r :: * -> *).
NumericExpression r =>
SValue r -> SValue r -> SValue r
(#^)
arithBfunc Subt = SValue r -> SValue r -> SValue r
forall (r :: * -> *).
NumericExpression r =>
SValue r -> SValue r -> SValue r
(#-)
arithBfunc 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 :: BoolBinOp -> SValue r -> SValue r -> SValue r
boolBfunc Impl = Name -> SValue r -> SValue r -> SValue r
forall a. HasCallStack => Name -> a
error "convExpr :=>"
boolBfunc Iff = Name -> SValue r -> SValue r -> SValue r
forall a. HasCallStack => Name -> a
error "convExpr :<=>"
eqBfunc :: (OOProg r) => EqBinOp -> (SValue r -> SValue r -> SValue r)
eqBfunc :: EqBinOp -> SValue r -> SValue r -> SValue r
eqBfunc Eq = SValue r -> SValue r -> SValue r
forall (r :: * -> *).
Comparison r =>
SValue r -> SValue r -> SValue r
(?==)
eqBfunc NEq = SValue r -> SValue r -> SValue r
forall (r :: * -> *).
Comparison r =>
SValue r -> SValue r -> SValue r
(?!=)
laBfunc :: (OOProg r) => LABinOp -> (SValue r -> SValue r -> SValue r)
laBfunc :: LABinOp -> SValue r -> SValue r -> SValue r
laBfunc Index = SValue r -> SValue r -> SValue r
forall (r :: * -> *). List r => SValue r -> SValue r -> SValue r
listAccess
ordBfunc :: (OOProg r) => OrdBinOp -> (SValue r -> SValue r -> SValue r)
ordBfunc :: OrdBinOp -> SValue r -> SValue r -> SValue r
ordBfunc Gt = SValue r -> SValue r -> SValue r
forall (r :: * -> *).
Comparison r =>
SValue r -> SValue r -> SValue r
(?>)
ordBfunc Lt = SValue r -> SValue r -> SValue r
forall (r :: * -> *).
Comparison r =>
SValue r -> SValue r -> SValue r
(?<)
ordBfunc LEq = SValue r -> SValue r -> SValue r
forall (r :: * -> *).
Comparison r =>
SValue r -> SValue r -> SValue r
(?<=)
ordBfunc 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 :: VVVBinOp -> SValue r -> SValue r -> SValue r
vecVecVecBfunc Cross = Name -> SValue r -> SValue r -> SValue r
forall a. HasCallStack => Name -> a
error "bfunc: Cross not implemented"
vecVecNumBfunc :: VVNBinOp -> (SValue r -> SValue r -> SValue r)
vecVecNumBfunc :: VVNBinOp -> SValue r -> SValue r -> SValue r
vecVecNumBfunc Dot = Name -> SValue r -> SValue r -> SValue r
forall a. HasCallStack => Name -> a
error "convExpr DotProduct"
genModDef :: (OOProg r) => Mod -> GenState (SFile r)
genModDef :: Mod -> GenState (SFile r)
genModDef (Mod n :: Name
n desc :: Name
desc is :: [Name]
is cs :: [Class]
cs fs :: [Func]
fs) = Name
-> Name
-> [Name]
-> [GenState (Maybe (SMethod r))]
-> [GenState (Maybe (SClass r))]
-> GenState (SFile 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 (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 [] -> []
(cl :: Class
cl:cls :: [Class]
cls) -> (SClass r -> Maybe (SClass r))
-> StateT DrasilState Identity (SClass r)
-> GenState (Maybe (SClass r))
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]
-> 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 (SClass r))
-> Class -> GenState (SClass r)
genClass Name
-> Maybe Name
-> Name
-> [CSStateVar r]
-> GenState [SMethod r]
-> StateT DrasilState Identity (SClass r)
forall (r :: * -> *).
OOProg r =>
Name
-> Maybe Name
-> Name
-> [CSStateVar 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 (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]
-> 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 (SClass r))
-> Class -> GenState (SClass r)
genClass Name
-> Maybe Name
-> Name
-> [CSStateVar r]
-> GenState [SMethod r]
-> StateT DrasilState Identity (SClass r)
forall (r :: * -> *).
OOProg r =>
Name
-> Maybe Name
-> Name
-> [CSStateVar r]
-> GenState [SMethod r]
-> GenState (SClass r)
auxClass) [Class]
cls)
genModFuncs :: (OOProg r) => Mod -> [GenState (SMethod r)]
genModFuncs :: Mod -> [GenState (SMethod r)]
genModFuncs (Mod _ _ _ _ fs :: [Func]
fs) = (Func -> GenState (SMethod r)) -> [Func] -> [GenState (SMethod r)]
forall a b. (a -> b) -> [a] -> [b]
map ((Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r))
-> [StateVariable] -> Func -> GenState (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]
-> GenState (SMethod 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 :: Mod -> [GenState (SClass r)]
genModClasses (Mod _ _ _ cs :: [Class]
cs _) = (Class -> GenState (SClass r)) -> [Class] -> [GenState (SClass r)]
forall a b. (a -> b) -> [a] -> [b]
map ((Name
-> Maybe Name
-> Name
-> [CSStateVar r]
-> GenState [SMethod r]
-> GenState (SClass r))
-> Class -> GenState (SClass r)
forall (r :: * -> *).
OOProg r =>
(Name
-> Maybe Name
-> Name
-> [CSStateVar r]
-> GenState [SMethod r]
-> GenState (SClass r))
-> Class -> GenState (SClass r)
genClass Name
-> Maybe Name
-> Name
-> [CSStateVar r]
-> GenState [SMethod r]
-> GenState (SClass r)
forall (r :: * -> *).
OOProg r =>
Name
-> Maybe Name
-> Name
-> [CSStateVar r]
-> GenState [SMethod r]
-> GenState (SClass r)
auxClass) [Class]
cs
genClass :: (OOProg r) => (Name -> Maybe Name -> Description -> [CSStateVar r]
-> GenState [SMethod r] -> GenState (SClass r)) ->
M.Class -> GenState (SClass r)
genClass :: (Name
-> Maybe Name
-> Name
-> [CSStateVar r]
-> GenState [SMethod r]
-> GenState (SClass r))
-> Class -> GenState (SClass r)
genClass f :: Name
-> Maybe Name
-> Name
-> [CSStateVar r]
-> GenState [SMethod r]
-> GenState (SClass r)
f (M.ClassDef n :: Name
n i :: Maybe Name
i desc :: Name
desc svs :: [StateVariable]
svs ms :: [Func]
ms) = let svar :: ScopeTag -> VS (r (Variable r)) -> CS (r (StateVar r))
svar Pub = VS (r (Variable r)) -> CS (r (StateVar r))
forall (r :: * -> *). StateVarSym r => SVariable r -> CSStateVar r
pubDVar
svar Priv = VS (r (Variable r)) -> CS (r (StateVar r))
forall (r :: * -> *). StateVarSym r => SVariable r -> CSStateVar r
privDVar
in do
[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)
mapM (\(SV s :: ScopeTag
s v :: Input
v) -> (CodeType -> CSStateVar r)
-> GenState CodeType -> StateT DrasilState Identity (CSStateVar r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (ScopeTag -> VS (r (Variable r)) -> CSStateVar r
forall (r :: * -> *).
StateVarSym r =>
ScopeTag -> VS (r (Variable r)) -> CS (r (StateVar r))
svar ScopeTag
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 -> 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
v) (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 :: * -> *). TypeSym r => CodeType -> VSType r
convType)
(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 (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)
mapM ((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)
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 :: (Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r))
-> [StateVariable] -> Func -> GenState (SMethod r)
genFunc f :: Name
-> VSType r
-> Name
-> [ParameterChunk]
-> Maybe Name
-> [MSBlock r]
-> GenState (SMethod r)
f svs :: [StateVariable]
svs (FDef (FuncDef n :: Name
n desc :: Name
desc parms :: [ParameterChunk]
parms o :: Space
o rd :: Maybe Name
rd s :: [FuncStmt]
s)) = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
[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)
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)
mapM Input -> StateT DrasilState Identity (VS (r (Variable r)))
forall (r :: * -> *). OOProg r => Input -> GenState (SVariable r)
mkVar (ChunkDB -> [FuncStmt] -> [Input]
fstdecl (CodeSpec -> ChunkDB
sysinfodb (CodeSpec -> ChunkDB) -> CodeSpec -> ChunkDB
forall a b. (a -> b) -> a -> b
$ DrasilState -> CodeSpec
codeSpec DrasilState
g) [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)) -> MS (r (Statement r))
forall (r :: * -> *).
DeclStatement r =>
SVariable r -> MSStatement r
varDec [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 _ svs :: [StateVariable]
svs (FDef (CtorDef n :: Name
n desc :: Name
desc parms :: [ParameterChunk]
parms i :: [Initializer]
i s :: [FuncStmt]
s)) = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
[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)
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)
mapM ((\iv :: Input
iv -> (CodeType -> VS (r (Variable r)))
-> GenState CodeType
-> StateT DrasilState Identity (VS (r (Variable r)))
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 :: * -> *). TypeSym r => CodeType -> VSType r
convType) (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)
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)
mapM Input -> StateT DrasilState Identity (VS (r (Variable r)))
forall (r :: * -> *). OOProg r => Input -> GenState (SVariable r)
mkVar (ChunkDB -> [FuncStmt] -> [Input]
fstdecl (CodeSpec -> ChunkDB
sysinfodb (CodeSpec -> ChunkDB) -> CodeSpec -> ChunkDB
forall a b. (a -> b) -> a -> b
$ DrasilState -> CodeSpec
codeSpec DrasilState
g) [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)) -> MS (r (Statement r))
forall (r :: * -> *).
DeclStatement r =>
SVariable r -> MSStatement r
varDec [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 _ _ (FData (FuncData n :: Name
n desc :: Name
desc ddef :: DataDesc
ddef)) = 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 :: FuncStmt -> GenState (MSStatement r)
convStmt (FAsg v :: Input
v (Matrix [es :: [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)
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 -> GenState (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
-> VS (r (Type r)) -> [VS (r (Value r))] -> VS (r (Value r))
listFunc (C.List _) = VS (r (Type r)) -> [VS (r (Value r))] -> VS (r (Value r))
forall (r :: * -> *).
Literal r =>
VSType r -> [SValue r] -> SValue r
litList
listFunc (C.Array _) = VS (r (Type r)) -> [VS (r (Value r))] -> VS (r (Value r))
forall (r :: * -> *).
Literal r =>
VSType r -> [SValue r] -> SValue r
litArray
listFunc _ = Name -> VS (r (Type r)) -> [VS (r (Value r))] -> VS (r (Value r))
forall a. HasCallStack => Name -> a
error "Type mismatch between variable and value in assignment FuncStmt"
[MSStatement r]
l <- StateT ValueState Identity (r (Variable r))
-> GenState [MSStatement r]
forall (r :: * -> *).
OOProg r =>
SVariable r -> GenState [MSStatement r]
maybeLog StateT ValueState Identity (r (Variable r))
v'
MSStatement r -> GenState (MSStatement r)
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
-> VS (r (Type r)) -> [VS (r (Value r))] -> VS (r (Value 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 (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 v :: Input
v e :: 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 -> GenState (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))
-> GenState [MSStatement r]
forall (r :: * -> *).
OOProg r =>
SVariable r -> GenState [MSStatement r]
maybeLog StateT ValueState Identity (r (Variable r))
v'
MSStatement r -> GenState (MSStatement r)
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 v :: Input
v i :: Integer
i e :: 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 -> GenState (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 _) = 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 _) = 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 _ = Name -> MSStatement r
forall a. HasCallStack => Name -> a
error "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))
-> GenState [MSStatement r]
forall (r :: * -> *).
OOProg r =>
SVariable r -> GenState [MSStatement r]
maybeLog StateT ValueState Identity (r (Variable r))
vi
MSStatement r -> GenState (MSStatement r)
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 v :: Input
v start :: CodeExpr
start end :: CodeExpr
end step :: CodeExpr
step st :: [FuncStmt]
st) = do
[MSStatement r]
stmts <- (FuncStmt -> GenState (MSStatement r))
-> [FuncStmt] -> GenState [MSStatement r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t 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 -> GenState (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 (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 v :: Input
v e :: CodeExpr
e st :: [FuncStmt]
st) = do
[MSStatement r]
stmts <- (FuncStmt -> GenState (MSStatement r))
-> [FuncStmt] -> GenState [MSStatement r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t 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 -> GenState (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 (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 e :: CodeExpr
e st :: [FuncStmt]
st) = do
[MSStatement r]
stmts <- (FuncStmt -> GenState (MSStatement r))
-> [FuncStmt] -> GenState [MSStatement r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t 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 (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 e :: CodeExpr
e tSt :: [FuncStmt]
tSt []) = do
[MSStatement r]
stmts <- (FuncStmt -> GenState (MSStatement r))
-> [FuncStmt] -> GenState [MSStatement r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t 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 (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 e :: CodeExpr
e tSt :: [FuncStmt]
tSt eSt :: [FuncStmt]
eSt) = do
[MSStatement r]
stmt1 <- (FuncStmt -> GenState (MSStatement r))
-> [FuncStmt] -> GenState [MSStatement r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t 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] -> GenState [MSStatement r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t 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 (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 e :: 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 (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 s :: Name
s) = MSStatement r -> GenState (MSStatement r)
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 t :: [FuncStmt]
t c :: [FuncStmt]
c) = do
[MSStatement r]
stmt1 <- (FuncStmt -> GenState (MSStatement r))
-> [FuncStmt] -> GenState [MSStatement r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t 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] -> GenState [MSStatement r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM FuncStmt -> GenState (MSStatement r)
forall (r :: * -> *).
OOProg r =>
FuncStmt -> GenState (MSStatement r)
convStmt [FuncStmt]
c
MSStatement r -> GenState (MSStatement r)
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 FContinue = MSStatement r -> GenState (MSStatement r)
forall (m :: * -> *) a. Monad m => a -> m a
return MSStatement r
forall (r :: * -> *). ControlStatement r => MSStatement r
continue
convStmt (FDecDef v :: Input
v (Matrix [[]])) = do
StateT ValueState Identity (r (Variable r))
vari <- Input -> GenState (StateT ValueState Identity (r (Variable r)))
forall (r :: * -> *). OOProg r => Input -> GenState (SVariable r)
mkVar Input
v
let convDec :: CodeType -> MSStatement r
convDec (C.List _) = Integer
-> StateT ValueState Identity (r (Variable r)) -> MSStatement r
forall (r :: * -> *).
DeclStatement r =>
Integer -> SVariable r -> MSStatement r
listDec 0 StateT ValueState Identity (r (Variable r))
vari
convDec (C.Array _) = Integer
-> StateT ValueState Identity (r (Variable r)) -> MSStatement r
forall (r :: * -> *).
DeclStatement r =>
Integer -> SVariable r -> MSStatement r
arrayDec 0 StateT ValueState Identity (r (Variable r))
vari
convDec _ = StateT ValueState Identity (r (Variable r)) -> MSStatement r
forall (r :: * -> *).
DeclStatement r =>
SVariable r -> MSStatement r
varDec StateT ValueState Identity (r (Variable r))
vari
(CodeType -> MSStatement r)
-> GenState CodeType -> GenState (MSStatement r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CodeType -> MSStatement r
convDec (Input -> GenState CodeType
forall c. HasSpace c => c -> GenState CodeType
codeType Input
v)
convStmt (FDecDef v :: Input
v e :: CodeExpr
e) = do
StateT ValueState Identity (r (Variable r))
v' <- Input -> GenState (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))
-> GenState [MSStatement r]
forall (r :: * -> *).
OOProg 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 [lst :: [CodeExpr]
lst]) = do
let contDecDef :: CodeType
-> VS (r (Variable r))
-> [VS (r (Value r))]
-> MS (r (Statement r))
contDecDef (C.List _) = VS (r (Variable r)) -> [VS (r (Value r))] -> MS (r (Statement r))
forall (r :: * -> *).
DeclStatement r =>
SVariable r -> [SValue r] -> MSStatement r
listDecDef
contDecDef (C.Array _) = VS (r (Variable r)) -> [VS (r (Value r))] -> MS (r (Statement r))
forall (r :: * -> *).
DeclStatement r =>
SVariable r -> [SValue r] -> MSStatement r
arrayDecDef
contDecDef _ = Name
-> VS (r (Variable r))
-> [VS (r (Value r))]
-> MS (r (Statement r))
forall a. HasCallStack => Name -> a
error "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)
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 (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))
-> [VS (r (Value r))]
-> MSStatement r
forall (r :: * -> *).
DeclStatement r =>
CodeType
-> VS (r (Variable r))
-> [VS (r (Value r))]
-> MS (r (Statement r))
contDecDef CodeType
t StateT ValueState Identity (r (Variable r))
v' [VS (r (Value r))]
e'
convDecDef _ = 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 (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)) -> MSStatement r
forall (r :: * -> *).
DeclStatement r =>
SVariable r -> SValue r -> MSStatement r
varDecDef StateT ValueState Identity (r (Variable r))
v' VS (r (Value r))
e'
MSStatement r
dd <- CodeExpr -> GenState (MSStatement r)
convDecDef CodeExpr
e
MSStatement r -> GenState (MSStatement r)
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 f :: CodeFuncChunk
f ps :: [ParameterChunk]
ps sts :: [FuncStmt]
sts) = do
StateT ValueState Identity (r (Variable r))
f' <- Input -> GenState (StateT ValueState Identity (r (Variable r)))
forall (r :: * -> *). OOProg r => Input -> GenState (SVariable r)
mkVar (Input -> GenState (StateT ValueState Identity (r (Variable r))))
-> Input -> GenState (StateT ValueState Identity (r (Variable r)))
forall a b. (a -> b) -> a -> b
$ CodeFuncChunk -> Input
forall c. (Quantity c, MayHaveUnit c) => c -> Input
quantvar CodeFuncChunk
f
[StateT ValueState Identity (r (Variable r))]
pms <- (ParameterChunk
-> GenState (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)
mapM (Input -> GenState (StateT ValueState Identity (r (Variable r)))
forall (r :: * -> *). OOProg r => Input -> GenState (SVariable r)
mkVar (Input -> GenState (StateT ValueState Identity (r (Variable r))))
-> (ParameterChunk -> Input)
-> ParameterChunk
-> GenState (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] -> GenState [MSStatement r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM FuncStmt -> GenState (MSStatement r)
forall (r :: * -> *).
OOProg r =>
FuncStmt -> GenState (MSStatement r)
convStmt [FuncStmt]
sts
MSStatement r -> GenState (MSStatement r)
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))
-> [StateT ValueState Identity (r (Variable r))]
-> MSBody r
-> MSStatement r
forall (r :: * -> *).
DeclStatement r =>
SVariable r -> [SVariable r] -> MSBody r -> MSStatement r
funcDecDef StateT ValueState Identity (r (Variable r))
f' [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 e :: 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 (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 ss :: [FuncStmt]
ss) = do
[MSStatement r]
stmts <- (FuncStmt -> GenState (MSStatement r))
-> [FuncStmt] -> GenState [MSStatement r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM FuncStmt -> GenState (MSStatement r)
forall (r :: * -> *).
OOProg r =>
FuncStmt -> GenState (MSStatement r)
convStmt [FuncStmt]
ss
MSStatement r -> GenState (MSStatement r)
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 a :: CodeExpr
a b :: 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 (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 :: Name -> Name -> DataDesc -> GenState (SMethod r)
genDataFunc nameTitle :: Name
nameTitle desc :: Name
desc ddef :: DataDesc
ddef = do
let parms :: [Input]
parms = DataDesc -> [Input]
getInputs DataDesc
ddef
[MS (r (Block r))]
bod <- DataDesc -> GenState [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 :: DataDesc -> GenState [MSBlock r]
readData ddef :: DataDesc
ddef = do
[[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)
mapM Data -> StateT DrasilState Identity [MS (r (Statement r))]
forall (r :: * -> *). OOProg r => Data -> GenState [MSStatement r]
inData DataDesc
ddef
VS (r (Value r))
v_filename <- Input -> GenState (VS (r (Value r)))
forall (r :: * -> *). OOProg r => Input -> GenState (SValue r)
mkVal (Input -> GenState (VS (r (Value r))))
-> Input -> GenState (VS (r (Value r)))
forall a b. (a -> b) -> a -> b
$ QuantityDict -> Input
forall c. (Quantity c, MayHaveUnit c) => c -> Input
quantvar QuantityDict
inFileName
[MSBlock r] -> GenState [MSBlock r]
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 -> MS (r (Statement r))
forall (r :: * -> *).
DeclStatement r =>
SVariable r -> MSStatement r
varDec SVariable r
forall (r :: * -> *). OOProg r => SVariable r
var_infile 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 (\d :: Data
d -> Data -> Bool
isLine Data
d Bool -> Bool -> Bool
|| Data -> Bool
isLines Data
d) DataDesc
ddef then [SVariable r -> MS (r (Statement r))
forall (r :: * -> *).
DeclStatement r =>
SVariable r -> MSStatement r
varDec SVariable r
forall (r :: * -> *). OOProg r => SVariable r
var_line, Integer -> SVariable r -> MS (r (Statement r))
forall (r :: * -> *).
DeclStatement r =>
Integer -> SVariable r -> MSStatement r
listDec 0 SVariable r
forall (r :: * -> *). OOProg r => SVariable r
var_linetokens] else []) [MS (r (Statement r))]
-> [MS (r (Statement r))] -> [MS (r (Statement r))]
forall a. [a] -> [a] -> [a]
++
[Integer -> SVariable r -> MS (r (Statement r))
forall (r :: * -> *).
DeclStatement r =>
Integer -> SVariable r -> MSStatement r
listDec 0 SVariable r
forall (r :: * -> *). OOProg r => SVariable r
var_lines | (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 :: * -> *). OOProg 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 :: * -> *). OOProg r => SValue r
v_infile ]]
where inData :: (OOProg r) => Data -> GenState [MSStatement r]
inData :: Data -> GenState [MSStatement r]
inData (Singleton v :: Input
v) = do
VS (r (Variable r))
vv <- Input -> GenState (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 :: * -> *).
OOProg r =>
SVariable r -> GenState [MSStatement r]
maybeLog VS (r (Variable r))
vv
[MSStatement r] -> GenState [MSStatement r]
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 :: * -> *). OOProg 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 JunkData = [MSStatement r] -> GenState [MSStatement r]
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 :: * -> *). OOProg r => SValue r
v_infile]
inData (Line lp :: LinePattern
lp d :: Delim
d) = do
[MSStatement r]
lnI <- Maybe Name -> LinePattern -> GenState [MSStatement r]
forall (r :: * -> *).
OOProg r =>
Maybe Name -> LinePattern -> GenState [MSStatement r]
lineData Maybe Name
forall a. Maybe a
Nothing LinePattern
lp
[MSStatement r]
logs <- LinePattern -> GenState [MSStatement r]
forall (r :: * -> *).
OOProg r =>
LinePattern -> GenState [MSStatement r]
getEntryVarLogs LinePattern
lp
[MSStatement r] -> GenState [MSStatement r]
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 :: * -> *). OOProg r => SValue r
v_infile VS (r (Variable r))
forall (r :: * -> *). OOProg r => SVariable r
var_line,
Delim -> VS (r (Variable r)) -> SValue r -> MSStatement r
forall (r :: * -> *).
StringStatement r =>
Delim -> SVariable r -> SValue r -> MSStatement r
stringSplit Delim
d VS (r (Variable r))
forall (r :: * -> *). OOProg r => SVariable r
var_linetokens SValue r
forall (r :: * -> *). OOProg 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 lp :: LinePattern
lp ls :: Maybe Integer
ls d :: Delim
d) = do
[MSStatement r]
lnV <- Maybe Name -> LinePattern -> GenState [MSStatement r]
forall (r :: * -> *).
OOProg r =>
Maybe Name -> LinePattern -> GenState [MSStatement r]
lineData (Name -> Maybe Name
forall a. a -> Maybe a
Just "_temp") LinePattern
lp
[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 Nothing = [SValue r -> VS (r (Variable r)) -> MSStatement r
forall (r :: * -> *).
IOStatement r =>
SValue r -> SVariable r -> MSStatement r
getFileInputAll SValue r
forall (r :: * -> *). OOProg r => SValue r
v_infile VS (r (Variable r))
forall (r :: * -> *). OOProg 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 :: * -> *). OOProg r => SVariable r
var_i (Integer -> SValue r
forall (r :: * -> *). Literal r => Integer -> SValue r
litInt 0) (SValue r -> SValue r
forall (r :: * -> *). List r => SValue r -> SValue r
listSize SValue r
forall (r :: * -> *). OOProg r => SValue r
v_lines) (Integer -> SValue r
forall (r :: * -> *). Literal r => Integer -> SValue r
litInt 1)
([MSStatement r] -> MSBody r
forall (r :: * -> *). BodySym r => [MSStatement r] -> MSBody r
bodyStatements ([MSStatement r] -> MSBody r) -> [MSStatement r] -> MSBody r
forall a b. (a -> b) -> a -> b
$ Delim -> VS (r (Variable r)) -> SValue r -> MSStatement r
forall (r :: * -> *).
StringStatement r =>
Delim -> SVariable r -> SValue r -> MSStatement r
stringSplit Delim
d VS (r (Variable r))
forall (r :: * -> *). OOProg 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 :: * -> *). OOProg r => SValue r
v_lines SValue r
forall (r :: * -> *). OOProg r => SValue r
v_i) MSStatement r -> [MSStatement r] -> [MSStatement r]
forall a. a -> [a] -> [a]
: [MSStatement r]
lnV)]
readLines (Just numLines :: 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 :: * -> *). OOProg r => SVariable r
var_i (Integer -> SValue r
forall (r :: * -> *). Literal r => Integer -> SValue r
litInt 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 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 :: * -> *). OOProg r => SValue r
v_infile VS (r (Variable r))
forall (r :: * -> *). OOProg r => SVariable r
var_line,
Delim -> VS (r (Variable r)) -> SValue r -> MSStatement r
forall (r :: * -> *).
StringStatement r =>
Delim -> SVariable r -> SValue r -> MSStatement r
stringSplit Delim
d VS (r (Variable r))
forall (r :: * -> *). OOProg r => SVariable r
var_linetokens SValue r
forall (r :: * -> *). OOProg 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 (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 ->
GenState [MSStatement r]
lineData :: Maybe Name -> LinePattern -> GenState [MSStatement r]
lineData s :: Maybe Name
s p :: LinePattern
p@(Straight _) = do
[VS (r (Variable r))]
vs <- Maybe Name -> LinePattern -> GenState [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 (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 :: * -> *). OOProg r => SValue r
v_linetokens]
lineData s :: Maybe Name
s p :: LinePattern
p@(Repeat ds :: [Input]
ds) = do
[VS (r (Variable r))]
vs <- Maybe Name -> LinePattern -> GenState [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)
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] -> [StateT DrasilState Identity (MSStatement r)]
forall (r :: * -> *).
OOProg r =>
Maybe Name -> [Input] -> [GenState (MSStatement r)]
clearTemps Maybe Name
s [Input]
ds [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 (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 :: * -> *). OOProg 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] ->
[GenState (MSStatement r)]
clearTemps :: Maybe Name -> [Input] -> [GenState (MSStatement r)]
clearTemps Nothing _ = []
clearTemps (Just sfx :: Name
sfx) es :: [Input]
es = (Input -> GenState (MSStatement r))
-> [Input] -> [GenState (MSStatement r)]
forall a b. (a -> b) -> [a] -> [b]
map (Name -> Input -> GenState (MSStatement r)
forall (r :: * -> *).
OOProg r =>
Name -> Input -> GenState (MSStatement r)
clearTemp Name
sfx) [Input]
es
clearTemp :: (OOProg r) => String -> DataItem ->
GenState (MSStatement r)
clearTemp :: Name -> Input -> GenState (MSStatement r)
clearTemp sfx :: Name
sfx v :: Input
v = (CodeType -> MSStatement r)
-> GenState CodeType -> GenState (MSStatement r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\t :: CodeType
t -> SVariable r -> [SValue r] -> MSStatement r
forall (r :: * -> *).
DeclStatement r =>
SVariable 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)) []) (Input -> GenState CodeType
forall c. HasSpace c => c -> GenState CodeType
codeType Input
v)
appendTemps :: (OOProg r) => Maybe String -> [DataItem] ->
[GenState (MSStatement r)]
appendTemps :: Maybe Name -> [Input] -> [GenState (MSStatement r)]
appendTemps Nothing _ = []
appendTemps (Just sfx :: Name
sfx) es :: [Input]
es = (Input -> GenState (MSStatement r))
-> [Input] -> [GenState (MSStatement r)]
forall a b. (a -> b) -> [a] -> [b]
map (Name -> Input -> GenState (MSStatement r)
forall (r :: * -> *).
OOProg r =>
Name -> Input -> GenState (MSStatement r)
appendTemp Name
sfx) [Input]
es
appendTemp :: (OOProg r) => String -> DataItem ->
GenState (MSStatement r)
appendTemp :: Name -> Input -> GenState (MSStatement r)
appendTemp sfx :: Name
sfx v :: Input
v = (CodeType -> MSStatement r)
-> GenState CodeType -> GenState (MSStatement r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\t :: CodeType
t -> SValue r -> MSStatement r
forall (r :: * -> *). StatementSym r => SValue r -> MSStatement r
valStmt (SValue r -> MSStatement r) -> SValue r -> MSStatement r
forall a b. (a -> b) -> a -> b
$ SValue r -> SValue r -> SValue r
forall (r :: * -> *). List r => SValue r -> SValue r -> SValue r
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)
l_line, l_lines, l_linetokens, l_infile, l_i :: Label
var_line, var_lines, var_linetokens, var_infile, var_i ::
(OOProg r) => SVariable r
v_line, v_lines, v_linetokens, v_infile, v_i ::
(OOProg r) => SValue r
l_line :: Name
l_line = "line"
var_line :: SVariable r
var_line = Name -> VSType r -> SVariable 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 :: SValue r
v_line = SVariable r -> SValue r
forall (r :: * -> *). VariableValue r => SVariable r -> SValue r
valueOf SVariable r
forall (r :: * -> *). OOProg r => SVariable r
var_line
l_lines :: Name
l_lines = "lines"
var_lines :: SVariable r
var_lines = Name -> VSType r -> SVariable 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 :: SValue r
v_lines = SVariable r -> SValue r
forall (r :: * -> *). VariableValue r => SVariable r -> SValue r
valueOf SVariable r
forall (r :: * -> *). OOProg r => SVariable r
var_lines
l_linetokens :: Name
l_linetokens = "linetokens"
var_linetokens :: SVariable r
var_linetokens = Name -> VSType r -> SVariable 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 :: SValue r
v_linetokens = SVariable r -> SValue r
forall (r :: * -> *). VariableValue r => SVariable r -> SValue r
valueOf SVariable r
forall (r :: * -> *). OOProg r => SVariable r
var_linetokens
l_infile :: Name
l_infile = "infile"
var_infile :: SVariable r
var_infile = Name -> VSType r -> SVariable 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 :: SValue r
v_infile = SVariable r -> SValue r
forall (r :: * -> *). VariableValue r => SVariable r -> SValue r
valueOf SVariable r
forall (r :: * -> *). OOProg r => SVariable r
var_infile
l_i :: Name
l_i = "i"
var_i :: SVariable r
var_i = Name -> VSType r -> SVariable 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 :: SValue r
v_i = SVariable r -> SValue r
forall (r :: * -> *). VariableValue r => SVariable r -> SValue r
valueOf SVariable r
forall (r :: * -> *). OOProg r => SVariable r
var_i
getEntryVars :: (OOProg r) => Maybe String -> LinePattern ->
GenState [SVariable r]
getEntryVars :: Maybe Name -> LinePattern -> GenState [SVariable r]
getEntryVars s :: Maybe Name
s lp :: LinePattern
lp = (Input -> StateT DrasilState Identity (SVariable r))
-> [Input] -> GenState [SVariable r]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((Input -> StateT DrasilState Identity (SVariable r))
-> (Name -> Input -> StateT DrasilState Identity (SVariable r))
-> Maybe Name
-> Input
-> StateT DrasilState Identity (SVariable r)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Input -> StateT DrasilState Identity (SVariable r)
forall (r :: * -> *). OOProg r => Input -> GenState (SVariable r)
mkVar (\st :: Name
st v :: Input
v -> Input -> GenState CodeType
forall c. HasSpace c => c -> GenState CodeType
codeType Input
v GenState CodeType
-> (CodeType -> StateT DrasilState Identity (SVariable r))
-> StateT DrasilState Identity (SVariable r)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Name -> VSType r -> StateT DrasilState Identity (SVariable 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) (VSType r -> StateT DrasilState Identity (SVariable r))
-> (CodeType -> VSType r)
-> CodeType
-> StateT DrasilState Identity (SVariable r)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VSType r -> VSType r
forall (r :: * -> *). TypeSym r => VSType r -> VSType r
listInnerType (VSType r -> VSType r)
-> (CodeType -> VSType r) -> CodeType -> VSType r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CodeType -> VSType r
forall (r :: * -> *). TypeSym r => CodeType -> VSType r
convType)) Maybe Name
s) (LinePattern -> [Input]
getPatternInputs LinePattern
lp)
getEntryVarLogs :: (OOProg r) => LinePattern ->
GenState [MSStatement r]
getEntryVarLogs :: LinePattern -> GenState [MSStatement r]
getEntryVarLogs lp :: LinePattern
lp = do
[VS (r (Variable r))]
vs <- Maybe Name -> LinePattern -> GenState [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)
mapM VS (r (Variable r)) -> GenState [MSStatement r]
forall (r :: * -> *).
OOProg r =>
SVariable r -> GenState [MSStatement r]
maybeLog [VS (r (Variable r))]
vs
[MSStatement r] -> GenState [MSStatement r]
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