{-# LANGUAGE TemplateHaskell, TupleSections #-}
module Language.Drasil.Code.ExtLibImport (ExtLibState(..), auxMods, defs,
imports, modExports, steps, genExternalLibraryCall) where
import Language.Drasil (HasSpace(typ), getActorName)
import Language.Drasil.Chunk.Code (CodeVarChunk, CodeFuncChunk, codeName,
ccObjVar)
import Language.Drasil.Chunk.Parameter (ParameterChunk)
import Language.Drasil.Chunk.NamedArgument (NamedArgument)
import Language.Drasil.CodeExpr (CodeExpr, ($&&), applyWithNamedArgs,
msgWithNamedArgs, new, newWithNamedArgs, sy)
import Language.Drasil.Mod (Class, StateVariable, Func(..), Mod, Name,
Description, packmodRequires, classDef, classImplements, FuncStmt(..),
funcDefParams, ctorDef)
import Language.Drasil.Code.ExternalLibrary (ExternalLibrary, Step(..),
FunctionInterface(..), Result(..), Argument(..), ArgumentInfo(..),
Parameter(..), ClassInfo(..), MethodInfo(..), FuncType(..))
import Language.Drasil.Code.ExternalLibraryCall (ExternalLibraryCall,
StepGroupFill(..), StepFill(..), FunctionIntFill(..), ArgumentFill(..),
ParameterFill(..), ClassInfoFill(..), MethodInfoFill(..))
import Control.Lens (makeLenses, (^.), over)
import Control.Monad (zipWithM)
import Control.Monad.State (State, execState, get, modify)
import Data.List (nub, partition)
import Data.List.NonEmpty (NonEmpty(..), (!!), toList)
import Data.Maybe (isJust)
import Prelude hiding ((!!))
data ExtLibState = ELS {
ExtLibState -> [Mod]
_auxMods :: [Mod],
ExtLibState -> [FuncStmt]
_defs :: [FuncStmt],
ExtLibState -> [Name]
_defined :: [Name],
ExtLibState -> [FuncStmt]
_steps :: [FuncStmt],
ExtLibState -> [Name]
_imports :: [String],
ExtLibState -> [(Name, Name)]
_modExports :: [(Name, Name)]
}
makeLenses ''ExtLibState
initELS :: ExtLibState
initELS :: ExtLibState
initELS = ELS :: [Mod]
-> [FuncStmt]
-> [Name]
-> [FuncStmt]
-> [Name]
-> [(Name, Name)]
-> ExtLibState
ELS {
_auxMods :: [Mod]
_auxMods = [],
_defs :: [FuncStmt]
_defs = [],
_defined :: [Name]
_defined = [],
_steps :: [FuncStmt]
_steps = [],
_imports :: [Name]
_imports = [],
_modExports :: [(Name, Name)]
_modExports = []
}
addMod :: Mod -> ExtLibState -> ExtLibState
addMod :: Mod -> ExtLibState -> ExtLibState
addMod m :: Mod
m = ASetter ExtLibState ExtLibState [Mod] [Mod]
-> ([Mod] -> [Mod]) -> ExtLibState -> ExtLibState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter ExtLibState ExtLibState [Mod] [Mod]
Lens' ExtLibState [Mod]
auxMods (Mod
mMod -> [Mod] -> [Mod]
forall a. a -> [a] -> [a]
:)
addDef :: CodeExpr -> CodeVarChunk -> ExtLibState -> ExtLibState
addDef :: CodeExpr -> CodeVarChunk -> ExtLibState -> ExtLibState
addDef e :: CodeExpr
e c :: CodeVarChunk
c s :: ExtLibState
s = if Name
n Name -> [Name] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (ExtLibState
s ExtLibState -> Getting [Name] ExtLibState [Name] -> [Name]
forall s a. s -> Getting a s a -> a
^. Getting [Name] ExtLibState [Name]
Lens' ExtLibState [Name]
defined)
then ExtLibState
s
else ASetter ExtLibState ExtLibState [FuncStmt] [FuncStmt]
-> ([FuncStmt] -> [FuncStmt]) -> ExtLibState -> ExtLibState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter ExtLibState ExtLibState [FuncStmt] [FuncStmt]
Lens' ExtLibState [FuncStmt]
defs ([FuncStmt] -> [FuncStmt] -> [FuncStmt]
forall a. [a] -> [a] -> [a]
++ [CodeVarChunk -> CodeExpr -> FuncStmt
FDecDef CodeVarChunk
c CodeExpr
e]) (Name -> ExtLibState -> ExtLibState
addDefined Name
n ExtLibState
s)
where n :: Name
n = CodeVarChunk -> Name
forall c. CodeIdea c => c -> Name
codeName CodeVarChunk
c
addFuncDef :: CodeFuncChunk -> [ParameterChunk] -> [FuncStmt] -> ExtLibState ->
ExtLibState
addFuncDef :: CodeFuncChunk
-> [ParameterChunk] -> [FuncStmt] -> ExtLibState -> ExtLibState
addFuncDef c :: CodeFuncChunk
c ps :: [ParameterChunk]
ps b :: [FuncStmt]
b s :: ExtLibState
s = if Name
n Name -> [Name] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (ExtLibState
s ExtLibState -> Getting [Name] ExtLibState [Name] -> [Name]
forall s a. s -> Getting a s a -> a
^. Getting [Name] ExtLibState [Name]
Lens' ExtLibState [Name]
defined) then ExtLibState
s else ASetter ExtLibState ExtLibState [FuncStmt] [FuncStmt]
-> ([FuncStmt] -> [FuncStmt]) -> ExtLibState -> ExtLibState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter ExtLibState ExtLibState [FuncStmt] [FuncStmt]
Lens' ExtLibState [FuncStmt]
defs
([FuncStmt] -> [FuncStmt] -> [FuncStmt]
forall a. [a] -> [a] -> [a]
++ [CodeFuncChunk -> [ParameterChunk] -> [FuncStmt] -> FuncStmt
FFuncDef CodeFuncChunk
c [ParameterChunk]
ps [FuncStmt]
b]) (Name -> ExtLibState -> ExtLibState
addDefined Name
n ExtLibState
s)
where n :: Name
n = CodeFuncChunk -> Name
forall c. CodeIdea c => c -> Name
codeName CodeFuncChunk
c
addFieldAsgs :: CodeVarChunk -> [CodeVarChunk] -> [CodeExpr] -> ExtLibState ->
ExtLibState
addFieldAsgs :: CodeVarChunk
-> [CodeVarChunk] -> [CodeExpr] -> ExtLibState -> ExtLibState
addFieldAsgs o :: CodeVarChunk
o cs :: [CodeVarChunk]
cs es :: [CodeExpr]
es = ASetter ExtLibState ExtLibState [FuncStmt] [FuncStmt]
-> ([FuncStmt] -> [FuncStmt]) -> ExtLibState -> ExtLibState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter ExtLibState ExtLibState [FuncStmt] [FuncStmt]
Lens' ExtLibState [FuncStmt]
defs ([FuncStmt] -> [FuncStmt] -> [FuncStmt]
forall a. [a] -> [a] -> [a]
++ (CodeVarChunk -> CodeExpr -> FuncStmt)
-> [CodeVarChunk] -> [CodeExpr] -> [FuncStmt]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith CodeVarChunk -> CodeExpr -> FuncStmt
FAsg ((CodeVarChunk -> CodeVarChunk) -> [CodeVarChunk] -> [CodeVarChunk]
forall a b. (a -> b) -> [a] -> [b]
map (CodeVarChunk -> CodeVarChunk -> CodeVarChunk
ccObjVar CodeVarChunk
o) [CodeVarChunk]
cs) [CodeExpr]
es)
addDefined :: Name -> ExtLibState -> ExtLibState
addDefined :: Name -> ExtLibState -> ExtLibState
addDefined n :: Name
n = ASetter ExtLibState ExtLibState [Name] [Name]
-> ([Name] -> [Name]) -> ExtLibState -> ExtLibState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter ExtLibState ExtLibState [Name] [Name]
Lens' ExtLibState [Name]
defined (Name
nName -> [Name] -> [Name]
forall a. a -> [a] -> [a]
:)
addImports :: [String] -> ExtLibState -> ExtLibState
addImports :: [Name] -> ExtLibState -> ExtLibState
addImports is :: [Name]
is = ASetter ExtLibState ExtLibState [Name] [Name]
-> ([Name] -> [Name]) -> ExtLibState -> ExtLibState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter ExtLibState ExtLibState [Name] [Name]
Lens' ExtLibState [Name]
imports (\l :: [Name]
l -> [Name] -> [Name]
forall a. Eq a => [a] -> [a]
nub ([Name] -> [Name]) -> [Name] -> [Name]
forall a b. (a -> b) -> a -> b
$ [Name]
l [Name] -> [Name] -> [Name]
forall a. [a] -> [a] -> [a]
++ [Name]
is)
addModExport :: (Name, Name) -> ExtLibState -> ExtLibState
addModExport :: (Name, Name) -> ExtLibState -> ExtLibState
addModExport e :: (Name, Name)
e = ASetter ExtLibState ExtLibState [(Name, Name)] [(Name, Name)]
-> ([(Name, Name)] -> [(Name, Name)]) -> ExtLibState -> ExtLibState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter ExtLibState ExtLibState [(Name, Name)] [(Name, Name)]
Lens' ExtLibState [(Name, Name)]
modExports ((Name, Name)
e(Name, Name) -> [(Name, Name)] -> [(Name, Name)]
forall a. a -> [a] -> [a]
:)
addSteps :: [FuncStmt] -> ExtLibState -> ExtLibState
addSteps :: [FuncStmt] -> ExtLibState -> ExtLibState
addSteps fs :: [FuncStmt]
fs = ASetter ExtLibState ExtLibState [FuncStmt] [FuncStmt]
-> ([FuncStmt] -> [FuncStmt]) -> ExtLibState -> ExtLibState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter ExtLibState ExtLibState [FuncStmt] [FuncStmt]
Lens' ExtLibState [FuncStmt]
steps ([FuncStmt] -> [FuncStmt] -> [FuncStmt]
forall a. [a] -> [a] -> [a]
++[FuncStmt]
fs)
refreshLocal :: ExtLibState -> ExtLibState
refreshLocal :: ExtLibState -> ExtLibState
refreshLocal s :: ExtLibState
s = ExtLibState
s {_defs :: [FuncStmt]
_defs = [], _defined :: [Name]
_defined = [], _imports :: [Name]
_imports = []}
returnLocal :: ExtLibState -> ExtLibState -> ExtLibState
returnLocal :: ExtLibState -> ExtLibState -> ExtLibState
returnLocal oldS :: ExtLibState
oldS newS :: ExtLibState
newS = ExtLibState
newS {_defs :: [FuncStmt]
_defs = ExtLibState
oldS ExtLibState
-> Getting [FuncStmt] ExtLibState [FuncStmt] -> [FuncStmt]
forall s a. s -> Getting a s a -> a
^. Getting [FuncStmt] ExtLibState [FuncStmt]
Lens' ExtLibState [FuncStmt]
defs,
_defined :: [Name]
_defined = ExtLibState
oldS ExtLibState -> Getting [Name] ExtLibState [Name] -> [Name]
forall s a. s -> Getting a s a -> a
^. Getting [Name] ExtLibState [Name]
Lens' ExtLibState [Name]
defined,
_imports :: [Name]
_imports = ExtLibState
oldS ExtLibState -> Getting [Name] ExtLibState [Name] -> [Name]
forall s a. s -> Getting a s a -> a
^. Getting [Name] ExtLibState [Name]
Lens' ExtLibState [Name]
imports}
genExternalLibraryCall :: ExternalLibrary -> ExternalLibraryCall ->
ExtLibState
genExternalLibraryCall :: ExternalLibrary -> ExternalLibraryCall -> ExtLibState
genExternalLibraryCall el :: ExternalLibrary
el elc :: ExternalLibraryCall
elc = State ExtLibState () -> ExtLibState -> ExtLibState
forall s a. State s a -> s -> s
execState (ExternalLibrary -> ExternalLibraryCall -> State ExtLibState ()
genExtLibCall ExternalLibrary
el ExternalLibraryCall
elc) ExtLibState
initELS
genExtLibCall :: ExternalLibrary -> ExternalLibraryCall ->
State ExtLibState ()
genExtLibCall :: ExternalLibrary -> ExternalLibraryCall -> State ExtLibState ()
genExtLibCall [] [] = () -> State ExtLibState ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
genExtLibCall (sg :: StepGroup
sg:el :: ExternalLibrary
el) (SGF n :: Int
n sgf :: [StepFill]
sgf:elc :: ExternalLibraryCall
elc) = let s :: [Step]
s = StepGroup
sgStepGroup -> Int -> [Step]
forall a. NonEmpty a -> Int -> a
!!Int
n in
if [Step] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Step]
s Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= [StepFill] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [StepFill]
sgf then Name -> State ExtLibState ()
forall a. HasCallStack => Name -> a
error Name
stepNumberMismatch else do
[FuncStmt]
fs <- (Step -> StepFill -> StateT ExtLibState Identity FuncStmt)
-> [Step] -> [StepFill] -> StateT ExtLibState Identity [FuncStmt]
forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> m c) -> [a] -> [b] -> m [c]
zipWithM Step -> StepFill -> StateT ExtLibState Identity FuncStmt
genStep [Step]
s [StepFill]
sgf
(ExtLibState -> ExtLibState) -> State ExtLibState ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ([FuncStmt] -> ExtLibState -> ExtLibState
addSteps [FuncStmt]
fs)
ExternalLibrary -> ExternalLibraryCall -> State ExtLibState ()
genExtLibCall ExternalLibrary
el ExternalLibraryCall
elc
genExtLibCall _ _ = Name -> State ExtLibState ()
forall a. HasCallStack => Name -> a
error Name
stepNumberMismatch
genStep :: Step -> StepFill -> State ExtLibState FuncStmt
genStep :: Step -> StepFill -> StateT ExtLibState Identity FuncStmt
genStep (Call fi :: FunctionInterface
fi) (CallF fif :: FunctionIntFill
fif) = FunctionInterface
-> FunctionIntFill -> StateT ExtLibState Identity FuncStmt
genFI FunctionInterface
fi FunctionIntFill
fif
genStep (Loop fis :: NonEmpty FunctionInterface
fis f :: [CodeExpr] -> CodeExpr
f ss :: NonEmpty Step
ss) (LoopF fifs :: NonEmpty FunctionIntFill
fifs ccList :: [CodeExpr]
ccList sfs :: NonEmpty StepFill
sfs) = do
[CodeExpr]
es <- (FunctionInterface
-> FunctionIntFill -> StateT ExtLibState Identity CodeExpr)
-> [FunctionInterface]
-> [FunctionIntFill]
-> StateT ExtLibState Identity [CodeExpr]
forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> m c) -> [a] -> [b] -> m [c]
zipWithM FunctionInterface
-> FunctionIntFill -> StateT ExtLibState Identity CodeExpr
genFIVal (NonEmpty FunctionInterface -> [FunctionInterface]
forall a. NonEmpty a -> [a]
toList NonEmpty FunctionInterface
fis) (NonEmpty FunctionIntFill -> [FunctionIntFill]
forall a. NonEmpty a -> [a]
toList NonEmpty FunctionIntFill
fifs)
[FuncStmt]
fs <- (Step -> StepFill -> StateT ExtLibState Identity FuncStmt)
-> [Step] -> [StepFill] -> StateT ExtLibState Identity [FuncStmt]
forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> m c) -> [a] -> [b] -> m [c]
zipWithM Step -> StepFill -> StateT ExtLibState Identity FuncStmt
genStep (NonEmpty Step -> [Step]
forall a. NonEmpty a -> [a]
toList NonEmpty Step
ss) (NonEmpty StepFill -> [StepFill]
forall a. NonEmpty a -> [a]
toList NonEmpty StepFill
sfs)
FuncStmt -> StateT ExtLibState Identity FuncStmt
forall (m :: * -> *) a. Monad m => a -> m a
return (FuncStmt -> StateT ExtLibState Identity FuncStmt)
-> FuncStmt -> StateT ExtLibState Identity FuncStmt
forall a b. (a -> b) -> a -> b
$ CodeExpr -> [FuncStmt] -> FuncStmt
FWhile ((CodeExpr -> CodeExpr -> CodeExpr) -> [CodeExpr] -> CodeExpr
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldl1 CodeExpr -> CodeExpr -> CodeExpr
forall r. ExprC r => r -> r -> r
($&&) [CodeExpr]
es CodeExpr -> CodeExpr -> CodeExpr
forall r. ExprC r => r -> r -> r
$&& [CodeExpr] -> CodeExpr
f [CodeExpr]
ccList) [FuncStmt]
fs
genStep (Statement f :: [CodeVarChunk] -> [CodeExpr] -> FuncStmt
f) (StatementF ccList :: [CodeVarChunk]
ccList exList :: [CodeExpr]
exList) = FuncStmt -> StateT ExtLibState Identity FuncStmt
forall (m :: * -> *) a. Monad m => a -> m a
return (FuncStmt -> StateT ExtLibState Identity FuncStmt)
-> FuncStmt -> StateT ExtLibState Identity FuncStmt
forall a b. (a -> b) -> a -> b
$ [CodeVarChunk] -> [CodeExpr] -> FuncStmt
f [CodeVarChunk]
ccList [CodeExpr]
exList
genStep _ _ = Name -> StateT ExtLibState Identity FuncStmt
forall a. HasCallStack => Name -> a
error Name
stepTypeMismatch
genFIVal :: FunctionInterface -> FunctionIntFill -> State ExtLibState CodeExpr
genFIVal :: FunctionInterface
-> FunctionIntFill -> StateT ExtLibState Identity CodeExpr
genFIVal (FI (r :: Name
r:|rs :: [Name]
rs) ft :: FuncType
ft f :: CodeFuncChunk
f as :: [Argument]
as _) (FIF afs :: [ArgumentFill]
afs) = do
[(Maybe NamedArgument, CodeExpr)]
args <- [Argument]
-> [ArgumentFill]
-> State ExtLibState [(Maybe NamedArgument, CodeExpr)]
genArguments [Argument]
as [ArgumentFill]
afs
let isNamed :: (Maybe a, b) -> Bool
isNamed = Maybe a -> Bool
forall a. Maybe a -> Bool
isJust (Maybe a -> Bool)
-> ((Maybe a, b) -> Maybe a) -> (Maybe a, b) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe a, b) -> Maybe a
forall a b. (a, b) -> a
fst
(nas :: [(Maybe NamedArgument, CodeExpr)]
nas, ars :: [(Maybe NamedArgument, CodeExpr)]
ars) = ((Maybe NamedArgument, CodeExpr) -> Bool)
-> [(Maybe NamedArgument, CodeExpr)]
-> ([(Maybe NamedArgument, CodeExpr)],
[(Maybe NamedArgument, CodeExpr)])
forall a. (a -> Bool) -> [a] -> ([a], [a])
partition (Maybe NamedArgument, CodeExpr) -> Bool
forall a b. (Maybe a, b) -> Bool
isNamed [(Maybe NamedArgument, CodeExpr)]
args
(ExtLibState -> ExtLibState) -> State ExtLibState ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ([Name] -> ExtLibState -> ExtLibState
addImports [Name]
rs (ExtLibState -> ExtLibState)
-> (ExtLibState -> ExtLibState) -> ExtLibState -> ExtLibState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Name, Name) -> ExtLibState -> ExtLibState
addModExport (CodeFuncChunk -> Name
forall c. CodeIdea c => c -> Name
codeName CodeFuncChunk
f, Name
r))
CodeExpr -> StateT ExtLibState Identity CodeExpr
forall (m :: * -> *) a. Monad m => a -> m a
return (CodeExpr -> StateT ExtLibState Identity CodeExpr)
-> CodeExpr -> StateT ExtLibState Identity CodeExpr
forall a b. (a -> b) -> a -> b
$ FuncType
-> CodeFuncChunk
-> [CodeExpr]
-> [(NamedArgument, CodeExpr)]
-> CodeExpr
forall r f a.
(ExprC r, HasUID f, HasUID a, IsArgumentName a, CodeExprC r,
Callable f, CodeIdea f) =>
FuncType -> f -> [r] -> [(a, r)] -> r
getCallFunc FuncType
ft CodeFuncChunk
f (((Maybe NamedArgument, CodeExpr) -> CodeExpr)
-> [(Maybe NamedArgument, CodeExpr)] -> [CodeExpr]
forall a b. (a -> b) -> [a] -> [b]
map (Maybe NamedArgument, CodeExpr) -> CodeExpr
forall a b. (a, b) -> b
snd [(Maybe NamedArgument, CodeExpr)]
ars) (((Maybe NamedArgument, CodeExpr) -> (NamedArgument, CodeExpr))
-> [(Maybe NamedArgument, CodeExpr)] -> [(NamedArgument, CodeExpr)]
forall a b. (a -> b) -> [a] -> [b]
map (\(n :: Maybe NamedArgument
n, e :: CodeExpr
e) ->
(NamedArgument, CodeExpr)
-> (NamedArgument -> (NamedArgument, CodeExpr))
-> Maybe NamedArgument
-> (NamedArgument, CodeExpr)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Name -> (NamedArgument, CodeExpr)
forall a. HasCallStack => Name -> a
error "defective isNamed") (,CodeExpr
e) Maybe NamedArgument
n) [(Maybe NamedArgument, CodeExpr)]
nas)
where getCallFunc :: FuncType -> f -> [r] -> [(a, r)] -> r
getCallFunc Function = f -> [r] -> [(a, r)] -> r
forall r f a.
(ExprC r, HasUID f, HasSymbol f, HasUID a, IsArgumentName a) =>
f -> [r] -> [(a, r)] -> r
applyWithNamedArgs
getCallFunc (Method o :: CodeVarChunk
o) = CodeVarChunk -> f -> [r] -> [(a, r)] -> r
forall r f c a.
(CodeExprC r, Callable f, HasUID f, CodeIdea f, HasUID c,
HasSpace c, CodeIdea c, HasUID a, IsArgumentName a) =>
c -> f -> [r] -> [(a, r)] -> r
msgWithNamedArgs CodeVarChunk
o
getCallFunc Constructor = f -> [r] -> [(a, r)] -> r
forall r f a.
(CodeExprC r, Callable f, HasUID f, CodeIdea f, HasUID a,
IsArgumentName a) =>
f -> [r] -> [(a, r)] -> r
newWithNamedArgs
genFI :: FunctionInterface -> FunctionIntFill -> State ExtLibState FuncStmt
genFI :: FunctionInterface
-> FunctionIntFill -> StateT ExtLibState Identity FuncStmt
genFI fi :: FunctionInterface
fi@(FI _ _ _ _ r :: Maybe Result
r) fif :: FunctionIntFill
fif = do
CodeExpr
fiEx <- FunctionInterface
-> FunctionIntFill -> StateT ExtLibState Identity CodeExpr
genFIVal FunctionInterface
fi FunctionIntFill
fif
FuncStmt -> StateT ExtLibState Identity FuncStmt
forall (m :: * -> *) a. Monad m => a -> m a
return (FuncStmt -> StateT ExtLibState Identity FuncStmt)
-> FuncStmt -> StateT ExtLibState Identity FuncStmt
forall a b. (a -> b) -> a -> b
$ Maybe Result -> CodeExpr -> FuncStmt
maybeGenAssg Maybe Result
r CodeExpr
fiEx
genArguments :: [Argument] -> [ArgumentFill] ->
State ExtLibState [(Maybe NamedArgument, CodeExpr)]
genArguments :: [Argument]
-> [ArgumentFill]
-> State ExtLibState [(Maybe NamedArgument, CodeExpr)]
genArguments (Arg n :: Maybe NamedArgument
n (LockedArg e :: CodeExpr
e):as :: [Argument]
as) afs :: [ArgumentFill]
afs = ([(Maybe NamedArgument, CodeExpr)]
-> [(Maybe NamedArgument, CodeExpr)])
-> State ExtLibState [(Maybe NamedArgument, CodeExpr)]
-> State ExtLibState [(Maybe NamedArgument, CodeExpr)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Maybe NamedArgument
n,CodeExpr
e)(Maybe NamedArgument, CodeExpr)
-> [(Maybe NamedArgument, CodeExpr)]
-> [(Maybe NamedArgument, CodeExpr)]
forall a. a -> [a] -> [a]
:) ([Argument]
-> [ArgumentFill]
-> State ExtLibState [(Maybe NamedArgument, CodeExpr)]
genArguments [Argument]
as [ArgumentFill]
afs)
genArguments as :: [Argument]
as (UserDefinedArgF n :: Maybe NamedArgument
n e :: CodeExpr
e:afs :: [ArgumentFill]
afs) = ([(Maybe NamedArgument, CodeExpr)]
-> [(Maybe NamedArgument, CodeExpr)])
-> State ExtLibState [(Maybe NamedArgument, CodeExpr)]
-> State ExtLibState [(Maybe NamedArgument, CodeExpr)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Maybe NamedArgument
n,CodeExpr
e)(Maybe NamedArgument, CodeExpr)
-> [(Maybe NamedArgument, CodeExpr)]
-> [(Maybe NamedArgument, CodeExpr)]
forall a. a -> [a] -> [a]
:) ([Argument]
-> [ArgumentFill]
-> State ExtLibState [(Maybe NamedArgument, CodeExpr)]
genArguments [Argument]
as [ArgumentFill]
afs)
genArguments (Arg n :: Maybe NamedArgument
n (Basic _ Nothing):as :: [Argument]
as) (BasicF e :: CodeExpr
e:afs :: [ArgumentFill]
afs) = ([(Maybe NamedArgument, CodeExpr)]
-> [(Maybe NamedArgument, CodeExpr)])
-> State ExtLibState [(Maybe NamedArgument, CodeExpr)]
-> State ExtLibState [(Maybe NamedArgument, CodeExpr)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Maybe NamedArgument
n,CodeExpr
e)(Maybe NamedArgument, CodeExpr)
-> [(Maybe NamedArgument, CodeExpr)]
-> [(Maybe NamedArgument, CodeExpr)]
forall a. a -> [a] -> [a]
:)
([Argument]
-> [ArgumentFill]
-> State ExtLibState [(Maybe NamedArgument, CodeExpr)]
genArguments [Argument]
as [ArgumentFill]
afs)
genArguments (Arg n :: Maybe NamedArgument
n (Basic _ (Just v :: CodeVarChunk
v)):as :: [Argument]
as) (BasicF e :: CodeExpr
e:afs :: [ArgumentFill]
afs) = do
(ExtLibState -> ExtLibState) -> State ExtLibState ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (CodeExpr -> CodeVarChunk -> ExtLibState -> ExtLibState
addDef CodeExpr
e CodeVarChunk
v)
([(Maybe NamedArgument, CodeExpr)]
-> [(Maybe NamedArgument, CodeExpr)])
-> State ExtLibState [(Maybe NamedArgument, CodeExpr)]
-> State ExtLibState [(Maybe NamedArgument, CodeExpr)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Maybe NamedArgument
n, CodeVarChunk -> CodeExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy CodeVarChunk
v)(Maybe NamedArgument, CodeExpr)
-> [(Maybe NamedArgument, CodeExpr)]
-> [(Maybe NamedArgument, CodeExpr)]
forall a. a -> [a] -> [a]
:) ([Argument]
-> [ArgumentFill]
-> State ExtLibState [(Maybe NamedArgument, CodeExpr)]
genArguments [Argument]
as [ArgumentFill]
afs)
genArguments (Arg n :: Maybe NamedArgument
n (Fn c :: CodeFuncChunk
c ps :: [Parameter]
ps s :: Step
s):as :: [Argument]
as) (FnF pfs :: [ParameterFill]
pfs sf :: StepFill
sf:afs :: [ArgumentFill]
afs) = do
let prms :: [ParameterChunk]
prms = [Parameter] -> [ParameterFill] -> [ParameterChunk]
genParameters [Parameter]
ps [ParameterFill]
pfs
FuncStmt
st <- Step -> StepFill -> StateT ExtLibState Identity FuncStmt
genStep Step
s StepFill
sf
(ExtLibState -> ExtLibState) -> State ExtLibState ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (CodeFuncChunk
-> [ParameterChunk] -> [FuncStmt] -> ExtLibState -> ExtLibState
addFuncDef CodeFuncChunk
c [ParameterChunk]
prms [FuncStmt
st])
([(Maybe NamedArgument, CodeExpr)]
-> [(Maybe NamedArgument, CodeExpr)])
-> State ExtLibState [(Maybe NamedArgument, CodeExpr)]
-> State ExtLibState [(Maybe NamedArgument, CodeExpr)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Maybe NamedArgument
n, CodeFuncChunk -> CodeExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy CodeFuncChunk
c)(Maybe NamedArgument, CodeExpr)
-> [(Maybe NamedArgument, CodeExpr)]
-> [(Maybe NamedArgument, CodeExpr)]
forall a. a -> [a] -> [a]
:) ([Argument]
-> [ArgumentFill]
-> State ExtLibState [(Maybe NamedArgument, CodeExpr)]
genArguments [Argument]
as [ArgumentFill]
afs)
genArguments (Arg n :: Maybe NamedArgument
n (Class rs :: [Name]
rs desc :: Name
desc o :: CodeVarChunk
o ctor :: CodeFuncChunk
ctor ci :: ClassInfo
ci):as :: [Argument]
as) (ClassF svs :: [StateVariable]
svs cif :: ClassInfoFill
cif:afs :: [ArgumentFill]
afs) = do
(c :: Class
c, is :: [Name]
is) <- CodeVarChunk
-> CodeFuncChunk
-> Name
-> Name
-> [StateVariable]
-> ClassInfo
-> ClassInfoFill
-> State ExtLibState (Class, [Name])
genClassInfo CodeVarChunk
o CodeFuncChunk
ctor Name
an Name
desc [StateVariable]
svs ClassInfo
ci ClassInfoFill
cif
(ExtLibState -> ExtLibState) -> State ExtLibState ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (Mod -> ExtLibState -> ExtLibState
addMod (Name -> Name -> [Name] -> [Class] -> [Func] -> Mod
packmodRequires Name
an Name
desc ([Name]
rs [Name] -> [Name] -> [Name]
forall a. [a] -> [a] -> [a]
++ [Name]
is) [Class
c] []))
([(Maybe NamedArgument, CodeExpr)]
-> [(Maybe NamedArgument, CodeExpr)])
-> State ExtLibState [(Maybe NamedArgument, CodeExpr)]
-> State ExtLibState [(Maybe NamedArgument, CodeExpr)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Maybe NamedArgument
n, CodeVarChunk -> CodeExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy CodeVarChunk
o)(Maybe NamedArgument, CodeExpr)
-> [(Maybe NamedArgument, CodeExpr)]
-> [(Maybe NamedArgument, CodeExpr)]
forall a. a -> [a] -> [a]
:) ([Argument]
-> [ArgumentFill]
-> State ExtLibState [(Maybe NamedArgument, CodeExpr)]
genArguments [Argument]
as [ArgumentFill]
afs)
where an :: Name
an = Space -> Name
getActorName (CodeVarChunk
o CodeVarChunk -> Getting Space CodeVarChunk Space -> Space
forall s a. s -> Getting a s a -> a
^. Getting Space CodeVarChunk Space
forall c. HasSpace c => Lens' c Space
typ)
genArguments (Arg n :: Maybe NamedArgument
n (Record (rq :: Name
rq:|rqs :: [Name]
rqs) rn :: CodeFuncChunk
rn r :: CodeVarChunk
r fs :: [CodeVarChunk]
fs):as :: [Argument]
as) (RecordF es :: [CodeExpr]
es:afs :: [ArgumentFill]
afs) =
if [CodeVarChunk] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [CodeVarChunk]
fs Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= [CodeExpr] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [CodeExpr]
es then Name -> State ExtLibState [(Maybe NamedArgument, CodeExpr)]
forall a. HasCallStack => Name -> a
error Name
recordFieldsMismatch else do
(ExtLibState -> ExtLibState) -> State ExtLibState ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (CodeVarChunk
-> [CodeVarChunk] -> [CodeExpr] -> ExtLibState -> ExtLibState
addFieldAsgs CodeVarChunk
r [CodeVarChunk]
fs [CodeExpr]
es (ExtLibState -> ExtLibState)
-> (ExtLibState -> ExtLibState) -> ExtLibState -> ExtLibState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CodeExpr -> CodeVarChunk -> ExtLibState -> ExtLibState
addDef (CodeFuncChunk -> [CodeExpr] -> CodeExpr
forall r f.
(CodeExprC r, Callable f, HasUID f, CodeIdea f) =>
f -> [r] -> r
new CodeFuncChunk
rn []) CodeVarChunk
r (ExtLibState -> ExtLibState)
-> (ExtLibState -> ExtLibState) -> ExtLibState -> ExtLibState
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
(Name, Name) -> ExtLibState -> ExtLibState
addModExport (CodeFuncChunk -> Name
forall c. CodeIdea c => c -> Name
codeName CodeFuncChunk
rn, Name
rq) (ExtLibState -> ExtLibState)
-> (ExtLibState -> ExtLibState) -> ExtLibState -> ExtLibState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Name] -> ExtLibState -> ExtLibState
addImports [Name]
rqs)
([(Maybe NamedArgument, CodeExpr)]
-> [(Maybe NamedArgument, CodeExpr)])
-> State ExtLibState [(Maybe NamedArgument, CodeExpr)]
-> State ExtLibState [(Maybe NamedArgument, CodeExpr)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Maybe NamedArgument
n, CodeVarChunk -> CodeExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy CodeVarChunk
r)(Maybe NamedArgument, CodeExpr)
-> [(Maybe NamedArgument, CodeExpr)]
-> [(Maybe NamedArgument, CodeExpr)]
forall a. a -> [a] -> [a]
:) ([Argument]
-> [ArgumentFill]
-> State ExtLibState [(Maybe NamedArgument, CodeExpr)]
genArguments [Argument]
as [ArgumentFill]
afs)
genArguments [] [] = [(Maybe NamedArgument, CodeExpr)]
-> State ExtLibState [(Maybe NamedArgument, CodeExpr)]
forall (m :: * -> *) a. Monad m => a -> m a
return []
genArguments _ _ = Name -> State ExtLibState [(Maybe NamedArgument, CodeExpr)]
forall a. HasCallStack => Name -> a
error Name
argumentMismatch
genClassInfo :: CodeVarChunk -> CodeFuncChunk -> Name -> Description ->
[StateVariable] -> ClassInfo -> ClassInfoFill ->
State ExtLibState (Class, [String])
genClassInfo :: CodeVarChunk
-> CodeFuncChunk
-> Name
-> Name
-> [StateVariable]
-> ClassInfo
-> ClassInfoFill
-> State ExtLibState (Class, [Name])
genClassInfo o :: CodeVarChunk
o c :: CodeFuncChunk
c n :: Name
n desc :: Name
desc svs :: [StateVariable]
svs ci :: ClassInfo
ci cif :: ClassInfoFill
cif = let (mis :: [MethodInfo]
mis, mifs :: [MethodInfoFill]
mifs, f :: Name -> [StateVariable] -> [Func] -> Class
f) = ClassInfo
-> ClassInfoFill
-> ([MethodInfo], [MethodInfoFill],
Name -> [StateVariable] -> [Func] -> Class)
genCI ClassInfo
ci ClassInfoFill
cif in
if [MethodInfo] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [MethodInfo]
mis Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= [MethodInfoFill] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [MethodInfoFill]
mifs then Name -> State ExtLibState (Class, [Name])
forall a. HasCallStack => Name -> a
error Name
methodInfoNumberMismatch else do
[(Func, [Name])]
ms <- (MethodInfo
-> MethodInfoFill -> StateT ExtLibState Identity (Func, [Name]))
-> [MethodInfo]
-> [MethodInfoFill]
-> StateT ExtLibState Identity [(Func, [Name])]
forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> m c) -> [a] -> [b] -> m [c]
zipWithM (CodeVarChunk
-> CodeFuncChunk
-> MethodInfo
-> MethodInfoFill
-> StateT ExtLibState Identity (Func, [Name])
genMethodInfo CodeVarChunk
o CodeFuncChunk
c) [MethodInfo]
mis [MethodInfoFill]
mifs
(ExtLibState -> ExtLibState) -> State ExtLibState ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (if (MethodInfo -> Bool) -> [MethodInfo] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any MethodInfo -> Bool
isConstructor [MethodInfo]
mis then ExtLibState -> ExtLibState
forall a. a -> a
id else CodeExpr -> CodeVarChunk -> ExtLibState -> ExtLibState
addDef (CodeFuncChunk -> [CodeExpr] -> CodeExpr
forall r f.
(CodeExprC r, Callable f, HasUID f, CodeIdea f) =>
f -> [r] -> r
new CodeFuncChunk
c []) CodeVarChunk
o)
(Class, [Name]) -> State ExtLibState (Class, [Name])
forall (m :: * -> *) a. Monad m => a -> m a
return (Name -> [StateVariable] -> [Func] -> Class
f Name
desc [StateVariable]
svs (((Func, [Name]) -> Func) -> [(Func, [Name])] -> [Func]
forall a b. (a -> b) -> [a] -> [b]
map (Func, [Name]) -> Func
forall a b. (a, b) -> a
fst [(Func, [Name])]
ms), ((Func, [Name]) -> [Name]) -> [(Func, [Name])] -> [Name]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Func, [Name]) -> [Name]
forall a b. (a, b) -> b
snd [(Func, [Name])]
ms)
where genCI :: ClassInfo
-> ClassInfoFill
-> ([MethodInfo], [MethodInfoFill],
Name -> [StateVariable] -> [Func] -> Class)
genCI (Regular mis' :: [MethodInfo]
mis') (RegularF mifs' :: [MethodInfoFill]
mifs') = ([MethodInfo]
mis', [MethodInfoFill]
mifs', Name -> Name -> [StateVariable] -> [Func] -> Class
classDef Name
n)
genCI (Implements intn :: Name
intn mis' :: [MethodInfo]
mis') (ImplementsF mifs' :: [MethodInfoFill]
mifs') = ([MethodInfo]
mis', [MethodInfoFill]
mifs',
Name -> Name -> Name -> [StateVariable] -> [Func] -> Class
classImplements Name
n Name
intn)
genCI _ _ = Name
-> ([MethodInfo], [MethodInfoFill],
Name -> [StateVariable] -> [Func] -> Class)
forall a. HasCallStack => Name -> a
error Name
classInfoMismatch
genMethodInfo :: CodeVarChunk -> CodeFuncChunk -> MethodInfo ->
MethodInfoFill -> State ExtLibState (Func, [String])
genMethodInfo :: CodeVarChunk
-> CodeFuncChunk
-> MethodInfo
-> MethodInfoFill
-> StateT ExtLibState Identity (Func, [Name])
genMethodInfo o :: CodeVarChunk
o c :: CodeFuncChunk
c (CI desc :: Name
desc ps :: [Parameter]
ps ss :: [Step]
ss) (CIF pfs :: [ParameterFill]
pfs is :: [Initializer]
is sfs :: [StepFill]
sfs) = do
let prms :: [ParameterChunk]
prms = [Parameter] -> [ParameterFill] -> [ParameterChunk]
genParameters [Parameter]
ps [ParameterFill]
pfs
(fs :: [FuncStmt]
fs, newS :: ExtLibState
newS) <- StateT ExtLibState Identity [FuncStmt]
-> State ExtLibState ([FuncStmt], ExtLibState)
forall a. State ExtLibState a -> State ExtLibState (a, ExtLibState)
withLocalState (StateT ExtLibState Identity [FuncStmt]
-> State ExtLibState ([FuncStmt], ExtLibState))
-> StateT ExtLibState Identity [FuncStmt]
-> State ExtLibState ([FuncStmt], ExtLibState)
forall a b. (a -> b) -> a -> b
$ (Step -> StepFill -> StateT ExtLibState Identity FuncStmt)
-> [Step] -> [StepFill] -> StateT ExtLibState Identity [FuncStmt]
forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> m c) -> [a] -> [b] -> m [c]
zipWithM Step -> StepFill -> StateT ExtLibState Identity FuncStmt
genStep [Step]
ss [StepFill]
sfs
(ExtLibState -> ExtLibState) -> State ExtLibState ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (CodeExpr -> CodeVarChunk -> ExtLibState -> ExtLibState
addDef (CodeFuncChunk -> [CodeExpr] -> CodeExpr
forall r f.
(CodeExprC r, Callable f, HasUID f, CodeIdea f) =>
f -> [r] -> r
new CodeFuncChunk
c ((ParameterChunk -> CodeExpr) -> [ParameterChunk] -> [CodeExpr]
forall a b. (a -> b) -> [a] -> [b]
map ParameterChunk -> CodeExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy [ParameterChunk]
prms)) CodeVarChunk
o)
(Func, [Name]) -> StateT ExtLibState Identity (Func, [Name])
forall (m :: * -> *) a. Monad m => a -> m a
return (Name
-> Name -> [ParameterChunk] -> [Initializer] -> [FuncStmt] -> Func
ctorDef (CodeFuncChunk -> Name
forall c. CodeIdea c => c -> Name
codeName CodeFuncChunk
c) Name
desc [ParameterChunk]
prms [Initializer]
is (ExtLibState
newS ExtLibState
-> Getting [FuncStmt] ExtLibState [FuncStmt] -> [FuncStmt]
forall s a. s -> Getting a s a -> a
^. Getting [FuncStmt] ExtLibState [FuncStmt]
Lens' ExtLibState [FuncStmt]
defs [FuncStmt] -> [FuncStmt] -> [FuncStmt]
forall a. [a] -> [a] -> [a]
++ [FuncStmt]
fs),
ExtLibState
newS ExtLibState -> Getting [Name] ExtLibState [Name] -> [Name]
forall s a. s -> Getting a s a -> a
^. Getting [Name] ExtLibState [Name]
Lens' ExtLibState [Name]
imports)
genMethodInfo _ _ (MI m :: CodeFuncChunk
m desc :: Name
desc ps :: [Parameter]
ps rDesc :: Maybe Name
rDesc ss :: NonEmpty Step
ss) (MIF pfs :: [ParameterFill]
pfs sfs :: NonEmpty StepFill
sfs) = do
let prms :: [ParameterChunk]
prms = [Parameter] -> [ParameterFill] -> [ParameterChunk]
genParameters [Parameter]
ps [ParameterFill]
pfs
(fs :: [FuncStmt]
fs, newS :: ExtLibState
newS) <- StateT ExtLibState Identity [FuncStmt]
-> State ExtLibState ([FuncStmt], ExtLibState)
forall a. State ExtLibState a -> State ExtLibState (a, ExtLibState)
withLocalState ((Step -> StepFill -> StateT ExtLibState Identity FuncStmt)
-> [Step] -> [StepFill] -> StateT ExtLibState Identity [FuncStmt]
forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> m c) -> [a] -> [b] -> m [c]
zipWithM Step -> StepFill -> StateT ExtLibState Identity FuncStmt
genStep (NonEmpty Step -> [Step]
forall a. NonEmpty a -> [a]
toList NonEmpty Step
ss) (NonEmpty StepFill -> [StepFill]
forall a. NonEmpty a -> [a]
toList NonEmpty StepFill
sfs))
(Func, [Name]) -> StateT ExtLibState Identity (Func, [Name])
forall (m :: * -> *) a. Monad m => a -> m a
return (Name
-> Name
-> [ParameterChunk]
-> Space
-> Maybe Name
-> [FuncStmt]
-> Func
funcDefParams (CodeFuncChunk -> Name
forall c. CodeIdea c => c -> Name
codeName CodeFuncChunk
m) Name
desc [ParameterChunk]
prms (CodeFuncChunk
m CodeFuncChunk -> Getting Space CodeFuncChunk Space -> Space
forall s a. s -> Getting a s a -> a
^. Getting Space CodeFuncChunk Space
forall c. HasSpace c => Lens' c Space
typ) Maybe Name
rDesc (
ExtLibState
newS ExtLibState
-> Getting [FuncStmt] ExtLibState [FuncStmt] -> [FuncStmt]
forall s a. s -> Getting a s a -> a
^. Getting [FuncStmt] ExtLibState [FuncStmt]
Lens' ExtLibState [FuncStmt]
defs [FuncStmt] -> [FuncStmt] -> [FuncStmt]
forall a. [a] -> [a] -> [a]
++ [FuncStmt]
fs), ExtLibState
newS ExtLibState -> Getting [Name] ExtLibState [Name] -> [Name]
forall s a. s -> Getting a s a -> a
^. Getting [Name] ExtLibState [Name]
Lens' ExtLibState [Name]
imports)
genMethodInfo _ _ _ _ = Name -> StateT ExtLibState Identity (Func, [Name])
forall a. HasCallStack => Name -> a
error Name
methodInfoMismatch
genParameters :: [Parameter] -> [ParameterFill] -> [ParameterChunk]
genParameters :: [Parameter] -> [ParameterFill] -> [ParameterChunk]
genParameters (LockedParam c :: ParameterChunk
c:ps :: [Parameter]
ps) pfs :: [ParameterFill]
pfs = ParameterChunk
c ParameterChunk -> [ParameterChunk] -> [ParameterChunk]
forall a. a -> [a] -> [a]
: [Parameter] -> [ParameterFill] -> [ParameterChunk]
genParameters [Parameter]
ps [ParameterFill]
pfs
genParameters ps :: [Parameter]
ps (UserDefined c :: ParameterChunk
c:pfs :: [ParameterFill]
pfs) = ParameterChunk
c ParameterChunk -> [ParameterChunk] -> [ParameterChunk]
forall a. a -> [a] -> [a]
: [Parameter] -> [ParameterFill] -> [ParameterChunk]
genParameters [Parameter]
ps [ParameterFill]
pfs
genParameters (NameableParam _:ps :: [Parameter]
ps) (NameableParamF c :: ParameterChunk
c:pfs :: [ParameterFill]
pfs) = ParameterChunk
c ParameterChunk -> [ParameterChunk] -> [ParameterChunk]
forall a. a -> [a] -> [a]
:
[Parameter] -> [ParameterFill] -> [ParameterChunk]
genParameters [Parameter]
ps [ParameterFill]
pfs
genParameters [] [] = []
genParameters _ _ = Name -> [ParameterChunk]
forall a. HasCallStack => Name -> a
error Name
paramMismatch
maybeGenAssg :: Maybe Result -> (CodeExpr -> FuncStmt)
maybeGenAssg :: Maybe Result -> CodeExpr -> FuncStmt
maybeGenAssg Nothing = CodeExpr -> FuncStmt
FVal
maybeGenAssg (Just (Assign c :: CodeVarChunk
c)) = CodeVarChunk -> CodeExpr -> FuncStmt
FDecDef CodeVarChunk
c
maybeGenAssg (Just Return) = CodeExpr -> FuncStmt
FRet
withLocalState :: State ExtLibState a -> State ExtLibState (a, ExtLibState)
withLocalState :: State ExtLibState a -> State ExtLibState (a, ExtLibState)
withLocalState st :: State ExtLibState a
st = do
ExtLibState
s <- StateT ExtLibState Identity ExtLibState
forall s (m :: * -> *). MonadState s m => m s
get
(ExtLibState -> ExtLibState) -> State ExtLibState ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ExtLibState -> ExtLibState
refreshLocal
a
st' <- State ExtLibState a
st
ExtLibState
newS <- StateT ExtLibState Identity ExtLibState
forall s (m :: * -> *). MonadState s m => m s
get
(ExtLibState -> ExtLibState) -> State ExtLibState ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (ExtLibState -> ExtLibState -> ExtLibState
returnLocal ExtLibState
s)
(a, ExtLibState) -> State ExtLibState (a, ExtLibState)
forall (m :: * -> *) a. Monad m => a -> m a
return (a
st', ExtLibState
newS)
isConstructor :: MethodInfo -> Bool
isConstructor :: MethodInfo -> Bool
isConstructor CI{} = Bool
True
isConstructor _ = Bool
False
elAndElc, stepNumberMismatch, stepTypeMismatch, argumentMismatch,
paramMismatch, recordFieldsMismatch, ciAndCif, classInfoMismatch,
methodInfoNumberMismatch, methodInfoMismatch :: String
elAndElc :: Name
elAndElc = "ExternalLibrary and ExternalLibraryCall have different "
stepNumberMismatch :: Name
stepNumberMismatch = Name
elAndElc Name -> Name -> Name
forall a. [a] -> [a] -> [a]
++ "number of steps"
stepTypeMismatch :: Name
stepTypeMismatch = Name
elAndElc Name -> Name -> Name
forall a. [a] -> [a] -> [a]
++ "order of steps"
argumentMismatch :: Name
argumentMismatch = "FunctionInterface and FunctionIntFill have different number or types of arguments"
paramMismatch :: Name
paramMismatch = "Parameters mismatched with ParameterFills"
recordFieldsMismatch :: Name
recordFieldsMismatch = "Different number of record fields than field values"
ciAndCif :: Name
ciAndCif = "ClassInfo and ClassInfoFill have different "
classInfoMismatch :: Name
classInfoMismatch = Name
ciAndCif Name -> Name -> Name
forall a. [a] -> [a] -> [a]
++ "class types"
methodInfoNumberMismatch :: Name
methodInfoNumberMismatch = Name
ciAndCif Name -> Name -> Name
forall a. [a] -> [a] -> [a]
++ "number of MethodInfos/MethodInfoFills"
methodInfoMismatch :: Name
methodInfoMismatch = "MethodInfo and MethodInfoFill have different method types"