module Drasil.GOOL.LanguageRenderer.CommonPseudoOO (int, constructor, doxFunc,
doxClass, doxMod, docMod', modDoc', functionDoc, extVar, classVar, objVarSelf,
indexOf, contains, containsInt, listAddFunc, discardFileLine, intClass, funcType, buildModule,
arrayType, pi, printSt, arrayDec, arrayDecDef, openFileA, forEach, forEach',
docMain, mainFunction, buildModule', call', listSizeFunc, listAccessFunc',
string, constDecDef, docInOutFunc, bindingError, extFuncAppMixedArgs, notNull,
listDecDef, destructorError, stateVarDef, constVar, litArray, litSet, listSetFunc, litSetFunc,
extraClass, listAccessFunc, doubleRender, double, openFileR, openFileW,
stateVar, self, multiAssign, multiReturn, listDec, funcDecDef, inOutCall,
forLoopError, mainBody, inOutFunc, docInOutFunc', boolRender, bool,
floatRender, float, stringRender', string', inherit, implements, listSize, setDecDef, setDec,
listAdd, listAppend, intToIndex, indexToInt, intToIndex', indexToInt',
varDecDef, openFileR', openFileW', openFileA', argExists, global, setMethodCall
) where
import Utils.Drasil (indent, stringList)
import Drasil.GOOL.CodeType (CodeType(..))
import Drasil.GOOL.InterfaceCommon (Label, Library, Body, MSBody, VSFunction,
VSType, Variable, SVariable, Value, SValue, MSStatement, MSParameter, SMethod,
MixedCall, bodyStatements, oneLiner, TypeSym(infile, outfile, listInnerType),
TypeElim(getType, getTypeString), VariableElim(variableName, variableType),
ValueSym(valueType), Comparison(..), (&=), ControlStatement(returnStmt),
VisibilitySym(..), MethodSym(function), funcApp, ScopeSym(Scope))
import qualified Drasil.GOOL.InterfaceCommon as IC (argsList,
TypeSym(int, bool, double, string, listType, arrayType, void), VariableSym(var),
Literal(litTrue, litFalse, litList, litSet, litInt, litString),
VariableValue(valueOf), StatementSym(valStmt, emptyStmt), DeclStatement(varDec,
varDecDef, constDecDef), List(intToIndex, indexToInt), ParameterSym(param,
pointerParam), MethodSym(mainFunction), AssignStatement(assign), ScopeSym(..))
import Drasil.GOOL.InterfaceGOOL (SFile, FSModule, SClass, CSStateVar,
OOTypeSym(obj), PermanenceSym(..), Initializers, objMethodCallNoParams, objMethodCall)
import qualified Drasil.GOOL.InterfaceGOOL as IG (ClassSym(buildClass),
OOVariableSym(self, objVar), OOFunctionSym(..))
import Drasil.GOOL.RendererClassesCommon (CommonRenderSym, ImportSym(..),
RenderBody(..), RenderType(..), RenderVariable(varFromData),
InternalVarElim(variableBind), RenderFunction(funcFromData),
MethodTypeSym(mType), RenderMethod(commentedFunc, mthdFromData),
BlockCommentSym(..), ScopeElim(scopeData))
import qualified Drasil.GOOL.RendererClassesCommon as S (RenderBody(multiBody),
RenderValue(call), RenderStatement(stmt),
InternalAssignStmt(multiAssign), InternalControlStmt(multiReturn),
InternalListFunc(listSizeFunc, listAddFunc, listAppendFunc))
import qualified Drasil.GOOL.RendererClassesCommon as RC (ImportElim(..),
BodyElim(..), InternalTypeElim(..), InternalVarElim(variable), ValueElim(..),
StatementElim(statement), VisibilityElim(..), MethodElim(..), FunctionElim(..))
import Drasil.GOOL.Helpers (vibcat, toCode, toState, onCodeValue, onStateValue,
on2StateValues, onStateList)
import Drasil.GOOL.RendererClassesOO (OORenderSym, OORenderMethod(intMethod),
ParentSpec)
import qualified Drasil.GOOL.RendererClassesOO as S (OOMethodTypeSym(construct),
OORenderMethod(intFunc), RenderClass(intClass, inherit),
RenderMod(modFromData))
import qualified Drasil.GOOL.RendererClassesOO as RC (PermElim(..),
StateVarElim(..), ClassElim(..))
import Drasil.GOOL.LanguageRenderer (array', new', args, array, listSep, access,
mathFunc, ModuleDocRenderer, FuncDocRenderer, functionDox, classDox,
moduleDox, variableList, valueList, intValue)
import qualified Drasil.GOOL.LanguageRenderer as R (self, self', module',
print, stateVar, stateVarList, constDecDef, extVar, listAccessFunc)
import Drasil.GOOL.LanguageRenderer.Constructors (mkStmt, mkStmtNoEnd,
mkStateVal, mkStateVar, mkVal, mkVal)
import Drasil.GOOL.LanguageRenderer.LanguagePolymorphic (classVarCheckStatic,
call, initStmts, docFunc, docFuncRepr, docClass, docMod, smartAdd, smartSub)
import Drasil.GOOL.AST (VisibilityTag(..), ScopeTag(Global), ScopeData, sd)
import Drasil.GOOL.State (FS, CS, lensFStoCS, lensFStoMS, lensCStoMS,
lensMStoVS, lensVStoMS, currParameters, getClassName, getLangImports,
getLibImports, getModuleImports, setClassName, setCurrMain, setMainDoc,
useVarName, setVarScope)
import Prelude hiding (print,pi,(<>))
import Data.List (sort, intercalate)
import Control.Monad (join)
import Control.Monad.State (get, modify)
import Control.Lens ((^.))
import qualified Control.Lens as L (set)
import Control.Lens.Zoom (zoom)
import Text.PrettyPrint.HughesPJ (Doc, text, empty, render, (<>), (<+>), parens,
brackets, braces, colon, vcat, equals)
import Metadata.Drasil.DrasilMetaCall (watermark)
intToIndex :: SValue r -> SValue r
intToIndex :: forall (r :: * -> *). SValue r -> SValue r
intToIndex = VS (r (Value r)) -> VS (r (Value r))
forall a. a -> a
id
indexToInt :: SValue r -> SValue r
indexToInt :: forall (r :: * -> *). SValue r -> SValue r
indexToInt = VS (r (Value r)) -> VS (r (Value r))
forall a. a -> a
id
global :: (Monad r) => r ScopeData
global :: forall (r :: * -> *). Monad r => r ScopeData
global = ScopeData -> r ScopeData
forall (r :: * -> *) a. Monad r => a -> r a
toCode (ScopeData -> r ScopeData) -> ScopeData -> r ScopeData
forall a b. (a -> b) -> a -> b
$ ScopeTag -> ScopeData
sd ScopeTag
Global
intRender :: String
intRender :: String
intRender = String
"int"
int :: (CommonRenderSym r) => VSType r
int :: forall (r :: * -> *). CommonRenderSym r => VSType r
int = CodeType
-> String -> Doc -> StateT ValueState Identity (r (Type r))
forall (r :: * -> *).
RenderType r =>
CodeType -> String -> Doc -> VSType r
typeFromData CodeType
Integer String
intRender (String -> Doc
text String
intRender)
constructor :: (OORenderSym r) => Label -> [MSParameter r] -> Initializers r ->
MSBody r -> SMethod r
constructor :: forall (r :: * -> *).
OORenderSym r =>
String
-> [MSParameter r] -> Initializers r -> MSBody r -> SMethod r
constructor String
fName [MSParameter r]
ps Initializers r
is MSBody r
b = MS String
getClassName MS String
-> (String -> StateT MethodState Identity (r (Method r)))
-> StateT MethodState Identity (r (Method r))
forall a b.
StateT MethodState Identity a
-> (a -> StateT MethodState Identity b)
-> StateT MethodState Identity b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (\String
c -> Bool
-> String
-> r (Visibility r)
-> r (Permanence r)
-> MSMthdType r
-> [MSParameter r]
-> MSBody r
-> StateT MethodState Identity (r (Method r))
forall (r :: * -> *).
OORenderMethod r =>
Bool
-> String
-> r (Visibility r)
-> r (Permanence r)
-> MSMthdType r
-> [MSParameter r]
-> MSBody r
-> SMethod r
intMethod Bool
False String
fName
r (Visibility r)
forall (r :: * -> *). VisibilitySym r => r (Visibility r)
public r (Permanence r)
forall (r :: * -> *). PermanenceSym r => r (Permanence r)
dynamic (String -> MSMthdType r
forall (r :: * -> *). OOMethodTypeSym r => String -> MSMthdType r
S.construct String
c) [MSParameter r]
ps ([MSBody r] -> MSBody r
forall (r :: * -> *). RenderBody r => [MSBody r] -> MSBody r
S.multiBody [Initializers r -> MSBody r
forall (r :: * -> *). OORenderSym r => Initializers r -> MSBody r
initStmts Initializers r
is, MSBody r
b]))
doxFunc :: (CommonRenderSym r) => String -> [String] -> Maybe String -> SMethod r ->
SMethod r
doxFunc :: forall (r :: * -> *).
CommonRenderSym r =>
String -> [String] -> Maybe String -> SMethod r -> SMethod r
doxFunc = FuncDocRenderer
-> String
-> [String]
-> Maybe String
-> StateT MethodState Identity (r (Method r))
-> StateT MethodState Identity (r (Method r))
forall (r :: * -> *).
CommonRenderSym r =>
FuncDocRenderer
-> String -> [String] -> Maybe String -> SMethod r -> SMethod r
docFunc FuncDocRenderer
functionDox
doxClass :: (OORenderSym r) => String -> SClass r -> SClass r
doxClass :: forall (r :: * -> *).
OORenderSym r =>
String -> SClass r -> SClass r
doxClass = ClassDocRenderer
-> String
-> StateT ClassState Identity (r (Class r))
-> StateT ClassState Identity (r (Class r))
forall (r :: * -> *).
OORenderSym r =>
ClassDocRenderer -> String -> SClass r -> SClass r
docClass ClassDocRenderer
classDox
doxMod :: (OORenderSym r) => String -> String -> [String] -> String -> SFile r ->
SFile r
doxMod :: forall (r :: * -> *).
OORenderSym r =>
String -> String -> [String] -> String -> SFile r -> SFile r
doxMod = ModuleDocRenderer
-> String
-> String
-> [String]
-> String
-> StateT FileState Identity (r (File r))
-> StateT FileState Identity (r (File r))
forall (r :: * -> *).
OORenderSym r =>
ModuleDocRenderer
-> String -> String -> [String] -> String -> SFile r -> SFile r
docMod ModuleDocRenderer
moduleDox
extVar :: (CommonRenderSym r) => Label -> Label -> VSType r -> SVariable r
extVar :: forall (r :: * -> *).
CommonRenderSym r =>
String -> String -> VSType r -> SVariable r
extVar String
l String
n VSType r
t = String
-> VSType r -> Doc -> StateT ValueState Identity (r (Variable r))
forall (r :: * -> *).
CommonRenderSym r =>
String -> VSType r -> Doc -> SVariable r
mkStateVar (String
l String -> String -> String
`access` String
n) VSType r
t (String -> String -> Doc
R.extVar String
l String
n)
classVar :: (CommonRenderSym r) => (Doc -> Doc -> Doc) -> VSType r -> SVariable r ->
SVariable r
classVar :: forall (r :: * -> *).
CommonRenderSym r =>
(Doc -> Doc -> Doc) -> VSType r -> SVariable r -> SVariable r
classVar Doc -> Doc -> Doc
f VSType r
c' SVariable r
v'= do
r (Type r)
c <- VSType r
c'
r (Variable r)
v <- SVariable r
v'
r (Variable r)
vr <- Binding -> String -> VSType r -> Doc -> SVariable r
forall (r :: * -> *).
RenderVariable r =>
Binding -> String -> VSType r -> Doc -> SVariable r
varFromData
(r (Variable r) -> Binding
forall (r :: * -> *).
InternalVarElim r =>
r (Variable r) -> Binding
variableBind r (Variable r)
v) (r (Type r) -> String
forall (r :: * -> *). TypeElim r => r (Type r) -> String
getTypeString r (Type r)
c String -> String -> String
`access` r (Variable r) -> String
forall (r :: * -> *). VariableElim r => r (Variable r) -> String
variableName r (Variable r)
v)
(r (Type r) -> VSType r
forall a s. a -> State s a
toState (r (Type r) -> VSType r) -> r (Type r) -> VSType r
forall a b. (a -> b) -> a -> b
$ r (Variable r) -> r (Type r)
forall (r :: * -> *).
VariableElim r =>
r (Variable r) -> r (Type r)
variableType r (Variable r)
v) (Doc -> Doc -> Doc
f (r (Type r) -> Doc
forall (r :: * -> *). InternalTypeElim r => r (Type r) -> Doc
RC.type' r (Type r)
c) (r (Variable r) -> Doc
forall (r :: * -> *). InternalVarElim r => r (Variable r) -> Doc
RC.variable r (Variable r)
v))
r (Variable r) -> SVariable r
forall a s. a -> State s a
toState (r (Variable r) -> SVariable r) -> r (Variable r) -> SVariable r
forall a b. (a -> b) -> a -> b
$ r (Variable r) -> r (Variable r)
forall (r :: * -> *).
CommonRenderSym r =>
r (Variable r) -> r (Variable r)
classVarCheckStatic r (Variable r)
vr
objVarSelf :: (OORenderSym r) => SVariable r -> SVariable r
objVarSelf :: forall (r :: * -> *). OORenderSym r => SVariable r -> SVariable r
objVarSelf = StateT ValueState Identity (r (Variable r))
-> StateT ValueState Identity (r (Variable r))
-> StateT ValueState Identity (r (Variable r))
forall (r :: * -> *).
OOVariableSym r =>
SVariable r -> SVariable r -> SVariable r
IG.objVar StateT ValueState Identity (r (Variable r))
forall (r :: * -> *). OOVariableSym r => SVariable r
IG.self
indexOf :: (OORenderSym r) => Label -> SValue r -> SValue r -> SValue r
indexOf :: forall (r :: * -> *).
OORenderSym r =>
String -> SValue r -> SValue r -> SValue r
indexOf String
f SValue r
l SValue r
v = SValue r -> SValue r
forall (r :: * -> *). List r => SValue r -> SValue r
IC.indexToInt (SValue r -> SValue r) -> SValue r -> SValue r
forall a b. (a -> b) -> a -> b
$ SValue r -> VSFunction r -> SValue r
forall (r :: * -> *).
OOFunctionSym r =>
SValue r -> VSFunction r -> SValue r
IG.objAccess SValue r
l (String -> VSType r -> [SValue r] -> VSFunction r
forall (r :: * -> *).
OOFunctionSym r =>
String -> VSType r -> [SValue r] -> VSFunction r
IG.func String
f VSType r
forall (r :: * -> *). TypeSym r => VSType r
IC.int [SValue r
v])
contains :: (OORenderSym r) => Label -> SValue r -> SValue r -> SValue r
contains :: forall (r :: * -> *).
OORenderSym r =>
String -> SValue r -> SValue r -> SValue r
contains String
f SValue r
s SValue r
v = SValue r -> VSFunction r -> SValue r
forall (r :: * -> *).
OOFunctionSym r =>
SValue r -> VSFunction r -> SValue r
IG.objAccess SValue r
s (String -> VSType r -> [SValue r] -> VSFunction r
forall (r :: * -> *).
OOFunctionSym r =>
String -> VSType r -> [SValue r] -> VSFunction r
IG.func String
f VSType r
forall (r :: * -> *). TypeSym r => VSType r
IC.bool [SValue r
v])
containsInt :: (OORenderSym r) => Label -> Label -> SValue r -> SValue r -> SValue r
containsInt :: forall (r :: * -> *).
OORenderSym r =>
String -> String -> SValue r -> SValue r -> SValue r
containsInt String
f String
fn SValue r
s SValue r
v = String -> SValue r -> SValue r -> SValue r
forall (r :: * -> *).
OORenderSym r =>
String -> SValue r -> SValue r -> SValue r
contains String
f SValue r
s SValue r
v SValue r -> SValue r -> SValue r
forall (r :: * -> *).
Comparison r =>
SValue r -> SValue r -> SValue r
?!= SValue r -> VSFunction r -> SValue r
forall (r :: * -> *).
OOFunctionSym r =>
SValue r -> VSFunction r -> SValue r
IG.objAccess SValue r
s (String -> VSType r -> [SValue r] -> VSFunction r
forall (r :: * -> *).
OOFunctionSym r =>
String -> VSType r -> [SValue r] -> VSFunction r
IG.func String
fn VSType r
forall (r :: * -> *). TypeSym r => VSType r
IC.bool [])
listAddFunc :: (OORenderSym r) => Label -> SValue r -> SValue r -> VSFunction r
listAddFunc :: forall (r :: * -> *).
OORenderSym r =>
String -> SValue r -> SValue r -> VSFunction r
listAddFunc String
f SValue r
i SValue r
v = String
-> VSType r
-> [SValue r]
-> StateT ValueState Identity (r (Function r))
forall (r :: * -> *).
OOFunctionSym r =>
String -> VSType r -> [SValue r] -> VSFunction r
IG.func String
f (VSType r -> VSType r
forall (r :: * -> *). TypeSym r => VSType r -> VSType r
IC.listType (VSType r -> VSType r) -> VSType r -> VSType r
forall a b. (a -> b) -> a -> b
$ (r (Value r) -> r (Type r)) -> SValue r -> VSType r
forall a b s. (a -> b) -> State s a -> State s b
onStateValue r (Value r) -> r (Type r)
forall (r :: * -> *). ValueSym r => r (Value r) -> r (Type r)
valueType SValue r
v)
[SValue r
i, SValue r
v]
discardFileLine :: (OORenderSym r) => Label -> SValue r -> MSStatement r
discardFileLine :: forall (r :: * -> *).
OORenderSym r =>
String -> SValue r -> MSStatement r
discardFileLine String
n SValue r
f = SValue r -> MSStatement r
forall (r :: * -> *). StatementSym r => SValue r -> MSStatement r
IC.valStmt (SValue r -> MSStatement r) -> SValue r -> MSStatement r
forall a b. (a -> b) -> a -> b
$ VSType r -> SValue r -> String -> SValue r
forall (r :: * -> *).
InternalValueExp r =>
VSType r -> SValue r -> String -> SValue r
objMethodCallNoParams VSType r
forall (r :: * -> *). TypeSym r => VSType r
IC.string SValue r
f String
n
intClass :: (OORenderSym r, Monad r) => (Label -> Doc -> Doc -> Doc -> Doc ->
Doc) -> Label -> r (Visibility r) -> r ParentSpec -> [CSStateVar r] ->
[SMethod r]-> [SMethod r] -> CS (r Doc)
intClass :: forall (r :: * -> *).
(OORenderSym r, Monad r) =>
(String -> Doc -> Doc -> Doc -> Doc -> Doc)
-> String
-> r (Visibility r)
-> r Doc
-> [CSStateVar r]
-> [SMethod r]
-> [SMethod r]
-> CS (r Doc)
intClass String -> Doc -> Doc -> Doc -> Doc -> Doc
f String
n r (Visibility r)
s r Doc
i [CSStateVar r]
svrs [SMethod r]
cstrs [SMethod r]
mths = do
(ClassState -> ClassState) -> StateT ClassState Identity ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (String -> ClassState -> ClassState
setClassName String
n)
Doc
svs <- ([r (StateVar r)] -> Doc) -> [CSStateVar r] -> State ClassState Doc
forall a b s. ([a] -> b) -> [State s a] -> State s b
onStateList ([Doc] -> Doc
R.stateVarList ([Doc] -> Doc)
-> ([r (StateVar r)] -> [Doc]) -> [r (StateVar r)] -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (r (StateVar r) -> Doc) -> [r (StateVar r)] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map r (StateVar r) -> Doc
forall (r :: * -> *). StateVarElim r => r (StateVar r) -> Doc
RC.stateVar) [CSStateVar r]
svrs
Doc
ms <- ([r (Method r)] -> Doc)
-> [State ClassState (r (Method r))] -> State ClassState Doc
forall a b s. ([a] -> b) -> [State s a] -> State s b
onStateList ([Doc] -> Doc
vibcat ([Doc] -> Doc)
-> ([r (Method r)] -> [Doc]) -> [r (Method r)] -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (r (Method r) -> Doc) -> [r (Method r)] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map r (Method r) -> Doc
forall (r :: * -> *). MethodElim r => r (Method r) -> Doc
RC.method) ((SMethod r -> State ClassState (r (Method r)))
-> [SMethod r] -> [State ClassState (r (Method r))]
forall a b. (a -> b) -> [a] -> [b]
map (LensLike'
(Zoomed (StateT MethodState Identity) (r (Method r)))
ClassState
MethodState
-> SMethod r -> State ClassState (r (Method r))
forall c.
LensLike'
(Zoomed (StateT MethodState Identity) c) ClassState MethodState
-> StateT MethodState Identity c -> StateT ClassState Identity c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
zoom LensLike'
(Zoomed (StateT MethodState Identity) (r (Method r)))
ClassState
MethodState
(MethodState -> Focusing Identity (r (Method r)) MethodState)
-> ClassState -> Focusing Identity (r (Method r)) ClassState
Lens' ClassState MethodState
lensCStoMS) ([SMethod r]
cstrs [SMethod r] -> [SMethod r] -> [SMethod r]
forall a. [a] -> [a] -> [a]
++ [SMethod r]
mths))
r Doc -> CS (r Doc)
forall a. a -> StateT ClassState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (r Doc -> CS (r Doc)) -> r Doc -> CS (r Doc)
forall a b. (a -> b) -> a -> b
$ (Doc -> Doc) -> r Doc -> r Doc
forall (r :: * -> *) a b. Functor r => (a -> b) -> r a -> r b
onCodeValue (\Doc
p -> String -> Doc -> Doc -> Doc -> Doc -> Doc
f String
n Doc
p (r (Visibility r) -> Doc
forall (r :: * -> *). VisibilityElim r => r (Visibility r) -> Doc
RC.visibility r (Visibility r)
s) Doc
svs Doc
ms) r Doc
i
funcType :: (CommonRenderSym r) => [VSType r] -> VSType r -> VSType r
funcType :: forall (r :: * -> *).
CommonRenderSym r =>
[VSType r] -> VSType r -> VSType r
funcType [VSType r]
ps' VSType r
r' = do
[r (Type r)]
ps <- [VSType r] -> StateT ValueState Identity [r (Type r)]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
forall (m :: * -> *) a. Monad m => [m a] -> m [a]
sequence [VSType r]
ps'
r (Type r)
r <- VSType r
r'
CodeType -> String -> Doc -> VSType r
forall (r :: * -> *).
RenderType r =>
CodeType -> String -> Doc -> VSType r
typeFromData ([CodeType] -> CodeType -> CodeType
Func ((r (Type r) -> CodeType) -> [r (Type r)] -> [CodeType]
forall a b. (a -> b) -> [a] -> [b]
map r (Type r) -> CodeType
forall (r :: * -> *). TypeElim r => r (Type r) -> CodeType
getType [r (Type r)]
ps) (r (Type r) -> CodeType
forall (r :: * -> *). TypeElim r => r (Type r) -> CodeType
getType r (Type r)
r)) String
"" Doc
empty
buildModule :: (OORenderSym r) => Label -> FS Doc -> FS Doc -> FS Doc ->
[SMethod r] -> [SClass r] -> FSModule r
buildModule :: forall (r :: * -> *).
OORenderSym r =>
String
-> FS Doc
-> FS Doc
-> FS Doc
-> [SMethod r]
-> [SClass r]
-> FSModule r
buildModule String
n FS Doc
imps FS Doc
top FS Doc
bot [SMethod r]
fs [SClass r]
cs = String -> FS Doc -> StateT FileState Identity (r (Module r))
forall (r :: * -> *). RenderMod r => String -> FS Doc -> FSModule r
S.modFromData String
n (do
[r (Class r)]
cls <- (SClass r -> StateT FileState Identity (r (Class r)))
-> [SClass r] -> StateT FileState Identity [r (Class r)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (LensLike'
(Zoomed (StateT ClassState Identity) (r (Class r)))
FileState
ClassState
-> SClass r -> StateT FileState Identity (r (Class r))
forall c.
LensLike'
(Zoomed (StateT ClassState Identity) c) FileState ClassState
-> StateT ClassState Identity c -> StateT FileState Identity c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
zoom LensLike'
(Zoomed (StateT ClassState Identity) (r (Class r)))
FileState
ClassState
(ClassState -> Focusing Identity (r (Class r)) ClassState)
-> FileState -> Focusing Identity (r (Class r)) FileState
Lens' FileState ClassState
lensFStoCS) [SClass r]
cs
[r (Method r)]
fns <- (SMethod r -> StateT FileState Identity (r (Method r)))
-> [SMethod r] -> StateT FileState Identity [r (Method r)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (LensLike'
(Zoomed (StateT MethodState Identity) (r (Method r)))
FileState
MethodState
-> SMethod r -> StateT FileState Identity (r (Method r))
forall c.
LensLike'
(Zoomed (StateT MethodState Identity) c) FileState MethodState
-> StateT MethodState Identity c -> StateT FileState Identity c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
zoom LensLike'
(Zoomed (StateT MethodState Identity) (r (Method r)))
FileState
MethodState
(MethodState -> Focusing Identity (r (Method r)) MethodState)
-> FileState -> Focusing Identity (r (Method r)) FileState
Lens' FileState MethodState
lensFStoMS) [SMethod r]
fs
Doc
is <- FS Doc
imps
Doc
tp <- FS Doc
top
Doc
bt <- FS Doc
bot
Doc -> FS Doc
forall a. a -> StateT FileState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc -> FS Doc) -> Doc -> FS Doc
forall a b. (a -> b) -> a -> b
$ Doc -> Doc -> Doc -> Doc
R.module' Doc
is ([Doc] -> Doc
vibcat (Doc
tp Doc -> [Doc] -> [Doc]
forall a. a -> [a] -> [a]
: (r (Class r) -> Doc) -> [r (Class r)] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map r (Class r) -> Doc
forall (r :: * -> *). ClassElim r => r (Class r) -> Doc
RC.class' [r (Class r)]
cls))
([Doc] -> Doc
vibcat ((r (Method r) -> Doc) -> [r (Method r)] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map r (Method r) -> Doc
forall (r :: * -> *). MethodElim r => r (Method r) -> Doc
RC.method [r (Method r)]
fns [Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++ [Doc
bt])))
arrayType :: (CommonRenderSym r) => VSType r -> VSType r
arrayType :: forall (r :: * -> *). CommonRenderSym r => VSType r -> VSType r
arrayType VSType r
t' = do
r (Type r)
t <- VSType r
t'
CodeType -> String -> Doc -> VSType r
forall (r :: * -> *).
RenderType r =>
CodeType -> String -> Doc -> VSType r
typeFromData (CodeType -> CodeType
Array (r (Type r) -> CodeType
forall (r :: * -> *). TypeElim r => r (Type r) -> CodeType
getType r (Type r)
t))
(r (Type r) -> String
forall (r :: * -> *). TypeElim r => r (Type r) -> String
getTypeString r (Type r)
t String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
array) (r (Type r) -> Doc
forall (r :: * -> *). InternalTypeElim r => r (Type r) -> Doc
RC.type' r (Type r)
t Doc -> Doc -> Doc
<> Doc -> Doc
brackets Doc
empty)
pi :: (CommonRenderSym r) => SValue r
pi :: forall (r :: * -> *). CommonRenderSym r => SValue r
pi = VSType r -> Doc -> StateT ValueState Identity (r (Value r))
forall (r :: * -> *).
CommonRenderSym r =>
VSType r -> Doc -> SValue r
mkStateVal VSType r
forall (r :: * -> *). TypeSym r => VSType r
IC.double (String -> Doc
text (String -> Doc) -> String -> Doc
forall a b. (a -> b) -> a -> b
$ String -> String
mathFunc String
"PI")
printSt :: (CommonRenderSym r) => SValue r -> SValue r -> MSStatement r
printSt :: forall (r :: * -> *).
CommonRenderSym r =>
SValue r -> SValue r -> MSStatement r
printSt SValue r
va' SValue r
vb' = do
r (Value r)
va <- LensLike'
(Zoomed (StateT ValueState Identity) (r (Value r)))
MethodState
ValueState
-> SValue r -> StateT MethodState Identity (r (Value r))
forall c.
LensLike'
(Zoomed (StateT ValueState Identity) c) MethodState ValueState
-> StateT ValueState Identity c -> StateT MethodState Identity c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
zoom LensLike'
(Zoomed (StateT ValueState Identity) (r (Value r)))
MethodState
ValueState
(ValueState -> Focusing Identity (r (Value r)) ValueState)
-> MethodState -> Focusing Identity (r (Value r)) MethodState
Lens' MethodState ValueState
lensMStoVS SValue r
va'
r (Value r)
vb <- LensLike'
(Zoomed (StateT ValueState Identity) (r (Value r)))
MethodState
ValueState
-> SValue r -> StateT MethodState Identity (r (Value r))
forall c.
LensLike'
(Zoomed (StateT ValueState Identity) c) MethodState ValueState
-> StateT ValueState Identity c -> StateT MethodState Identity c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
zoom LensLike'
(Zoomed (StateT ValueState Identity) (r (Value r)))
MethodState
ValueState
(ValueState -> Focusing Identity (r (Value r)) ValueState)
-> MethodState -> Focusing Identity (r (Value r)) MethodState
Lens' MethodState ValueState
lensMStoVS SValue r
vb'
Doc -> MSStatement r
forall (r :: * -> *). CommonRenderSym r => Doc -> MSStatement r
mkStmt (r (Value r) -> r (Value r) -> Doc
forall (r :: * -> *).
CommonRenderSym r =>
r (Value r) -> r (Value r) -> Doc
R.print r (Value r)
va r (Value r)
vb)
arrayDec :: (CommonRenderSym r) => SValue r -> SVariable r -> r (Scope r)
-> MSStatement r
arrayDec :: forall (r :: * -> *).
CommonRenderSym r =>
SValue r -> SVariable r -> r (Scope r) -> MSStatement r
arrayDec SValue r
n SVariable r
vr r (Scope r)
scp = do
r (Value r)
sz <- LensLike'
(Zoomed (StateT ValueState Identity) (r (Value r)))
MethodState
ValueState
-> SValue r -> StateT MethodState Identity (r (Value r))
forall c.
LensLike'
(Zoomed (StateT ValueState Identity) c) MethodState ValueState
-> StateT ValueState Identity c -> StateT MethodState Identity c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
zoom LensLike'
(Zoomed (StateT ValueState Identity) (r (Value r)))
MethodState
ValueState
(ValueState -> Focusing Identity (r (Value r)) ValueState)
-> MethodState -> Focusing Identity (r (Value r)) MethodState
Lens' MethodState ValueState
lensMStoVS SValue r
n
r (Variable r)
v <- LensLike'
(Zoomed (StateT ValueState Identity) (r (Variable r)))
MethodState
ValueState
-> SVariable r -> StateT MethodState Identity (r (Variable r))
forall c.
LensLike'
(Zoomed (StateT ValueState Identity) c) MethodState ValueState
-> StateT ValueState Identity c -> StateT MethodState Identity c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
zoom LensLike'
(Zoomed (StateT ValueState Identity) (r (Variable r)))
MethodState
ValueState
(ValueState -> Focusing Identity (r (Variable r)) ValueState)
-> MethodState -> Focusing Identity (r (Variable r)) MethodState
Lens' MethodState ValueState
lensMStoVS SVariable r
vr
(MethodState -> MethodState) -> StateT MethodState Identity ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((MethodState -> MethodState) -> StateT MethodState Identity ())
-> (MethodState -> MethodState) -> StateT MethodState Identity ()
forall a b. (a -> b) -> a -> b
$ String -> MethodState -> MethodState
useVarName (String -> MethodState -> MethodState)
-> String -> MethodState -> MethodState
forall a b. (a -> b) -> a -> b
$ r (Variable r) -> String
forall (r :: * -> *). VariableElim r => r (Variable r) -> String
variableName r (Variable r)
v
(MethodState -> MethodState) -> StateT MethodState Identity ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((MethodState -> MethodState) -> StateT MethodState Identity ())
-> (MethodState -> MethodState) -> StateT MethodState Identity ()
forall a b. (a -> b) -> a -> b
$ String -> ScopeData -> MethodState -> MethodState
setVarScope (r (Variable r) -> String
forall (r :: * -> *). VariableElim r => r (Variable r) -> String
variableName r (Variable r)
v) (r (Scope r) -> ScopeData
forall (r :: * -> *). ScopeElim r => r (Scope r) -> ScopeData
scopeData r (Scope r)
scp)
let tp :: r (Type r)
tp = r (Variable r) -> r (Type r)
forall (r :: * -> *).
VariableElim r =>
r (Variable r) -> r (Type r)
variableType r (Variable r)
v
r (Type r)
innerTp <- LensLike'
(Zoomed (StateT ValueState Identity) (r (Type r)))
MethodState
ValueState
-> StateT ValueState Identity (r (Type r))
-> StateT MethodState Identity (r (Type r))
forall c.
LensLike'
(Zoomed (StateT ValueState Identity) c) MethodState ValueState
-> StateT ValueState Identity c -> StateT MethodState Identity c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
zoom LensLike'
(Zoomed (StateT ValueState Identity) (r (Type r)))
MethodState
ValueState
(ValueState -> Focusing Identity (r (Type r)) ValueState)
-> MethodState -> Focusing Identity (r (Type r)) MethodState
Lens' MethodState ValueState
lensMStoVS (StateT ValueState Identity (r (Type r))
-> StateT MethodState Identity (r (Type r)))
-> StateT ValueState Identity (r (Type r))
-> StateT MethodState Identity (r (Type r))
forall a b. (a -> b) -> a -> b
$ StateT ValueState Identity (r (Type r))
-> StateT ValueState Identity (r (Type r))
forall (r :: * -> *). TypeSym r => VSType r -> VSType r
listInnerType (StateT ValueState Identity (r (Type r))
-> StateT ValueState Identity (r (Type r)))
-> StateT ValueState Identity (r (Type r))
-> StateT ValueState Identity (r (Type r))
forall a b. (a -> b) -> a -> b
$ r (Type r) -> StateT ValueState Identity (r (Type r))
forall a. a -> StateT ValueState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return r (Type r)
tp
Doc -> MSStatement r
forall (r :: * -> *). CommonRenderSym r => Doc -> MSStatement r
mkStmt (Doc -> MSStatement r) -> Doc -> MSStatement r
forall a b. (a -> b) -> a -> b
$ r (Type r) -> Doc
forall (r :: * -> *). InternalTypeElim r => r (Type r) -> Doc
RC.type' r (Type r)
tp Doc -> Doc -> Doc
<+> r (Variable r) -> Doc
forall (r :: * -> *). InternalVarElim r => r (Variable r) -> Doc
RC.variable r (Variable r)
v Doc -> Doc -> Doc
<+> Doc
equals Doc -> Doc -> Doc
<+> Doc
new' Doc -> Doc -> Doc
<+>
r (Type r) -> Doc
forall (r :: * -> *). InternalTypeElim r => r (Type r) -> Doc
RC.type' r (Type r)
innerTp Doc -> Doc -> Doc
<> Doc -> Doc
brackets (r (Value r) -> Doc
forall (r :: * -> *). ValueElim r => r (Value r) -> Doc
RC.value r (Value r)
sz)
arrayDecDef :: (CommonRenderSym r) => SVariable r -> r (Scope r) ->
[SValue r] -> MSStatement r
arrayDecDef :: forall (r :: * -> *).
CommonRenderSym r =>
SVariable r -> r (Scope r) -> [SValue r] -> MSStatement r
arrayDecDef SVariable r
v' r (Scope r)
scp [SValue r]
vals' = do
[r (Value r)]
vs <- (SValue r -> StateT MethodState Identity (r (Value r)))
-> [SValue r] -> StateT MethodState Identity [r (Value r)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (LensLike'
(Zoomed (StateT ValueState Identity) (r (Value r)))
MethodState
ValueState
-> SValue r -> StateT MethodState Identity (r (Value r))
forall c.
LensLike'
(Zoomed (StateT ValueState Identity) c) MethodState ValueState
-> StateT ValueState Identity c -> StateT MethodState Identity c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
zoom LensLike'
(Zoomed (StateT ValueState Identity) (r (Value r)))
MethodState
ValueState
(ValueState -> Focusing Identity (r (Value r)) ValueState)
-> MethodState -> Focusing Identity (r (Value r)) MethodState
Lens' MethodState ValueState
lensMStoVS) [SValue r]
vals'
r (Statement r)
vd <- SVariable r -> r (Scope r) -> MSStatement r
forall (r :: * -> *).
DeclStatement r =>
SVariable r -> r (Scope r) -> MSStatement r
IC.varDec SVariable r
v' r (Scope r)
scp
Doc -> MSStatement r
forall (r :: * -> *). CommonRenderSym r => Doc -> MSStatement r
mkStmt (r (Statement r) -> Doc
forall (r :: * -> *). StatementElim r => r (Statement r) -> Doc
RC.statement r (Statement r)
vd Doc -> Doc -> Doc
<+> Doc
equals Doc -> Doc -> Doc
<+> Doc -> Doc
braces ([r (Value r)] -> Doc
forall (r :: * -> *). CommonRenderSym r => [r (Value r)] -> Doc
valueList [r (Value r)]
vs))
openFileA :: (CommonRenderSym r) => (SValue r -> VSType r -> SValue r -> SValue r) ->
SVariable r -> SValue r -> MSStatement r
openFileA :: forall (r :: * -> *).
CommonRenderSym r =>
(SValue r -> VSType r -> SValue r -> SValue r)
-> SVariable r -> SValue r -> MSStatement r
openFileA SValue r -> VSType r -> SValue r -> SValue r
f SVariable r
vr SValue r
vl = SVariable r
vr SVariable r
-> SValue r -> StateT MethodState Identity (r (Statement r))
forall (r :: * -> *).
AssignStatement r =>
SVariable r -> SValue r -> MSStatement r
&= SValue r -> VSType r -> SValue r -> SValue r
f SValue r
vl VSType r
forall (r :: * -> *). TypeSym r => VSType r
outfile SValue r
forall (r :: * -> *). Literal r => SValue r
IC.litTrue
forEach :: (CommonRenderSym r) => Doc -> Doc -> Doc -> Doc -> SVariable r -> SValue r
-> MSBody r -> MSStatement r
forEach :: forall (r :: * -> *).
CommonRenderSym r =>
Doc
-> Doc
-> Doc
-> Doc
-> SVariable r
-> SValue r
-> MSBody r
-> MSStatement r
forEach Doc
bStart Doc
bEnd Doc
forEachLabel Doc
inLbl SVariable r
e' SValue r
v' MSBody r
b' = do
r (Variable r)
e <- LensLike'
(Zoomed (StateT ValueState Identity) (r (Variable r)))
MethodState
ValueState
-> SVariable r -> StateT MethodState Identity (r (Variable r))
forall c.
LensLike'
(Zoomed (StateT ValueState Identity) c) MethodState ValueState
-> StateT ValueState Identity c -> StateT MethodState Identity c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
zoom LensLike'
(Zoomed (StateT ValueState Identity) (r (Variable r)))
MethodState
ValueState
(ValueState -> Focusing Identity (r (Variable r)) ValueState)
-> MethodState -> Focusing Identity (r (Variable r)) MethodState
Lens' MethodState ValueState
lensMStoVS SVariable r
e'
r (Value r)
v <- LensLike'
(Zoomed (StateT ValueState Identity) (r (Value r)))
MethodState
ValueState
-> SValue r -> StateT MethodState Identity (r (Value r))
forall c.
LensLike'
(Zoomed (StateT ValueState Identity) c) MethodState ValueState
-> StateT ValueState Identity c -> StateT MethodState Identity c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
zoom LensLike'
(Zoomed (StateT ValueState Identity) (r (Value r)))
MethodState
ValueState
(ValueState -> Focusing Identity (r (Value r)) ValueState)
-> MethodState -> Focusing Identity (r (Value r)) MethodState
Lens' MethodState ValueState
lensMStoVS SValue r
v'
r (Body r)
b <- MSBody r
b'
Doc -> MSStatement r
forall (r :: * -> *). CommonRenderSym r => Doc -> MSStatement r
mkStmtNoEnd (Doc -> MSStatement r) -> Doc -> MSStatement r
forall a b. (a -> b) -> a -> b
$ [Doc] -> Doc
vcat [
Doc
forEachLabel Doc -> Doc -> Doc
<+> Doc -> Doc
parens (r (Type r) -> Doc
forall (r :: * -> *). InternalTypeElim r => r (Type r) -> Doc
RC.type' (r (Variable r) -> r (Type r)
forall (r :: * -> *).
VariableElim r =>
r (Variable r) -> r (Type r)
variableType r (Variable r)
e) Doc -> Doc -> Doc
<+> r (Variable r) -> Doc
forall (r :: * -> *). InternalVarElim r => r (Variable r) -> Doc
RC.variable r (Variable r)
e Doc -> Doc -> Doc
<+>
Doc
inLbl Doc -> Doc -> Doc
<+> r (Value r) -> Doc
forall (r :: * -> *). ValueElim r => r (Value r) -> Doc
RC.value r (Value r)
v) Doc -> Doc -> Doc
<+> Doc
bStart,
Doc -> Doc
indent (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ r (Body r) -> Doc
forall (r :: * -> *). BodyElim r => r (Body r) -> Doc
RC.body r (Body r)
b,
Doc
bEnd]
mainDesc, argsDesc :: String
mainDesc :: String
mainDesc = String
"Controls the flow of the program"
argsDesc :: String
argsDesc = String
"List of command-line arguments"
docMain :: (OORenderSym r) => MSBody r -> SMethod r
docMain :: forall (r :: * -> *). OORenderSym r => MSBody r -> SMethod r
docMain MSBody r
b = MS (r (BlockComment r))
-> StateT MethodState Identity (r (Method r))
-> StateT MethodState Identity (r (Method r))
forall (r :: * -> *).
RenderMethod r =>
MS (r (BlockComment r)) -> SMethod r -> SMethod r
commentedFunc (State MethodState [String] -> MS (r (BlockComment r))
forall a. State a [String] -> State a (r (BlockComment r))
forall (r :: * -> *) a.
BlockCommentSym r =>
State a [String] -> State a (r (BlockComment r))
docComment (State MethodState [String] -> MS (r (BlockComment r)))
-> State MethodState [String] -> MS (r (BlockComment r))
forall a b. (a -> b) -> a -> b
$ [String] -> State MethodState [String]
forall a s. a -> State s a
toState ([String] -> State MethodState [String])
-> [String] -> State MethodState [String]
forall a b. (a -> b) -> a -> b
$ FuncDocRenderer
functionDox
String
mainDesc [(String
args, String
argsDesc)] []) (MSBody r -> StateT MethodState Identity (r (Method r))
forall (r :: * -> *). MethodSym r => MSBody r -> SMethod r
IC.mainFunction MSBody r
b)
mainFunction :: (OORenderSym r) => VSType r -> Label -> MSBody r -> SMethod r
mainFunction :: forall (r :: * -> *).
OORenderSym r =>
VSType r -> String -> MSBody r -> SMethod r
mainFunction VSType r
s String
n = Bool
-> String
-> r (Visibility r)
-> r (Permanence r)
-> MSMthdType r
-> [MSParameter r]
-> StateT MethodState Identity (r (Body r))
-> StateT MethodState Identity (r (Method r))
forall (r :: * -> *).
OORenderMethod r =>
Bool
-> String
-> r (Visibility r)
-> r (Permanence r)
-> MSMthdType r
-> [MSParameter r]
-> MSBody r
-> SMethod r
S.intFunc Bool
True String
n r (Visibility r)
forall (r :: * -> *). VisibilitySym r => r (Visibility r)
public r (Permanence r)
forall (r :: * -> *). PermanenceSym r => r (Permanence r)
static (VSType r -> MSMthdType r
forall (r :: * -> *). MethodTypeSym r => VSType r -> MSMthdType r
mType VSType r
forall (r :: * -> *). TypeSym r => VSType r
IC.void)
[SVariable r -> MSParameter r
forall (r :: * -> *).
ParameterSym r =>
SVariable r -> MSParameter r
IC.param (String -> VSType r -> SVariable r
forall (r :: * -> *).
VariableSym r =>
String -> VSType r -> SVariable r
IC.var String
args (VSType r
s VSType r -> (r (Type r) -> VSType r) -> VSType r
forall a b.
StateT ValueState Identity a
-> (a -> StateT ValueState Identity b)
-> StateT ValueState Identity b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (\r (Type r)
argT -> CodeType -> String -> Doc -> VSType r
forall (r :: * -> *).
RenderType r =>
CodeType -> String -> Doc -> VSType r
typeFromData (CodeType -> CodeType
List CodeType
String)
(Doc -> String
render (r (Type r) -> Doc
forall (r :: * -> *). InternalTypeElim r => r (Type r) -> Doc
RC.type' r (Type r)
argT) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
array) (r (Type r) -> Doc
forall (r :: * -> *). InternalTypeElim r => r (Type r) -> Doc
RC.type' r (Type r)
argT Doc -> Doc -> Doc
<> Doc
array'))))]
buildModule' :: (OORenderSym r) => Label -> (String -> r (Import r)) -> [Label]
-> [SMethod r] -> [SClass r] -> FSModule r
buildModule' :: forall (r :: * -> *).
OORenderSym r =>
String
-> (String -> r (Import r))
-> [String]
-> [SMethod r]
-> [SClass r]
-> FSModule r
buildModule' String
n String -> r (Import r)
inc [String]
is [SMethod r]
ms [SClass r]
cs = String -> FS Doc -> StateT FileState Identity (r (Module r))
forall (r :: * -> *). RenderMod r => String -> FS Doc -> FSModule r
S.modFromData String
n (do
[r (Class r)]
cls <- (SClass r -> StateT FileState Identity (r (Class r)))
-> [SClass r] -> StateT FileState Identity [r (Class r)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (LensLike'
(Zoomed (StateT ClassState Identity) (r (Class r)))
FileState
ClassState
-> SClass r -> StateT FileState Identity (r (Class r))
forall c.
LensLike'
(Zoomed (StateT ClassState Identity) c) FileState ClassState
-> StateT ClassState Identity c -> StateT FileState Identity c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
zoom LensLike'
(Zoomed (StateT ClassState Identity) (r (Class r)))
FileState
ClassState
(ClassState -> Focusing Identity (r (Class r)) ClassState)
-> FileState -> Focusing Identity (r (Class r)) FileState
Lens' FileState ClassState
lensFStoCS)
(if [SMethod r] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [SMethod r]
ms then [SClass r]
cs else Maybe String
-> [CSStateVar r] -> [SMethod r] -> [SMethod r] -> SClass r
forall (r :: * -> *).
ClassSym r =>
Maybe String
-> [CSStateVar r] -> [SMethod r] -> [SMethod r] -> SClass r
IG.buildClass Maybe String
forall a. Maybe a
Nothing [] [] [SMethod r]
ms SClass r -> [SClass r] -> [SClass r]
forall a. a -> [a] -> [a]
: [SClass r]
cs)
[String]
lis <- FS [String]
getLangImports
[String]
libis <- FS [String]
getLibImports
[String]
mis <- FS [String]
getModuleImports
Doc -> FS Doc
forall a. a -> StateT FileState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc -> FS Doc) -> Doc -> FS Doc
forall a b. (a -> b) -> a -> b
$ [Doc] -> Doc
vibcat [
[Doc] -> Doc
vcat ((String -> Doc) -> [String] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (r (Import r) -> Doc
forall (r :: * -> *). ImportElim r => r (Import r) -> Doc
RC.import' (r (Import r) -> Doc) -> (String -> r (Import r)) -> String -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> r (Import r)
inc) ([String]
lis [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String] -> [String]
forall a. Ord a => [a] -> [a]
sort ([String]
is [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
libis) [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
mis)),
[Doc] -> Doc
vibcat ((r (Class r) -> Doc) -> [r (Class r)] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map r (Class r) -> Doc
forall (r :: * -> *). ClassElim r => r (Class r) -> Doc
RC.class' [r (Class r)]
cls)])
call' :: (CommonRenderSym r) => String -> Maybe Library -> Maybe Doc -> MixedCall r
call' :: forall (r :: * -> *).
CommonRenderSym r =>
String -> Maybe String -> Maybe Doc -> MixedCall r
call' String
l Maybe String
_ Maybe Doc
_ String
_ VSType r
_ [SValue r]
_ ((SVariable r, SValue r)
_:[(SVariable r, SValue r)]
_) = String -> SValue r
forall a. HasCallStack => String -> a
error (String -> SValue r) -> String -> SValue r
forall a b. (a -> b) -> a -> b
$ String -> String
namedArgError String
l
call' String
_ Maybe String
l Maybe Doc
o String
n VSType r
t [SValue r]
ps [(SVariable r, SValue r)]
ns = Doc -> Maybe String -> Maybe Doc -> MixedCall r
forall (r :: * -> *).
CommonRenderSym r =>
Doc -> Maybe String -> Maybe Doc -> MixedCall r
call Doc
empty Maybe String
l Maybe Doc
o String
n VSType r
t [SValue r]
ps [(SVariable r, SValue r)]
ns
namedArgError :: String -> String
namedArgError :: String -> String
namedArgError String
l = String
"Named arguments not supported in " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
l
listSizeFunc :: (OORenderSym r) => VSFunction r
listSizeFunc :: forall (r :: * -> *). OORenderSym r => VSFunction r
listSizeFunc = String
-> VSType r
-> [SValue r]
-> StateT ValueState Identity (r (Function r))
forall (r :: * -> *).
OOFunctionSym r =>
String -> VSType r -> [SValue r] -> VSFunction r
IG.func String
"size" VSType r
forall (r :: * -> *). TypeSym r => VSType r
IC.int []
listAccessFunc' :: (OORenderSym r) => Label -> VSType r -> SValue r ->
VSFunction r
listAccessFunc' :: forall (r :: * -> *).
OORenderSym r =>
String -> VSType r -> SValue r -> VSFunction r
listAccessFunc' String
f VSType r
t SValue r
i = String
-> VSType r
-> [SValue r]
-> StateT ValueState Identity (r (Function r))
forall (r :: * -> *).
OOFunctionSym r =>
String -> VSType r -> [SValue r] -> VSFunction r
IG.func String
f VSType r
t [SValue r -> SValue r
forall (r :: * -> *). CommonRenderSym r => SValue r -> SValue r
intValue SValue r
i]
stringRender :: String
stringRender :: String
stringRender = String
"string"
string :: (CommonRenderSym r) => VSType r
string :: forall (r :: * -> *). CommonRenderSym r => VSType r
string = CodeType
-> String -> Doc -> StateT ValueState Identity (r (Type r))
forall (r :: * -> *).
RenderType r =>
CodeType -> String -> Doc -> VSType r
typeFromData CodeType
String String
stringRender (String -> Doc
text String
stringRender)
constDecDef :: (CommonRenderSym r) => SVariable r -> r (Scope r) -> SValue r
-> MSStatement r
constDecDef :: forall (r :: * -> *).
CommonRenderSym r =>
SVariable r -> r (Scope r) -> SValue r -> MSStatement r
constDecDef SVariable r
vr' r (Scope r)
scp SValue r
v'= do
r (Variable r)
vr <- LensLike'
(Zoomed (StateT ValueState Identity) (r (Variable r)))
MethodState
ValueState
-> SVariable r -> StateT MethodState Identity (r (Variable r))
forall c.
LensLike'
(Zoomed (StateT ValueState Identity) c) MethodState ValueState
-> StateT ValueState Identity c -> StateT MethodState Identity c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
zoom LensLike'
(Zoomed (StateT ValueState Identity) (r (Variable r)))
MethodState
ValueState
(ValueState -> Focusing Identity (r (Variable r)) ValueState)
-> MethodState -> Focusing Identity (r (Variable r)) MethodState
Lens' MethodState ValueState
lensMStoVS SVariable r
vr'
r (Value r)
v <- LensLike'
(Zoomed (StateT ValueState Identity) (r (Value r)))
MethodState
ValueState
-> SValue r -> StateT MethodState Identity (r (Value r))
forall c.
LensLike'
(Zoomed (StateT ValueState Identity) c) MethodState ValueState
-> StateT ValueState Identity c -> StateT MethodState Identity c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
zoom LensLike'
(Zoomed (StateT ValueState Identity) (r (Value r)))
MethodState
ValueState
(ValueState -> Focusing Identity (r (Value r)) ValueState)
-> MethodState -> Focusing Identity (r (Value r)) MethodState
Lens' MethodState ValueState
lensMStoVS SValue r
v'
(MethodState -> MethodState) -> StateT MethodState Identity ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((MethodState -> MethodState) -> StateT MethodState Identity ())
-> (MethodState -> MethodState) -> StateT MethodState Identity ()
forall a b. (a -> b) -> a -> b
$ String -> MethodState -> MethodState
useVarName (String -> MethodState -> MethodState)
-> String -> MethodState -> MethodState
forall a b. (a -> b) -> a -> b
$ r (Variable r) -> String
forall (r :: * -> *). VariableElim r => r (Variable r) -> String
variableName r (Variable r)
vr
(MethodState -> MethodState) -> StateT MethodState Identity ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((MethodState -> MethodState) -> StateT MethodState Identity ())
-> (MethodState -> MethodState) -> StateT MethodState Identity ()
forall a b. (a -> b) -> a -> b
$ String -> ScopeData -> MethodState -> MethodState
setVarScope (r (Variable r) -> String
forall (r :: * -> *). VariableElim r => r (Variable r) -> String
variableName r (Variable r)
vr) (r (Scope r) -> ScopeData
forall (r :: * -> *). ScopeElim r => r (Scope r) -> ScopeData
scopeData r (Scope r)
scp)
Doc -> MSStatement r
forall (r :: * -> *). CommonRenderSym r => Doc -> MSStatement r
mkStmt (r (Variable r) -> r (Value r) -> Doc
forall (r :: * -> *).
CommonRenderSym r =>
r (Variable r) -> r (Value r) -> Doc
R.constDecDef r (Variable r)
vr r (Value r)
v)
docInOutFunc :: (CommonRenderSym 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
docInOutFunc :: forall (r :: * -> *).
CommonRenderSym 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
docInOutFunc [SVariable r]
-> [SVariable r] -> [SVariable r] -> MSBody r -> SMethod r
f String
desc [(String, SVariable r)]
is [(String, SVariable r)
o] [] MSBody r
b = FuncDocRenderer
-> String -> [String] -> [String] -> SMethod r -> SMethod r
forall (r :: * -> *).
CommonRenderSym r =>
FuncDocRenderer
-> String -> [String] -> [String] -> SMethod r -> SMethod r
docFuncRepr FuncDocRenderer
functionDox String
desc (((String, SVariable r) -> String)
-> [(String, SVariable r)] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String, SVariable r) -> String
forall a b. (a, b) -> a
fst [(String, SVariable r)]
is)
[(String, SVariable r) -> String
forall a b. (a, b) -> a
fst (String, SVariable r)
o] ([SVariable r]
-> [SVariable r] -> [SVariable r] -> MSBody r -> SMethod r
f (((String, SVariable r) -> SVariable r)
-> [(String, SVariable r)] -> [SVariable r]
forall a b. (a -> b) -> [a] -> [b]
map (String, SVariable r) -> SVariable r
forall a b. (a, b) -> b
snd [(String, SVariable r)]
is) [(String, SVariable r) -> SVariable r
forall a b. (a, b) -> b
snd (String, SVariable r)
o] [] MSBody r
b)
docInOutFunc [SVariable r]
-> [SVariable r] -> [SVariable r] -> MSBody r -> SMethod r
f String
desc [(String, SVariable r)]
is [] [(String, SVariable r)
both] MSBody r
b = FuncDocRenderer
-> String -> [String] -> [String] -> SMethod r -> SMethod r
forall (r :: * -> *).
CommonRenderSym r =>
FuncDocRenderer
-> String -> [String] -> [String] -> SMethod r -> SMethod r
docFuncRepr FuncDocRenderer
functionDox String
desc (((String, SVariable r) -> String)
-> [(String, SVariable r)] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String, SVariable r) -> String
forall a b. (a, b) -> a
fst ([(String, SVariable r)] -> [String])
-> [(String, SVariable r)] -> [String]
forall a b. (a -> b) -> a -> b
$
(String, SVariable r)
both (String, SVariable r)
-> [(String, SVariable r)] -> [(String, SVariable r)]
forall a. a -> [a] -> [a]
: [(String, SVariable r)]
is) [(String, SVariable r) -> String
forall a b. (a, b) -> a
fst (String, SVariable r)
both] ([SVariable r]
-> [SVariable r] -> [SVariable r] -> MSBody r -> SMethod r
f (((String, SVariable r) -> SVariable r)
-> [(String, SVariable r)] -> [SVariable r]
forall a b. (a -> b) -> [a] -> [b]
map (String, SVariable r) -> SVariable r
forall a b. (a, b) -> b
snd [(String, SVariable r)]
is) [] [(String, SVariable r) -> SVariable r
forall a b. (a, b) -> b
snd (String, SVariable r)
both] MSBody r
b)
docInOutFunc [SVariable r]
-> [SVariable r] -> [SVariable r] -> MSBody r -> SMethod r
f String
desc [(String, SVariable r)]
is [(String, SVariable r)]
os [(String, SVariable r)]
bs MSBody r
b = FuncDocRenderer
-> String -> [String] -> [String] -> SMethod r -> SMethod r
forall (r :: * -> *).
CommonRenderSym r =>
FuncDocRenderer
-> String -> [String] -> [String] -> SMethod r -> SMethod r
docFuncRepr FuncDocRenderer
functionDox String
desc (((String, SVariable r) -> String)
-> [(String, SVariable r)] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String, SVariable r) -> String
forall a b. (a, b) -> a
fst ([(String, SVariable r)] -> [String])
-> [(String, SVariable r)] -> [String]
forall a b. (a -> b) -> a -> b
$ [(String, SVariable r)]
bs [(String, SVariable r)]
-> [(String, SVariable r)] -> [(String, SVariable r)]
forall a. [a] -> [a] -> [a]
++
[(String, SVariable r)]
is [(String, SVariable r)]
-> [(String, SVariable r)] -> [(String, SVariable r)]
forall a. [a] -> [a] -> [a]
++ [(String, SVariable r)]
os) [] ([SVariable r]
-> [SVariable r] -> [SVariable r] -> MSBody r -> SMethod r
f (((String, SVariable r) -> SVariable r)
-> [(String, SVariable r)] -> [SVariable r]
forall a b. (a -> b) -> [a] -> [b]
map (String, SVariable r) -> SVariable r
forall a b. (a, b) -> b
snd [(String, SVariable r)]
is) (((String, SVariable r) -> SVariable r)
-> [(String, SVariable r)] -> [SVariable r]
forall a b. (a -> b) -> [a] -> [b]
map (String, SVariable r) -> SVariable r
forall a b. (a, b) -> b
snd [(String, SVariable r)]
os) (((String, SVariable r) -> SVariable r)
-> [(String, SVariable r)] -> [SVariable r]
forall a b. (a -> b) -> [a] -> [b]
map (String, SVariable r) -> SVariable r
forall a b. (a, b) -> b
snd [(String, SVariable r)]
bs) MSBody r
b)
extFuncAppMixedArgs :: (CommonRenderSym r) => Library -> MixedCall r
extFuncAppMixedArgs :: forall (r :: * -> *). CommonRenderSym r => String -> MixedCall r
extFuncAppMixedArgs String
l = Maybe String
-> Maybe Doc
-> String
-> StateT ValueState Identity (r (Type r))
-> [StateT ValueState Identity (r (Value r))]
-> [(StateT ValueState Identity (r (Variable r)),
StateT ValueState Identity (r (Value r)))]
-> StateT ValueState Identity (r (Value r))
forall (r :: * -> *).
RenderValue r =>
Maybe String -> Maybe Doc -> MixedCall r
S.call (String -> Maybe String
forall a. a -> Maybe a
Just String
l) Maybe Doc
forall a. Maybe a
Nothing
bindingError :: String -> String
bindingError :: String -> String
bindingError String
l = String
"Binding unimplemented in " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
l
notNull :: (CommonRenderSym r) => String -> SValue r -> SValue r
notNull :: forall (r :: * -> *).
CommonRenderSym r =>
String -> SValue r -> SValue r
notNull String
nil SValue r
v = SValue r
v SValue r -> SValue r -> SValue r
forall (r :: * -> *).
Comparison r =>
SValue r -> SValue r -> SValue r
?!= SVariable r -> SValue r
forall (r :: * -> *). VariableValue r => SVariable r -> SValue r
IC.valueOf (String -> StateT ValueState Identity (r (Type r)) -> SVariable r
forall (r :: * -> *).
VariableSym r =>
String -> VSType r -> SVariable r
IC.var String
nil (StateT ValueState Identity (r (Type r)) -> SVariable r)
-> StateT ValueState Identity (r (Type r)) -> SVariable r
forall a b. (a -> b) -> a -> b
$ (r (Value r) -> r (Type r))
-> SValue r -> StateT ValueState Identity (r (Type r))
forall a b s. (a -> b) -> State s a -> State s b
onStateValue r (Value r) -> r (Type r)
forall (r :: * -> *). ValueSym r => r (Value r) -> r (Type r)
valueType SValue r
v)
listDecDef :: (CommonRenderSym r) => SVariable r -> r (Scope r) ->
[SValue r] -> MSStatement r
listDecDef :: forall (r :: * -> *).
CommonRenderSym r =>
SVariable r -> r (Scope r) -> [SValue r] -> MSStatement r
listDecDef SVariable r
v r (Scope r)
scp [SValue r]
vals = do
r (Variable r)
vr <- LensLike'
(Zoomed (StateT ValueState Identity) (r (Variable r)))
MethodState
ValueState
-> SVariable r -> StateT MethodState Identity (r (Variable r))
forall c.
LensLike'
(Zoomed (StateT ValueState Identity) c) MethodState ValueState
-> StateT ValueState Identity c -> StateT MethodState Identity c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
zoom LensLike'
(Zoomed (StateT ValueState Identity) (r (Variable r)))
MethodState
ValueState
(ValueState -> Focusing Identity (r (Variable r)) ValueState)
-> MethodState -> Focusing Identity (r (Variable r)) MethodState
Lens' MethodState ValueState
lensMStoVS SVariable r
v
let lst :: SValue r
lst = VSType r -> [SValue r] -> SValue r
forall (r :: * -> *).
Literal r =>
VSType r -> [SValue r] -> SValue r
IC.litList (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
$ r (Type r) -> VSType r
forall a. a -> StateT ValueState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (r (Type r) -> VSType r) -> r (Type r) -> VSType r
forall a b. (a -> b) -> a -> b
$ r (Variable r) -> r (Type r)
forall (r :: * -> *).
VariableElim r =>
r (Variable r) -> r (Type r)
variableType r (Variable r)
vr) [SValue r]
vals
SVariable r -> r (Scope r) -> SValue r -> MSStatement r
forall (r :: * -> *).
DeclStatement r =>
SVariable r -> r (Scope r) -> SValue r -> MSStatement r
IC.varDecDef (r (Variable r) -> SVariable r
forall a. a -> StateT ValueState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return r (Variable r)
vr) r (Scope r)
scp SValue r
lst
setDecDef :: (CommonRenderSym r) => SVariable r -> r (Scope r) -> [SValue r] -> MSStatement r
setDecDef :: forall (r :: * -> *).
CommonRenderSym r =>
SVariable r -> r (Scope r) -> [SValue r] -> MSStatement r
setDecDef SVariable r
v r (Scope r)
scp [SValue r]
vals = do
r (Variable r)
vr <- LensLike'
(Zoomed (StateT ValueState Identity) (r (Variable r)))
MethodState
ValueState
-> SVariable r -> StateT MethodState Identity (r (Variable r))
forall c.
LensLike'
(Zoomed (StateT ValueState Identity) c) MethodState ValueState
-> StateT ValueState Identity c -> StateT MethodState Identity c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
zoom LensLike'
(Zoomed (StateT ValueState Identity) (r (Variable r)))
MethodState
ValueState
(ValueState -> Focusing Identity (r (Variable r)) ValueState)
-> MethodState -> Focusing Identity (r (Variable r)) MethodState
Lens' MethodState ValueState
lensMStoVS SVariable r
v
let st :: SValue r
st = VSType r -> [SValue r] -> SValue r
forall (r :: * -> *).
Literal r =>
VSType r -> [SValue r] -> SValue r
IC.litSet (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
$ r (Type r) -> VSType r
forall a. a -> StateT ValueState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (r (Type r) -> VSType r) -> r (Type r) -> VSType r
forall a b. (a -> b) -> a -> b
$ r (Variable r) -> r (Type r)
forall (r :: * -> *).
VariableElim r =>
r (Variable r) -> r (Type r)
variableType r (Variable r)
vr) [SValue r]
vals
SVariable r -> r (Scope r) -> SValue r -> MSStatement r
forall (r :: * -> *).
DeclStatement r =>
SVariable r -> r (Scope r) -> SValue r -> MSStatement r
IC.varDecDef (r (Variable r) -> SVariable r
forall a. a -> StateT ValueState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return r (Variable r)
vr) r (Scope r)
scp SValue r
st
setDec :: (OORenderSym r) => (r (Value r) -> Doc) -> SValue r -> SVariable r -> r (Scope r) -> MSStatement r
setDec :: forall (r :: * -> *).
OORenderSym r =>
(r (Value r) -> Doc)
-> SValue r -> SVariable r -> r (Scope r) -> MSStatement r
setDec r (Value r) -> Doc
f SValue r
vl SVariable r
v r (Scope r)
scp = do
r (Value r)
sz <- LensLike'
(Zoomed (StateT ValueState Identity) (r (Value r)))
MethodState
ValueState
-> SValue r -> StateT MethodState Identity (r (Value r))
forall c.
LensLike'
(Zoomed (StateT ValueState Identity) c) MethodState ValueState
-> StateT ValueState Identity c -> StateT MethodState Identity c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
zoom LensLike'
(Zoomed (StateT ValueState Identity) (r (Value r)))
MethodState
ValueState
(ValueState -> Focusing Identity (r (Value r)) ValueState)
-> MethodState -> Focusing Identity (r (Value r)) MethodState
Lens' MethodState ValueState
lensMStoVS SValue r
vl
r (Statement r)
vd <- SVariable r -> r (Scope r) -> MSStatement r
forall (r :: * -> *).
DeclStatement r =>
SVariable r -> r (Scope r) -> MSStatement r
IC.varDec SVariable r
v r (Scope r)
scp
Doc -> MSStatement r
forall (r :: * -> *). CommonRenderSym r => Doc -> MSStatement r
mkStmt (r (Statement r) -> Doc
forall (r :: * -> *). StatementElim r => r (Statement r) -> Doc
RC.statement r (Statement r)
vd Doc -> Doc -> Doc
<> r (Value r) -> Doc
f r (Value r)
sz)
setMethodCall :: (OORenderSym r) => Label -> SValue r -> SValue r -> SValue r
setMethodCall :: forall (r :: * -> *).
OORenderSym r =>
String -> SValue r -> SValue r -> SValue r
setMethodCall String
n SValue r
a SValue r
b = VSType r -> SValue r -> String -> [SValue r] -> SValue r
forall (r :: * -> *).
InternalValueExp r =>
VSType r -> SValue r -> String -> [SValue r] -> SValue r
objMethodCall (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
$ (r (Value r) -> r (Type r)) -> SValue r -> VSType r
forall a b s. (a -> b) -> State s a -> State s b
onStateValue r (Value r) -> r (Type r)
forall (r :: * -> *). ValueSym r => r (Value r) -> r (Type r)
valueType SValue r
a) SValue r
a String
n [SValue r
b]
destructorError :: String -> String
destructorError :: String -> String
destructorError String
l = String
"Destructors not allowed in " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
l
stateVarDef :: (OORenderSym r, Monad r) => r (Visibility r) -> r (Permanence r) ->
SVariable r -> SValue r -> CS (r Doc)
stateVarDef :: forall (r :: * -> *).
(OORenderSym r, Monad r) =>
r (Visibility r)
-> r (Permanence r) -> SVariable r -> SValue r -> CS (r Doc)
stateVarDef r (Visibility r)
s r (Permanence r)
p SVariable r
vr SValue r
vl = LensLike'
(Zoomed (StateT MethodState Identity) (r Doc))
ClassState
MethodState
-> StateT MethodState Identity (r Doc)
-> StateT ClassState Identity (r Doc)
forall c.
LensLike'
(Zoomed (StateT MethodState Identity) c) ClassState MethodState
-> StateT MethodState Identity c -> StateT ClassState Identity c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
zoom LensLike'
(Zoomed (StateT MethodState Identity) (r Doc))
ClassState
MethodState
(MethodState -> Focusing Identity (r Doc) MethodState)
-> ClassState -> Focusing Identity (r Doc) ClassState
Lens' ClassState MethodState
lensCStoMS (StateT MethodState Identity (r Doc)
-> StateT ClassState Identity (r Doc))
-> StateT MethodState Identity (r Doc)
-> StateT ClassState Identity (r Doc)
forall a b. (a -> b) -> a -> b
$ (r (Statement r) -> r Doc)
-> State MethodState (r (Statement r))
-> StateT MethodState Identity (r Doc)
forall a b s. (a -> b) -> State s a -> State s b
onStateValue (Doc -> r Doc
forall (r :: * -> *) a. Monad r => a -> r a
toCode (Doc -> r Doc)
-> (r (Statement r) -> Doc) -> r (Statement r) -> r Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Doc -> Doc -> Doc -> Doc
R.stateVar
(r (Visibility r) -> Doc
forall (r :: * -> *). VisibilityElim r => r (Visibility r) -> Doc
RC.visibility r (Visibility r)
s) (r (Permanence r) -> Doc
forall (r :: * -> *). PermElim r => r (Permanence r) -> Doc
RC.perm r (Permanence r)
p) (Doc -> Doc) -> (r (Statement r) -> Doc) -> r (Statement r) -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. r (Statement r) -> Doc
forall (r :: * -> *). StatementElim r => r (Statement r) -> Doc
RC.statement)
(State MethodState (r (Statement r))
-> State MethodState (r (Statement r))
forall (r :: * -> *).
RenderStatement r =>
MSStatement r -> MSStatement r
S.stmt (State MethodState (r (Statement r))
-> State MethodState (r (Statement r)))
-> State MethodState (r (Statement r))
-> State MethodState (r (Statement r))
forall a b. (a -> b) -> a -> b
$ SVariable r
-> r (Scope r) -> SValue r -> State MethodState (r (Statement r))
forall (r :: * -> *).
DeclStatement r =>
SVariable r -> r (Scope r) -> SValue r -> MSStatement r
IC.varDecDef SVariable r
vr r (Scope r)
forall (r :: * -> *). ScopeSym r => r (Scope r)
IC.local SValue r
vl)
constVar :: (CommonRenderSym r, Monad r) => Doc -> r (Visibility r) -> SVariable r ->
SValue r -> CS (r Doc)
constVar :: forall (r :: * -> *).
(CommonRenderSym r, Monad r) =>
Doc -> r (Visibility r) -> SVariable r -> SValue r -> CS (r Doc)
constVar Doc
p r (Visibility r)
s SVariable r
vr SValue r
vl = LensLike'
(Zoomed (StateT MethodState Identity) (r Doc))
ClassState
MethodState
-> StateT MethodState Identity (r Doc)
-> StateT ClassState Identity (r Doc)
forall c.
LensLike'
(Zoomed (StateT MethodState Identity) c) ClassState MethodState
-> StateT MethodState Identity c -> StateT ClassState Identity c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
zoom LensLike'
(Zoomed (StateT MethodState Identity) (r Doc))
ClassState
MethodState
(MethodState -> Focusing Identity (r Doc) MethodState)
-> ClassState -> Focusing Identity (r Doc) ClassState
Lens' ClassState MethodState
lensCStoMS (StateT MethodState Identity (r Doc)
-> StateT ClassState Identity (r Doc))
-> StateT MethodState Identity (r Doc)
-> StateT ClassState Identity (r Doc)
forall a b. (a -> b) -> a -> b
$ (r (Statement r) -> r Doc)
-> State MethodState (r (Statement r))
-> StateT MethodState Identity (r Doc)
forall a b s. (a -> b) -> State s a -> State s b
onStateValue (Doc -> r Doc
forall (r :: * -> *) a. Monad r => a -> r a
toCode (Doc -> r Doc)
-> (r (Statement r) -> Doc) -> r (Statement r) -> r Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Doc -> Doc -> Doc -> Doc
R.stateVar
(r (Visibility r) -> Doc
forall (r :: * -> *). VisibilityElim r => r (Visibility r) -> Doc
RC.visibility r (Visibility r)
s) Doc
p (Doc -> Doc) -> (r (Statement r) -> Doc) -> r (Statement r) -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. r (Statement r) -> Doc
forall (r :: * -> *). StatementElim r => r (Statement r) -> Doc
RC.statement) (State MethodState (r (Statement r))
-> State MethodState (r (Statement r))
forall (r :: * -> *).
RenderStatement r =>
MSStatement r -> MSStatement r
S.stmt (State MethodState (r (Statement r))
-> State MethodState (r (Statement r)))
-> State MethodState (r (Statement r))
-> State MethodState (r (Statement r))
forall a b. (a -> b) -> a -> b
$ SVariable r
-> r (Scope r) -> SValue r -> State MethodState (r (Statement r))
forall (r :: * -> *).
DeclStatement r =>
SVariable r -> r (Scope r) -> SValue r -> MSStatement r
IC.constDecDef SVariable r
vr r (Scope r)
forall (r :: * -> *). ScopeSym r => r (Scope r)
IC.local SValue r
vl)
litArray :: (CommonRenderSym r) => (Doc -> Doc) -> VSType r -> [SValue r] -> SValue r
litArray :: forall (r :: * -> *).
CommonRenderSym r =>
(Doc -> Doc) -> VSType r -> [SValue r] -> SValue r
litArray Doc -> Doc
f VSType r
t [SValue r]
es = [SValue r] -> StateT ValueState Identity [r (Value r)]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
forall (m :: * -> *) a. Monad m => [m a] -> m [a]
sequence [SValue r]
es StateT ValueState Identity [r (Value r)]
-> ([r (Value r)] -> SValue r) -> SValue r
forall a b.
StateT ValueState Identity a
-> (a -> StateT ValueState Identity b)
-> StateT ValueState Identity b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (\[r (Value r)]
elems -> VSType r -> Doc -> SValue r
forall (r :: * -> *).
CommonRenderSym r =>
VSType r -> Doc -> SValue r
mkStateVal (VSType r -> VSType r
forall (r :: * -> *). TypeSym r => VSType r -> VSType r
IC.arrayType VSType r
t)
(Doc -> Doc
f (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ [r (Value r)] -> Doc
forall (r :: * -> *). CommonRenderSym r => [r (Value r)] -> Doc
valueList [r (Value r)]
elems))
litSet :: (CommonRenderSym r) => (Doc -> Doc) -> (Doc -> Doc) -> VSType r -> [SValue r] -> SValue r
litSet :: forall (r :: * -> *).
CommonRenderSym r =>
(Doc -> Doc) -> (Doc -> Doc) -> VSType r -> [SValue r] -> SValue r
litSet Doc -> Doc
f1 Doc -> Doc
f2 VSType r
t [SValue r]
es = [SValue r] -> StateT ValueState Identity [r (Value r)]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
forall (m :: * -> *) a. Monad m => [m a] -> m [a]
sequence [SValue r]
es StateT ValueState Identity [r (Value r)]
-> ([r (Value r)] -> SValue r) -> SValue r
forall a b.
StateT ValueState Identity a
-> (a -> StateT ValueState Identity b)
-> StateT ValueState Identity b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (\[r (Value r)]
elems -> VSType r -> Doc -> SValue r
forall (r :: * -> *).
CommonRenderSym r =>
VSType r -> Doc -> SValue r
mkStateVal (VSType r -> VSType r
forall (r :: * -> *). TypeSym r => VSType r -> VSType r
IC.arrayType VSType r
t)
(Doc -> Doc
f1 (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ Doc -> Doc
f2 (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ [r (Value r)] -> Doc
forall (r :: * -> *). CommonRenderSym r => [r (Value r)] -> Doc
valueList [r (Value r)]
elems))
litSetFunc :: (CommonRenderSym r) => String -> VSType r -> [SValue r] -> SValue r
litSetFunc :: forall (r :: * -> *).
CommonRenderSym r =>
String -> VSType r -> [SValue r] -> SValue r
litSetFunc String
s VSType r
t [SValue r]
es = [SValue r] -> StateT ValueState Identity [r (Value r)]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
forall (m :: * -> *) a. Monad m => [m a] -> m [a]
sequence [SValue r]
es StateT ValueState Identity [r (Value r)]
-> ([r (Value r)] -> SValue r) -> SValue r
forall a b.
StateT ValueState Identity a
-> (a -> StateT ValueState Identity b)
-> StateT ValueState Identity b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (\[r (Value r)]
elems -> VSType r -> Doc -> SValue r
forall (r :: * -> *).
CommonRenderSym r =>
VSType r -> Doc -> SValue r
mkStateVal (VSType r -> VSType r
forall (r :: * -> *). TypeSym r => VSType r -> VSType r
IC.arrayType VSType r
t)
(String -> Doc
text String
s Doc -> Doc -> Doc
<> Doc -> Doc
parens ([r (Value r)] -> Doc
forall (r :: * -> *). CommonRenderSym r => [r (Value r)] -> Doc
valueList [r (Value r)]
elems)))
extraClass :: (OORenderSym r) => Label -> Maybe Label -> [CSStateVar r] ->
[SMethod r] -> [SMethod r] -> SClass r
String
n = String
-> r (Visibility r)
-> r Doc
-> [CS (r (StateVar r))]
-> [MS (r (Method r))]
-> [MS (r (Method r))]
-> CS (r (Class r))
forall (r :: * -> *).
RenderClass r =>
String
-> r (Visibility r)
-> r Doc
-> [CSStateVar r]
-> [SMethod r]
-> [SMethod r]
-> SClass r
S.intClass String
n r (Visibility r)
forall (r :: * -> *). VisibilitySym r => r (Visibility r)
public (r Doc
-> [CS (r (StateVar r))]
-> [MS (r (Method r))]
-> [MS (r (Method r))]
-> CS (r (Class r)))
-> (Maybe String -> r Doc)
-> Maybe String
-> [CS (r (StateVar r))]
-> [MS (r (Method r))]
-> [MS (r (Method r))]
-> CS (r (Class r))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe String -> r Doc
forall (r :: * -> *). RenderClass r => Maybe String -> r Doc
S.inherit
listAccessFunc :: (CommonRenderSym r) => VSType r -> SValue r -> VSFunction r
listAccessFunc :: forall (r :: * -> *).
CommonRenderSym r =>
VSType r -> SValue r -> VSFunction r
listAccessFunc VSType r
t SValue r
v = SValue r -> SValue r
forall (r :: * -> *). CommonRenderSym r => SValue r -> SValue r
intValue SValue r
v SValue r
-> (r (Value r) -> StateT ValueState Identity (r (Function r)))
-> StateT ValueState Identity (r (Function r))
forall a b.
StateT ValueState Identity a
-> (a -> StateT ValueState Identity b)
-> StateT ValueState Identity b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ((Doc -> VSType r -> StateT ValueState Identity (r (Function r))
forall (r :: * -> *).
RenderFunction r =>
Doc -> VSType r -> VSFunction r
`funcFromData` VSType r
t) (Doc -> StateT ValueState Identity (r (Function r)))
-> (r (Value r) -> Doc)
-> r (Value r)
-> StateT ValueState Identity (r (Function r))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. r (Value r) -> Doc
forall (r :: * -> *). CommonRenderSym r => r (Value r) -> Doc
R.listAccessFunc)
listSetFunc :: (CommonRenderSym r) => (Doc -> Doc -> Doc) -> SValue r -> SValue r ->
SValue r -> VSFunction r
listSetFunc :: forall (r :: * -> *).
CommonRenderSym r =>
(Doc -> Doc -> Doc)
-> SValue r -> SValue r -> SValue r -> VSFunction r
listSetFunc Doc -> Doc -> Doc
f SValue r
v SValue r
idx SValue r
setVal = StateT
ValueState Identity (StateT ValueState Identity (r (Function r)))
-> StateT ValueState Identity (r (Function r))
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (StateT
ValueState Identity (StateT ValueState Identity (r (Function r)))
-> StateT ValueState Identity (r (Function r)))
-> StateT
ValueState Identity (StateT ValueState Identity (r (Function r)))
-> StateT ValueState Identity (r (Function r))
forall a b. (a -> b) -> a -> b
$ (r (Value r)
-> r (Value r) -> StateT ValueState Identity (r (Function r)))
-> SValue r
-> SValue r
-> StateT
ValueState Identity (StateT ValueState Identity (r (Function r)))
forall a b c s.
(a -> b -> c) -> State s a -> State s b -> State s c
on2StateValues (\r (Value r)
i r (Value r)
toVal -> Doc -> VSType r -> StateT ValueState Identity (r (Function r))
forall (r :: * -> *).
RenderFunction r =>
Doc -> VSType r -> VSFunction r
funcFromData
(Doc -> Doc -> Doc
f (r (Value r) -> Doc
forall (r :: * -> *). ValueElim r => r (Value r) -> Doc
RC.value r (Value r)
i) (r (Value r) -> Doc
forall (r :: * -> *). ValueElim r => r (Value r) -> Doc
RC.value r (Value r)
toVal)) ((r (Value r) -> r (Type r)) -> SValue r -> VSType r
forall a b s. (a -> b) -> State s a -> State s b
onStateValue r (Value r) -> r (Type r)
forall (r :: * -> *). ValueSym r => r (Value r) -> r (Type r)
valueType SValue r
v)) (SValue r -> SValue r
forall (r :: * -> *). CommonRenderSym r => SValue r -> SValue r
intValue SValue r
idx)
SValue r
setVal
doubleRender :: String
doubleRender :: String
doubleRender = String
"Double"
double :: (CommonRenderSym r) => VSType r
double :: forall (r :: * -> *). CommonRenderSym r => VSType r
double = CodeType
-> String -> Doc -> StateT ValueState Identity (r (Type r))
forall (r :: * -> *).
RenderType r =>
CodeType -> String -> Doc -> VSType r
typeFromData CodeType
Double String
doubleRender (String -> Doc
text String
doubleRender)
openFileR :: (CommonRenderSym r) => (SValue r -> VSType r -> SValue r) -> SVariable r
-> SValue r -> MSStatement r
openFileR :: forall (r :: * -> *).
CommonRenderSym r =>
(SValue r -> VSType r -> SValue r)
-> SVariable r -> SValue r -> MSStatement r
openFileR SValue r -> VSType r -> SValue r
f SVariable r
vr SValue r
vl = SVariable r
vr SVariable r
-> SValue r -> StateT MethodState Identity (r (Statement r))
forall (r :: * -> *).
AssignStatement r =>
SVariable r -> SValue r -> MSStatement r
&= SValue r -> VSType r -> SValue r
f SValue r
vl VSType r
forall (r :: * -> *). TypeSym r => VSType r
infile
openFileW :: (CommonRenderSym r) => (SValue r -> VSType r -> SValue r -> SValue r) ->
SVariable r -> SValue r -> MSStatement r
openFileW :: forall (r :: * -> *).
CommonRenderSym r =>
(SValue r -> VSType r -> SValue r -> SValue r)
-> SVariable r -> SValue r -> MSStatement r
openFileW SValue r -> VSType r -> SValue r -> SValue r
f SVariable r
vr SValue r
vl = SVariable r
vr SVariable r
-> SValue r -> StateT MethodState Identity (r (Statement r))
forall (r :: * -> *).
AssignStatement r =>
SVariable r -> SValue r -> MSStatement r
&= SValue r -> VSType r -> SValue r -> SValue r
f SValue r
vl VSType r
forall (r :: * -> *). TypeSym r => VSType r
outfile SValue r
forall (r :: * -> *). Literal r => SValue r
IC.litFalse
stateVar :: (OORenderSym r, Monad r) => r (Visibility r) -> r (Permanence r) ->
SVariable r -> CS (r Doc)
stateVar :: forall (r :: * -> *).
(OORenderSym r, Monad r) =>
r (Visibility r) -> r (Permanence r) -> SVariable r -> CS (r Doc)
stateVar r (Visibility r)
s r (Permanence r)
p SVariable r
v = LensLike'
(Zoomed (StateT MethodState Identity) (r Doc))
ClassState
MethodState
-> StateT MethodState Identity (r Doc)
-> StateT ClassState Identity (r Doc)
forall c.
LensLike'
(Zoomed (StateT MethodState Identity) c) ClassState MethodState
-> StateT MethodState Identity c -> StateT ClassState Identity c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
zoom LensLike'
(Zoomed (StateT MethodState Identity) (r Doc))
ClassState
MethodState
(MethodState -> Focusing Identity (r Doc) MethodState)
-> ClassState -> Focusing Identity (r Doc) ClassState
Lens' ClassState MethodState
lensCStoMS (StateT MethodState Identity (r Doc)
-> StateT ClassState Identity (r Doc))
-> StateT MethodState Identity (r Doc)
-> StateT ClassState Identity (r Doc)
forall a b. (a -> b) -> a -> b
$ (r (Statement r) -> r Doc)
-> State MethodState (r (Statement r))
-> StateT MethodState Identity (r Doc)
forall a b s. (a -> b) -> State s a -> State s b
onStateValue (Doc -> r Doc
forall (r :: * -> *) a. Monad r => a -> r a
toCode (Doc -> r Doc)
-> (r (Statement r) -> Doc) -> r (Statement r) -> r Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Doc -> Doc -> Doc -> Doc
R.stateVar
(r (Visibility r) -> Doc
forall (r :: * -> *). VisibilityElim r => r (Visibility r) -> Doc
RC.visibility r (Visibility r)
s) (r (Permanence r) -> Doc
forall (r :: * -> *). PermElim r => r (Permanence r) -> Doc
RC.perm r (Permanence r)
p) (Doc -> Doc) -> (r (Statement r) -> Doc) -> r (Statement r) -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. r (Statement r) -> Doc
forall (r :: * -> *). StatementElim r => r (Statement r) -> Doc
RC.statement) (State MethodState (r (Statement r))
-> State MethodState (r (Statement r))
forall (r :: * -> *).
RenderStatement r =>
MSStatement r -> MSStatement r
S.stmt (State MethodState (r (Statement r))
-> State MethodState (r (Statement r)))
-> State MethodState (r (Statement r))
-> State MethodState (r (Statement r))
forall a b. (a -> b) -> a -> b
$ SVariable r -> r (Scope r) -> State MethodState (r (Statement r))
forall (r :: * -> *).
DeclStatement r =>
SVariable r -> r (Scope r) -> MSStatement r
IC.varDec SVariable r
v r (Scope r)
forall (r :: * -> *). ScopeSym r => r (Scope r)
IC.local)
self :: (OORenderSym r) => SVariable r
self :: forall (r :: * -> *). OORenderSym r => SVariable r
self = LensLike'
(Zoomed (StateT MethodState Identity) String)
ValueState
MethodState
-> MS String -> StateT ValueState Identity String
forall c.
LensLike'
(Zoomed (StateT MethodState Identity) c) ValueState MethodState
-> StateT MethodState Identity c -> StateT ValueState Identity c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
zoom LensLike'
(Zoomed (StateT MethodState Identity) String)
ValueState
MethodState
(MethodState -> Focusing Identity String MethodState)
-> ValueState -> Focusing Identity String ValueState
Lens' ValueState MethodState
lensVStoMS MS String
getClassName StateT ValueState Identity String
-> (String -> StateT ValueState Identity (r (Variable r)))
-> StateT ValueState Identity (r (Variable r))
forall a b.
StateT ValueState Identity a
-> (a -> StateT ValueState Identity b)
-> StateT ValueState Identity b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (\String
l -> String
-> VSType r -> Doc -> StateT ValueState Identity (r (Variable r))
forall (r :: * -> *).
CommonRenderSym r =>
String -> VSType r -> Doc -> SVariable r
mkStateVar String
R.self (String -> VSType r
forall (r :: * -> *). OOTypeSym r => String -> VSType r
obj String
l)
Doc
R.self')
multiAssign :: (CommonRenderSym r) => (Doc -> Doc) -> [SVariable r] -> [SValue r] ->
MSStatement r
multiAssign :: forall (r :: * -> *).
CommonRenderSym r =>
(Doc -> Doc) -> [SVariable r] -> [SValue r] -> MSStatement r
multiAssign Doc -> Doc
_ [] [SValue r]
_ = String -> StateT MethodState Identity (r (Statement r))
forall a. HasCallStack => String -> a
error String
"Attempt to write assign statement for no variables."
multiAssign Doc -> Doc
_ [SVariable r]
_ [] = String -> StateT MethodState Identity (r (Statement r))
forall a. HasCallStack => String -> a
error String
"Attempt to write assign statement with no values."
multiAssign Doc -> Doc
f [SVariable r]
vars [SValue r]
vals = if [SValue r] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [SValue r]
vals Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
1 Bool -> Bool -> Bool
&& [SVariable r] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [SVariable r]
vars Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= [SValue r] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [SValue r]
vals
then String -> StateT MethodState Identity (r (Statement r))
forall a. HasCallStack => String -> a
error (String -> StateT MethodState Identity (r (Statement r)))
-> String -> StateT MethodState Identity (r (Statement r))
forall a b. (a -> b) -> a -> b
$ String
"Attempted multiple assign statement with different number " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"of variables than values"
else do
[r (Variable r)]
vrs <- (SVariable r -> StateT MethodState Identity (r (Variable r)))
-> [SVariable r] -> StateT MethodState Identity [r (Variable r)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (LensLike'
(Zoomed (StateT ValueState Identity) (r (Variable r)))
MethodState
ValueState
-> SVariable r -> StateT MethodState Identity (r (Variable r))
forall c.
LensLike'
(Zoomed (StateT ValueState Identity) c) MethodState ValueState
-> StateT ValueState Identity c -> StateT MethodState Identity c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
zoom LensLike'
(Zoomed (StateT ValueState Identity) (r (Variable r)))
MethodState
ValueState
(ValueState -> Focusing Identity (r (Variable r)) ValueState)
-> MethodState -> Focusing Identity (r (Variable r)) MethodState
Lens' MethodState ValueState
lensMStoVS) [SVariable r]
vars
[r (Value r)]
vls <- (SValue r -> StateT MethodState Identity (r (Value r)))
-> [SValue r] -> StateT MethodState Identity [r (Value r)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (LensLike'
(Zoomed (StateT ValueState Identity) (r (Value r)))
MethodState
ValueState
-> SValue r -> StateT MethodState Identity (r (Value r))
forall c.
LensLike'
(Zoomed (StateT ValueState Identity) c) MethodState ValueState
-> StateT ValueState Identity c -> StateT MethodState Identity c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
zoom LensLike'
(Zoomed (StateT ValueState Identity) (r (Value r)))
MethodState
ValueState
(ValueState -> Focusing Identity (r (Value r)) ValueState)
-> MethodState -> Focusing Identity (r (Value r)) MethodState
Lens' MethodState ValueState
lensMStoVS) [SValue r]
vals
let wrapIfMult :: [a] -> Doc -> Doc
wrapIfMult :: forall a. [a] -> Doc -> Doc
wrapIfMult [a]
l = if [a] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
l Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1 then Doc -> Doc
f else Doc -> Doc
forall a. a -> a
id
String -> VSType r -> Doc -> SVariable r
forall (r :: * -> *).
CommonRenderSym r =>
String -> VSType r -> Doc -> SVariable r
mkStateVar String
"" VSType r
forall (r :: * -> *). TypeSym r => VSType r
IC.void ([r (Variable r)] -> Doc -> Doc
forall a. [a] -> Doc -> Doc
wrapIfMult [r (Variable r)]
vrs ([r (Variable r)] -> Doc
forall (r :: * -> *). CommonRenderSym r => [r (Variable r)] -> Doc
variableList [r (Variable r)]
vrs)) SVariable r
-> SValue r -> StateT MethodState Identity (r (Statement r))
forall (r :: * -> *).
AssignStatement r =>
SVariable r -> SValue r -> MSStatement r
&=
VSType r -> Doc -> SValue r
forall (r :: * -> *).
CommonRenderSym r =>
VSType r -> Doc -> SValue r
mkStateVal VSType r
forall (r :: * -> *). TypeSym r => VSType r
IC.void ([r (Value r)] -> Doc -> Doc
forall a. [a] -> Doc -> Doc
wrapIfMult [r (Value r)]
vls ([r (Value r)] -> Doc
forall (r :: * -> *). CommonRenderSym r => [r (Value r)] -> Doc
valueList [r (Value r)]
vls))
multiReturn :: (CommonRenderSym r) => (Doc -> Doc) -> [SValue r] -> MSStatement r
multiReturn :: forall (r :: * -> *).
CommonRenderSym r =>
(Doc -> Doc) -> [SValue r] -> MSStatement r
multiReturn Doc -> Doc
_ [] = String -> StateT MethodState Identity (r (Statement r))
forall a. HasCallStack => String -> a
error String
"Attempt to write return statement with no values."
multiReturn Doc -> Doc
_ [SValue r
v] = SValue r -> StateT MethodState Identity (r (Statement r))
forall (r :: * -> *).
ControlStatement r =>
SValue r -> MSStatement r
returnStmt SValue r
v
multiReturn Doc -> Doc
f [SValue r]
vs = do
[r (Value r)]
vs' <- (SValue r -> StateT MethodState Identity (r (Value r)))
-> [SValue r] -> StateT MethodState Identity [r (Value r)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (LensLike'
(Zoomed (StateT ValueState Identity) (r (Value r)))
MethodState
ValueState
-> SValue r -> StateT MethodState Identity (r (Value r))
forall c.
LensLike'
(Zoomed (StateT ValueState Identity) c) MethodState ValueState
-> StateT ValueState Identity c -> StateT MethodState Identity c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
zoom LensLike'
(Zoomed (StateT ValueState Identity) (r (Value r)))
MethodState
ValueState
(ValueState -> Focusing Identity (r (Value r)) ValueState)
-> MethodState -> Focusing Identity (r (Value r)) MethodState
Lens' MethodState ValueState
lensMStoVS) [SValue r]
vs
SValue r -> StateT MethodState Identity (r (Statement r))
forall (r :: * -> *).
ControlStatement r =>
SValue r -> MSStatement r
returnStmt (SValue r -> StateT MethodState Identity (r (Statement r)))
-> SValue r -> StateT MethodState Identity (r (Statement r))
forall a b. (a -> b) -> a -> b
$ VSType r -> Doc -> SValue r
forall (r :: * -> *).
CommonRenderSym r =>
VSType r -> Doc -> SValue r
mkStateVal VSType r
forall (r :: * -> *). TypeSym r => VSType r
IC.void (Doc -> SValue r) -> Doc -> SValue r
forall a b. (a -> b) -> a -> b
$ Doc -> Doc
f (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ [r (Value r)] -> Doc
forall (r :: * -> *). CommonRenderSym r => [r (Value r)] -> Doc
valueList [r (Value r)]
vs'
listDec :: (CommonRenderSym r) => SVariable r -> r (Scope r) -> MSStatement r
listDec :: forall (r :: * -> *).
CommonRenderSym r =>
SVariable r -> r (Scope r) -> MSStatement r
listDec SVariable r
v r (Scope r)
scp = SVariable r
-> r (Scope r)
-> [SValue r]
-> StateT MethodState Identity (r (Statement r))
forall (r :: * -> *).
CommonRenderSym r =>
SVariable r -> r (Scope r) -> [SValue r] -> MSStatement r
listDecDef SVariable r
v r (Scope r)
scp []
funcDecDef :: (OORenderSym r) => SVariable r -> r (Scope r) -> [SVariable r] ->
MSBody r -> MSStatement r
funcDecDef :: forall (r :: * -> *).
OORenderSym r =>
SVariable r
-> r (Scope r) -> [SVariable r] -> MSBody r -> MSStatement r
funcDecDef SVariable r
v r (Scope r)
scp [SVariable r]
ps MSBody r
b = do
r (Variable r)
vr <- LensLike'
(Zoomed (StateT ValueState Identity) (r (Variable r)))
MethodState
ValueState
-> SVariable r -> StateT MethodState Identity (r (Variable r))
forall c.
LensLike'
(Zoomed (StateT ValueState Identity) c) MethodState ValueState
-> StateT ValueState Identity c -> StateT MethodState Identity c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
zoom LensLike'
(Zoomed (StateT ValueState Identity) (r (Variable r)))
MethodState
ValueState
(ValueState -> Focusing Identity (r (Variable r)) ValueState)
-> MethodState -> Focusing Identity (r (Variable r)) MethodState
Lens' MethodState ValueState
lensMStoVS SVariable r
v
(MethodState -> MethodState) -> StateT MethodState Identity ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((MethodState -> MethodState) -> StateT MethodState Identity ())
-> (MethodState -> MethodState) -> StateT MethodState Identity ()
forall a b. (a -> b) -> a -> b
$ String -> MethodState -> MethodState
useVarName (String -> MethodState -> MethodState)
-> String -> MethodState -> MethodState
forall a b. (a -> b) -> a -> b
$ r (Variable r) -> String
forall (r :: * -> *). VariableElim r => r (Variable r) -> String
variableName r (Variable r)
vr
(MethodState -> MethodState) -> StateT MethodState Identity ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((MethodState -> MethodState) -> StateT MethodState Identity ())
-> (MethodState -> MethodState) -> StateT MethodState Identity ()
forall a b. (a -> b) -> a -> b
$ String -> ScopeData -> MethodState -> MethodState
setVarScope (r (Variable r) -> String
forall (r :: * -> *). VariableElim r => r (Variable r) -> String
variableName r (Variable r)
vr) (r (Scope r) -> ScopeData
forall (r :: * -> *). ScopeElim r => r (Scope r) -> ScopeData
scopeData r (Scope r)
scp)
MethodState
s <- StateT MethodState Identity MethodState
forall s (m :: * -> *). MonadState s m => m s
get
r (Method r)
f <- String
-> r (Visibility r)
-> VSType r
-> [MSParameter r]
-> MSBody r
-> StateT MethodState Identity (r (Method r))
forall (r :: * -> *).
MethodSym r =>
String
-> r (Visibility r)
-> VSType r
-> [MSParameter r]
-> MSBody r
-> SMethod r
function (r (Variable r) -> String
forall (r :: * -> *). VariableElim r => r (Variable r) -> String
variableName r (Variable r)
vr) r (Visibility r)
forall (r :: * -> *). VisibilitySym r => r (Visibility r)
private (r (Type r) -> VSType r
forall a. a -> StateT ValueState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (r (Type r) -> VSType r) -> r (Type r) -> VSType r
forall a b. (a -> b) -> a -> b
$ r (Variable r) -> r (Type r)
forall (r :: * -> *).
VariableElim r =>
r (Variable r) -> r (Type r)
variableType r (Variable r)
vr)
((SVariable r -> MSParameter r) -> [SVariable r] -> [MSParameter r]
forall a b. (a -> b) -> [a] -> [b]
map SVariable r -> MSParameter r
forall (r :: * -> *).
ParameterSym r =>
SVariable r -> MSParameter r
IC.param [SVariable r]
ps) MSBody r
b
(MethodState -> MethodState) -> StateT MethodState Identity ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (ASetter MethodState MethodState [String] [String]
-> [String] -> MethodState -> MethodState
forall s t a b. ASetter s t a b -> b -> s -> t
L.set ASetter MethodState MethodState [String] [String]
Lens' MethodState [String]
currParameters (MethodState
s MethodState -> Getting [String] MethodState [String] -> [String]
forall s a. s -> Getting a s a -> a
^. Getting [String] MethodState [String]
Lens' MethodState [String]
currParameters))
Doc -> MSStatement r
forall (r :: * -> *). CommonRenderSym r => Doc -> MSStatement r
mkStmtNoEnd (Doc -> MSStatement r) -> Doc -> MSStatement r
forall a b. (a -> b) -> a -> b
$ r (Method r) -> Doc
forall (r :: * -> *). MethodElim r => r (Method r) -> Doc
RC.method r (Method r)
f
inOutCall :: (CommonRenderSym r) => (Label -> VSType r -> [SValue r] -> SValue r) ->
Label -> [SValue r] -> [SVariable r] -> [SVariable r] -> MSStatement r
inOutCall :: forall (r :: * -> *).
CommonRenderSym r =>
(String -> VSType r -> [SValue r] -> SValue r)
-> String
-> [SValue r]
-> [SVariable r]
-> [SVariable r]
-> MSStatement r
inOutCall String -> VSType r -> [SValue r] -> SValue r
f String
n [SValue r]
ins [] [] = SValue r -> MSStatement r
forall (r :: * -> *). StatementSym r => SValue r -> MSStatement r
IC.valStmt (SValue r -> MSStatement r) -> SValue r -> MSStatement r
forall a b. (a -> b) -> a -> b
$ String -> VSType r -> [SValue r] -> SValue r
f String
n VSType r
forall (r :: * -> *). TypeSym r => VSType r
IC.void [SValue r]
ins
inOutCall String -> VSType r -> [SValue r] -> SValue r
f String
n [SValue r]
ins [SVariable r]
outs [SVariable r]
both = [SVariable r] -> [SValue r] -> MSStatement r
forall (r :: * -> *).
InternalAssignStmt r =>
[SVariable r] -> [SValue r] -> MSStatement r
S.multiAssign [SVariable r]
rets [String -> VSType r -> [SValue r] -> SValue r
f String
n VSType r
forall (r :: * -> *). TypeSym r => VSType r
IC.void ((SVariable r -> SValue r) -> [SVariable r] -> [SValue r]
forall a b. (a -> b) -> [a] -> [b]
map SVariable r -> SValue r
forall (r :: * -> *). VariableValue r => SVariable r -> SValue r
IC.valueOf
[SVariable r]
both [SValue r] -> [SValue r] -> [SValue r]
forall a. [a] -> [a] -> [a]
++ [SValue r]
ins)]
where rets :: [SVariable r]
rets = [SVariable r]
both [SVariable r] -> [SVariable r] -> [SVariable r]
forall a. [a] -> [a] -> [a]
++ [SVariable r]
outs
forLoopError :: String -> String
forLoopError :: String -> String
forLoopError String
l = String
"Classic for loops not available in " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
l String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
", use " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"forRange, forEach, or while instead"
mainBody :: (CommonRenderSym r) => MSBody r -> SMethod r
mainBody :: forall (r :: * -> *). CommonRenderSym r => MSBody r -> SMethod r
mainBody MSBody r
b = do
(MethodState -> MethodState) -> StateT MethodState Identity ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify MethodState -> MethodState
setCurrMain
r (Body r)
bod <- MSBody r
b
(MethodState -> MethodState) -> StateT MethodState Identity ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (Doc -> MethodState -> MethodState
setMainDoc (Doc -> MethodState -> MethodState)
-> Doc -> MethodState -> MethodState
forall a b. (a -> b) -> a -> b
$ r (Body r) -> Doc
forall (r :: * -> *). BodyElim r => r (Body r) -> Doc
RC.body r (Body r)
bod)
VisibilityTag -> Doc -> SMethod r
forall (r :: * -> *).
RenderMethod r =>
VisibilityTag -> Doc -> SMethod r
mthdFromData VisibilityTag
Pub Doc
empty
inOutFunc :: (CommonRenderSym r) => (VSType r -> [MSParameter r] -> MSBody r ->
SMethod r) -> [SVariable r] -> [SVariable r] -> [SVariable r] -> MSBody r ->
SMethod r
inOutFunc :: forall (r :: * -> *).
CommonRenderSym r =>
(VSType r -> [MSParameter r] -> MSBody r -> SMethod r)
-> [SVariable r]
-> [SVariable r]
-> [SVariable r]
-> MSBody r
-> SMethod r
inOutFunc VSType r -> [MSParameter r] -> MSBody r -> SMethod r
f [SVariable r]
ins [] [] MSBody r
b = VSType r -> [MSParameter r] -> MSBody r -> SMethod r
f VSType r
forall (r :: * -> *). TypeSym r => VSType r
IC.void ((SVariable r -> MSParameter r) -> [SVariable r] -> [MSParameter r]
forall a b. (a -> b) -> [a] -> [b]
map SVariable r -> MSParameter r
forall (r :: * -> *).
ParameterSym r =>
SVariable r -> MSParameter r
IC.param [SVariable r]
ins) MSBody r
b
inOutFunc VSType r -> [MSParameter r] -> MSBody r -> SMethod r
f [SVariable r]
ins [SVariable r]
outs [SVariable r]
both MSBody r
b = VSType r -> [MSParameter r] -> MSBody r -> SMethod r
f
([VSType r] -> VSType r
forall (r :: * -> *). RenderType r => [VSType r] -> VSType r
multiType ([VSType r] -> VSType r) -> [VSType r] -> VSType r
forall a b. (a -> b) -> a -> b
$ (SVariable r -> VSType r) -> [SVariable r] -> [VSType r]
forall a b. (a -> b) -> [a] -> [b]
map ((r (Variable r) -> r (Type r)) -> SVariable r -> VSType r
forall a b s. (a -> b) -> State s a -> State s b
onStateValue r (Variable r) -> r (Type r)
forall (r :: * -> *).
VariableElim r =>
r (Variable r) -> r (Type r)
variableType) [SVariable r]
rets)
((SVariable r -> MSParameter r) -> [SVariable r] -> [MSParameter r]
forall a b. (a -> b) -> [a] -> [b]
map SVariable r -> MSParameter r
forall (r :: * -> *).
ParameterSym r =>
SVariable r -> MSParameter r
IC.pointerParam [SVariable r]
both [MSParameter r] -> [MSParameter r] -> [MSParameter r]
forall a. [a] -> [a] -> [a]
++ (SVariable r -> MSParameter r) -> [SVariable r] -> [MSParameter r]
forall a b. (a -> b) -> [a] -> [b]
map SVariable r -> MSParameter r
forall (r :: * -> *).
ParameterSym r =>
SVariable r -> MSParameter r
IC.param [SVariable r]
ins)
([MSBody r] -> MSBody r
forall (r :: * -> *). RenderBody r => [MSBody r] -> MSBody r
multiBody [[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
$ (SVariable r -> MSStatement r) -> [SVariable r] -> [MSStatement r]
forall a b. (a -> b) -> [a] -> [b]
map (SVariable r -> r (Scope r) -> MSStatement r
forall (r :: * -> *).
DeclStatement r =>
SVariable r -> r (Scope r) -> MSStatement r
`IC.varDec` r (Scope r)
forall (r :: * -> *). ScopeSym r => r (Scope r)
IC.local) [SVariable r]
outs, MSBody r
b,
MSStatement r -> MSBody r
forall (r :: * -> *). BodySym r => MSStatement r -> MSBody r
oneLiner (MSStatement r -> MSBody r) -> MSStatement r -> MSBody r
forall a b. (a -> b) -> a -> b
$ [SValue r] -> MSStatement r
forall (r :: * -> *).
InternalControlStmt r =>
[SValue r] -> MSStatement r
S.multiReturn ([SValue r] -> MSStatement r) -> [SValue r] -> MSStatement r
forall a b. (a -> b) -> a -> b
$ (SVariable r -> SValue r) -> [SVariable r] -> [SValue r]
forall a b. (a -> b) -> [a] -> [b]
map SVariable r -> SValue r
forall (r :: * -> *). VariableValue r => SVariable r -> SValue r
IC.valueOf [SVariable r]
rets])
where rets :: [SVariable r]
rets = [SVariable r]
both [SVariable r] -> [SVariable r] -> [SVariable r]
forall a. [a] -> [a] -> [a]
++ [SVariable r]
outs
docInOutFunc' :: (CommonRenderSym r) => FuncDocRenderer -> ([SVariable r] ->
[SVariable r] -> [SVariable r] -> MSBody r -> SMethod r) ->
String -> [(String, SVariable r)] -> [(String, SVariable r)] ->
[(String, SVariable r)] -> MSBody r -> SMethod r
docInOutFunc' :: forall (r :: * -> *).
CommonRenderSym r =>
FuncDocRenderer
-> ([SVariable r]
-> [SVariable r] -> [SVariable r] -> MSBody r -> SMethod r)
-> String
-> [(String, SVariable r)]
-> [(String, SVariable r)]
-> [(String, SVariable r)]
-> MSBody r
-> SMethod r
docInOutFunc' FuncDocRenderer
dfr [SVariable r]
-> [SVariable r] -> [SVariable r] -> MSBody r -> SMethod r
f String
desc [(String, SVariable r)]
is [(String, SVariable r)]
os [(String, SVariable r)]
bs MSBody r
b = FuncDocRenderer
-> String -> [String] -> [String] -> SMethod r -> SMethod r
forall (r :: * -> *).
CommonRenderSym r =>
FuncDocRenderer
-> String -> [String] -> [String] -> SMethod r -> SMethod r
docFuncRepr FuncDocRenderer
dfr String
desc (((String, SVariable r) -> String)
-> [(String, SVariable r)] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String, SVariable r) -> String
forall a b. (a, b) -> a
fst ([(String, SVariable r)] -> [String])
-> [(String, SVariable r)] -> [String]
forall a b. (a -> b) -> a -> b
$ [(String, SVariable r)]
bs [(String, SVariable r)]
-> [(String, SVariable r)] -> [(String, SVariable r)]
forall a. [a] -> [a] -> [a]
++ [(String, SVariable r)]
is)
(((String, SVariable r) -> String)
-> [(String, SVariable r)] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String, SVariable r) -> String
forall a b. (a, b) -> a
fst ([(String, SVariable r)] -> [String])
-> [(String, SVariable r)] -> [String]
forall a b. (a -> b) -> a -> b
$ [(String, SVariable r)]
bs [(String, SVariable r)]
-> [(String, SVariable r)] -> [(String, SVariable r)]
forall a. [a] -> [a] -> [a]
++ [(String, SVariable r)]
os) ([SVariable r]
-> [SVariable r] -> [SVariable r] -> MSBody r -> SMethod r
f (((String, SVariable r) -> SVariable r)
-> [(String, SVariable r)] -> [SVariable r]
forall a b. (a -> b) -> [a] -> [b]
map (String, SVariable r) -> SVariable r
forall a b. (a, b) -> b
snd [(String, SVariable r)]
is) (((String, SVariable r) -> SVariable r)
-> [(String, SVariable r)] -> [SVariable r]
forall a b. (a -> b) -> [a] -> [b]
map (String, SVariable r) -> SVariable r
forall a b. (a, b) -> b
snd [(String, SVariable r)]
os) (((String, SVariable r) -> SVariable r)
-> [(String, SVariable r)] -> [SVariable r]
forall a b. (a -> b) -> [a] -> [b]
map (String, SVariable r) -> SVariable r
forall a b. (a, b) -> b
snd [(String, SVariable r)]
bs) MSBody r
b)
floatRender :: String
floatRender :: String
floatRender = String
"Float"
float :: (CommonRenderSym r) => VSType r
float :: forall (r :: * -> *). CommonRenderSym r => VSType r
float = CodeType
-> String -> Doc -> StateT ValueState Identity (r (Type r))
forall (r :: * -> *).
RenderType r =>
CodeType -> String -> Doc -> VSType r
typeFromData CodeType
Float String
floatRender (String -> Doc
text String
floatRender)
stringRender' :: String
stringRender' :: String
stringRender' = String
"String"
string' :: (CommonRenderSym r) => VSType r
string' :: forall (r :: * -> *). CommonRenderSym r => VSType r
string' = CodeType
-> String -> Doc -> StateT ValueState Identity (r (Type r))
forall (r :: * -> *).
RenderType r =>
CodeType -> String -> Doc -> VSType r
typeFromData CodeType
String String
stringRender' (String -> Doc
text String
stringRender')
inherit :: (Monad r) => Maybe Label -> r ParentSpec
inherit :: forall (r :: * -> *). Monad r => Maybe String -> r Doc
inherit Maybe String
n = Doc -> r Doc
forall (r :: * -> *) a. Monad r => a -> r a
toCode (Doc -> r Doc) -> Doc -> r Doc
forall a b. (a -> b) -> a -> b
$ Doc -> (String -> Doc) -> Maybe String -> Doc
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Doc
empty ((Doc
colon Doc -> Doc -> Doc
<+>) (Doc -> Doc) -> (String -> Doc) -> String -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Doc
text) Maybe String
n
implements :: (Monad r) => [Label] -> r ParentSpec
implements :: forall (r :: * -> *). Monad r => [String] -> r Doc
implements [String]
is = Doc -> r Doc
forall (r :: * -> *) a. Monad r => a -> r a
toCode (Doc -> r Doc) -> Doc -> r Doc
forall a b. (a -> b) -> a -> b
$ Doc
colon Doc -> Doc -> Doc
<+> String -> Doc
text (String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
listSep [String]
is)
forEach' :: (CommonRenderSym r) => (r (Variable r) -> r (Value r) -> r (Body r) -> Doc)
-> SVariable r -> SValue r -> MSBody r -> MSStatement r
forEach' :: forall (r :: * -> *).
CommonRenderSym r =>
(r (Variable r) -> r (Value r) -> r (Body r) -> Doc)
-> SVariable r -> SValue r -> MSBody r -> MSStatement r
forEach' r (Variable r) -> r (Value r) -> r (Body r) -> Doc
f SVariable r
i' SValue r
v' MSBody r
b' = do
r (Variable r)
i <- LensLike'
(Zoomed (StateT ValueState Identity) (r (Variable r)))
MethodState
ValueState
-> SVariable r -> StateT MethodState Identity (r (Variable r))
forall c.
LensLike'
(Zoomed (StateT ValueState Identity) c) MethodState ValueState
-> StateT ValueState Identity c -> StateT MethodState Identity c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
zoom LensLike'
(Zoomed (StateT ValueState Identity) (r (Variable r)))
MethodState
ValueState
(ValueState -> Focusing Identity (r (Variable r)) ValueState)
-> MethodState -> Focusing Identity (r (Variable r)) MethodState
Lens' MethodState ValueState
lensMStoVS SVariable r
i'
r (Value r)
v <- LensLike'
(Zoomed (StateT ValueState Identity) (r (Value r)))
MethodState
ValueState
-> SValue r -> StateT MethodState Identity (r (Value r))
forall c.
LensLike'
(Zoomed (StateT ValueState Identity) c) MethodState ValueState
-> StateT ValueState Identity c -> StateT MethodState Identity c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
zoom LensLike'
(Zoomed (StateT ValueState Identity) (r (Value r)))
MethodState
ValueState
(ValueState -> Focusing Identity (r (Value r)) ValueState)
-> MethodState -> Focusing Identity (r (Value r)) MethodState
Lens' MethodState ValueState
lensMStoVS SValue r
v'
r (Body r)
b <- MSBody r
b'
Doc -> MSStatement r
forall (r :: * -> *). CommonRenderSym r => Doc -> MSStatement r
mkStmtNoEnd (r (Variable r) -> r (Value r) -> r (Body r) -> Doc
f r (Variable r)
i r (Value r)
v r (Body r)
b)
boolRender :: String
boolRender :: String
boolRender = String
"Bool"
bool :: (CommonRenderSym r) => VSType r
bool :: forall (r :: * -> *). CommonRenderSym r => VSType r
bool = CodeType
-> String -> Doc -> StateT ValueState Identity (r (Type r))
forall (r :: * -> *).
RenderType r =>
CodeType -> String -> Doc -> VSType r
typeFromData CodeType
Boolean String
boolRender (String -> Doc
text String
boolRender)
docMod' :: (OORenderSym r) => String -> String -> [String] -> String -> SFile r -> SFile r
docMod' :: forall (r :: * -> *).
OORenderSym r =>
String -> String -> [String] -> String -> SFile r -> SFile r
docMod' = ModuleDocRenderer
-> String
-> String
-> [String]
-> String
-> StateT FileState Identity (r (File r))
-> StateT FileState Identity (r (File r))
forall (r :: * -> *).
OORenderSym r =>
ModuleDocRenderer
-> String -> String -> [String] -> String -> SFile r -> SFile r
docMod ModuleDocRenderer
modDoc'
modDoc' :: ModuleDocRenderer
modDoc' :: ModuleDocRenderer
modDoc' String
desc [String]
as String
date String
m = String
m String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String
desc | Bool -> Bool
not (String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
desc)] [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
[String -> String -> String
docField String
authorDoc ([String] -> String
stringList [String]
as) | Bool -> Bool
not ([String] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
as)] [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
[String -> String -> String
docField String
dateDoc String
date | Bool -> Bool
not (String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
date)] [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
[String -> String -> String
docField String
noteDoc String
watermark]
docField :: String -> String -> String
docField :: String -> String -> String
docField String
ty String
info = String
docCommandInit String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
ty String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
docCommandSep String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
info
functionDoc :: FuncDocRenderer
functionDoc :: FuncDocRenderer
functionDoc String
desc [(String, String)]
params [String]
returns = [String
desc | Bool -> Bool
not (String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
desc)]
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ ((String, String) -> String) -> [(String, String)] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (\(String
v, String
vDesc) -> String
docCommandInit String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
paramDoc String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
v String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
docCommandSep String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
vDesc) [(String, String)]
params
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map ((String
docCommandInit String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
returnDoc String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
docCommandSep) String -> String -> String
forall a. [a] -> [a] -> [a]
++) [String]
returns
docCommandInit, docCommandSep, authorDoc, dateDoc,
noteDoc, paramDoc, returnDoc :: String
docCommandInit :: String
docCommandInit = String
"- "
docCommandSep :: String
docCommandSep = String
": "
authorDoc :: String
authorDoc = String
"Authors"
dateDoc :: String
dateDoc = String
"Date"
noteDoc :: String
noteDoc = String
"Note"
paramDoc :: String
paramDoc = String
"Parameter"
returnDoc :: String
returnDoc = String
"Returns"
varDecDef :: (CommonRenderSym r) => SVariable r -> r (Scope r) -> Maybe (SValue r)
-> MSStatement r
varDecDef :: forall (r :: * -> *).
CommonRenderSym r =>
SVariable r -> r (Scope r) -> Maybe (SValue r) -> MSStatement r
varDecDef SVariable r
v r (Scope r)
scp Maybe (SValue r)
e = do
r (Variable r)
v' <- LensLike'
(Zoomed (StateT ValueState Identity) (r (Variable r)))
MethodState
ValueState
-> SVariable r -> StateT MethodState Identity (r (Variable r))
forall c.
LensLike'
(Zoomed (StateT ValueState Identity) c) MethodState ValueState
-> StateT ValueState Identity c -> StateT MethodState Identity c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
zoom LensLike'
(Zoomed (StateT ValueState Identity) (r (Variable r)))
MethodState
ValueState
(ValueState -> Focusing Identity (r (Variable r)) ValueState)
-> MethodState -> Focusing Identity (r (Variable r)) MethodState
Lens' MethodState ValueState
lensMStoVS SVariable r
v
(MethodState -> MethodState) -> StateT MethodState Identity ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((MethodState -> MethodState) -> StateT MethodState Identity ())
-> (MethodState -> MethodState) -> StateT MethodState Identity ()
forall a b. (a -> b) -> a -> b
$ String -> MethodState -> MethodState
useVarName (r (Variable r) -> String
forall (r :: * -> *). VariableElim r => r (Variable r) -> String
variableName r (Variable r)
v')
(MethodState -> MethodState) -> StateT MethodState Identity ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((MethodState -> MethodState) -> StateT MethodState Identity ())
-> (MethodState -> MethodState) -> StateT MethodState Identity ()
forall a b. (a -> b) -> a -> b
$ String -> ScopeData -> MethodState -> MethodState
setVarScope (r (Variable r) -> String
forall (r :: * -> *). VariableElim r => r (Variable r) -> String
variableName r (Variable r)
v') (r (Scope r) -> ScopeData
forall (r :: * -> *). ScopeElim r => r (Scope r) -> ScopeData
scopeData r (Scope r)
scp)
Maybe (SValue r) -> MSStatement r
def Maybe (SValue r)
e
where
def :: Maybe (SValue r) -> MSStatement r
def Maybe (SValue r)
Nothing = MSStatement r
forall (r :: * -> *). StatementSym r => MSStatement r
IC.emptyStmt
def (Just SValue r
d) = SVariable r -> SValue r -> MSStatement r
forall (r :: * -> *).
AssignStatement r =>
SVariable r -> SValue r -> MSStatement r
IC.assign SVariable r
v SValue r
d
fileOpen, fileR, fileW, fileA :: Label
fileOpen :: String
fileOpen = String
"open"
fileR :: String
fileR = String
"r"
fileW :: String
fileW = String
"w"
fileA :: String
fileA = String
"a"
openFileR', openFileW', openFileA' :: (CommonRenderSym r) => SValue r -> SValue r
openFileR' :: forall (r :: * -> *). CommonRenderSym r => SValue r -> SValue r
openFileR' SValue r
n = PosCall r
forall (r :: * -> *). ValueExpression r => PosCall r
funcApp String
fileOpen VSType r
forall (r :: * -> *). TypeSym r => VSType r
infile [SValue r
n, String -> SValue r
forall (r :: * -> *). Literal r => String -> SValue r
IC.litString String
fileR]
openFileW' :: forall (r :: * -> *). CommonRenderSym r => SValue r -> SValue r
openFileW' SValue r
n = PosCall r
forall (r :: * -> *). ValueExpression r => PosCall r
funcApp String
fileOpen VSType r
forall (r :: * -> *). TypeSym r => VSType r
infile [SValue r
n, String -> SValue r
forall (r :: * -> *). Literal r => String -> SValue r
IC.litString String
fileW]
openFileA' :: forall (r :: * -> *). CommonRenderSym r => SValue r -> SValue r
openFileA' SValue r
n = PosCall r
forall (r :: * -> *). ValueExpression r => PosCall r
funcApp String
fileOpen VSType r
forall (r :: * -> *). TypeSym r => VSType r
infile [SValue r
n, String -> SValue r
forall (r :: * -> *). Literal r => String -> SValue r
IC.litString String
fileA]
argExists :: (CommonRenderSym r) => Integer -> SValue r
argExists :: forall (r :: * -> *). CommonRenderSym r => Integer -> SValue r
argExists Integer
i = StateT ValueState Identity (r (Value r))
-> StateT ValueState Identity (r (Value r))
forall (r :: * -> *). CommonRenderSym r => SValue r -> SValue r
listSize StateT ValueState Identity (r (Value r))
forall (r :: * -> *). CommandLineArgs r => SValue r
IC.argsList StateT ValueState Identity (r (Value r))
-> StateT ValueState Identity (r (Value r))
-> StateT ValueState Identity (r (Value r))
forall (r :: * -> *).
Comparison r =>
SValue r -> SValue r -> SValue r
?> Integer -> StateT ValueState Identity (r (Value r))
forall (r :: * -> *). Literal r => Integer -> SValue r
IC.litInt (Integer -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Integer) -> Integer -> Integer
forall a b. (a -> b) -> a -> b
$ Integer
iInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
+Integer
1)
listSize :: (CommonRenderSym r) => SValue r -> SValue r
listSize :: forall (r :: * -> *). CommonRenderSym r => SValue r -> SValue r
listSize SValue r
l = do
r (Function r)
f <- SValue r -> StateT ValueState Identity (r (Function r))
forall (r :: * -> *).
InternalListFunc r =>
SValue r -> VSFunction r
S.listSizeFunc SValue r
l
r (Type r) -> Doc -> SValue r
forall (r :: * -> *).
CommonRenderSym r =>
r (Type r) -> Doc -> SValue r
mkVal (r (Function r) -> r (Type r)
forall (r :: * -> *).
FunctionElim r =>
r (Function r) -> r (Type r)
RC.functionType r (Function r)
f) (r (Function r) -> Doc
forall (r :: * -> *). FunctionElim r => r (Function r) -> Doc
RC.function r (Function r)
f)
listAdd :: (CommonRenderSym r) => SValue r -> SValue r -> SValue r -> SValue r
listAdd :: forall (r :: * -> *).
CommonRenderSym r =>
SValue r -> SValue r -> SValue r -> SValue r
listAdd SValue r
l SValue r
i SValue r
v = do
r (Function r)
f <- SValue r
-> SValue r
-> SValue r
-> StateT ValueState Identity (r (Function r))
forall (r :: * -> *).
InternalListFunc r =>
SValue r -> SValue r -> SValue r -> VSFunction r
S.listAddFunc SValue r
l (SValue r -> SValue r
forall (r :: * -> *). List r => SValue r -> SValue r
IC.intToIndex SValue r
i) SValue r
v
r (Type r) -> Doc -> SValue r
forall (r :: * -> *).
CommonRenderSym r =>
r (Type r) -> Doc -> SValue r
mkVal (r (Function r) -> r (Type r)
forall (r :: * -> *).
FunctionElim r =>
r (Function r) -> r (Type r)
RC.functionType r (Function r)
f) (r (Function r) -> Doc
forall (r :: * -> *). FunctionElim r => r (Function r) -> Doc
RC.function r (Function r)
f)
listAppend :: (CommonRenderSym r) => SValue r -> SValue r -> SValue r
listAppend :: forall (r :: * -> *).
CommonRenderSym r =>
SValue r -> SValue r -> SValue r
listAppend SValue r
l SValue r
v = do
r (Function r)
f <- SValue r -> SValue r -> StateT ValueState Identity (r (Function r))
forall (r :: * -> *).
InternalListFunc r =>
SValue r -> SValue r -> VSFunction r
S.listAppendFunc SValue r
l SValue r
v
r (Type r) -> Doc -> SValue r
forall (r :: * -> *).
CommonRenderSym r =>
r (Type r) -> Doc -> SValue r
mkVal (r (Function r) -> r (Type r)
forall (r :: * -> *).
FunctionElim r =>
r (Function r) -> r (Type r)
RC.functionType r (Function r)
f) (r (Function r) -> Doc
forall (r :: * -> *). FunctionElim r => r (Function r) -> Doc
RC.function r (Function r)
f)
intToIndex' :: (CommonRenderSym r) => SValue r -> SValue r
intToIndex' :: forall (r :: * -> *). CommonRenderSym r => SValue r -> SValue r
intToIndex' SValue r
v = SValue r
v SValue r -> SValue r -> SValue r
forall (r :: * -> *).
CommonRenderSym r =>
SValue r -> SValue r -> SValue r
`smartAdd` Integer -> SValue r
forall (r :: * -> *). Literal r => Integer -> SValue r
IC.litInt Integer
1
indexToInt' :: (CommonRenderSym r) => SValue r -> SValue r
indexToInt' :: forall (r :: * -> *). CommonRenderSym r => SValue r -> SValue r
indexToInt' SValue r
v = SValue r
v SValue r -> SValue r -> SValue r
forall (r :: * -> *).
CommonRenderSym r =>
SValue r -> SValue r -> SValue r
`smartSub` Integer -> SValue r
forall (r :: * -> *). Literal r => Integer -> SValue r
IC.litInt Integer
1