Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Drasil.GOOL
Description
re-export smart constructors for external code writing
Synopsis
- type Label = String
- type GSProgram a = GS (a (Program a))
- type SFile a = FS (a (File a))
- type MSBody a = MS (a (Body a))
- type MSBlock a = MS (a (Block a))
- type VSType a = VS (a (Type a))
- type SVariable a = VS (a (Variable a))
- type SValue a = VS (a (Value a))
- type VSFunction a = VS (a (Function a))
- type MSStatement a = MS (a (Statement a))
- type MSParameter a = MS (a (Parameter a))
- type SMethod a = MS (a (Method a))
- type CSStateVar a = CS (a (StateVar a))
- type SClass a = CS (a (Class a))
- type FSModule a = FS (a (Module a))
- type NamedArgs r = [(SVariable r, SValue r)]
- type Initializers r = [(SVariable r, SValue r)]
- class (VectorType r, VectorDecl r, VectorThunk r, VectorExpression r, ThunkAssign r, AssignStatement r, DeclStatement r, IOStatement r, StringStatement r, FunctionSym r, FuncAppStatement r, CommentStatement r, ControlStatement r, InternalList r, Argument r, Literal r, MathConstant r, VariableValue r, CommandLineArgs r, NumericExpression r, BooleanExpression r, Comparison r, ValueExpression r, List r, Set r, TypeElim r, VariableElim r, MethodSym r, ScopeSym r) => SharedProg r
- class (SharedProg r, ProgramSym r, OOVariableValue r, OODeclStatement r, OOFuncAppStatement r, OOValueExpression r, InternalValueExp r, GetSet r, ObserverPattern r, StrategyPattern r) => OOProg r
- class FileSym r => ProgramSym r where
- class ModuleSym r => FileSym r where
- class PermanenceSym r where
- type Permanence r
- static :: r (Permanence r)
- dynamic :: r (Permanence r)
- class BlockSym r => BodySym r where
- bodyStatements :: BodySym r => [MSStatement r] -> MSBody r
- oneLiner :: BodySym r => MSStatement r -> MSBody r
- class StatementSym r => BlockSym r where
- type Block r
- block :: [MSStatement r] -> MSBlock r
- class TypeSym r where
- type Type r
- bool :: VSType r
- int :: VSType r
- float :: VSType r
- double :: VSType r
- char :: VSType r
- string :: VSType r
- infile :: VSType r
- outfile :: VSType r
- listType :: VSType r -> VSType r
- setType :: VSType r -> VSType r
- arrayType :: VSType r -> VSType r
- listInnerType :: VSType r -> VSType r
- funcType :: [VSType r] -> VSType r -> VSType r
- void :: VSType r
- class TypeSym r => OOTypeSym r where
- class TypeSym r => TypeElim r where
- class ThunkSym r where
- class TypeSym r => VectorType r where
- class DeclStatement r => VectorDecl r where
- vecDec :: Integer -> SVariable r -> r (Scope r) -> MSStatement r
- vecDecDef :: SVariable r -> r (Scope r) -> [SValue r] -> MSStatement r
- class (VariableSym r, ThunkSym r) => VectorThunk r where
- class (ThunkSym r, ValueSym r) => VectorExpression r where
- class (VariableSym r, ThunkSym r, StatementSym r) => ThunkAssign r where
- thunkAssign :: SVariable r -> VSThunk r -> MSStatement r
- class ValueSym r => StatementSym r where
- type Statement r
- valStmt :: SValue r -> MSStatement r
- emptyStmt :: MSStatement r
- multi :: [MSStatement r] -> MSStatement r
- class (VariableSym r, StatementSym r) => AssignStatement r where
- (&-=) :: SVariable r -> SValue r -> MSStatement r
- (&+=) :: SVariable r -> SValue r -> MSStatement r
- (&++) :: SVariable r -> MSStatement r
- (&--) :: SVariable r -> MSStatement r
- assign :: SVariable r -> SValue r -> MSStatement r
- (&=) :: AssignStatement r => SVariable r -> SValue r -> MSStatement r
- assignToListIndex :: (StatementSym r, VariableValue r, List r) => SVariable r -> SValue r -> SValue r -> MSStatement r
- class (VariableSym r, StatementSym r, ScopeSym r) => DeclStatement r where
- varDec :: SVariable r -> r (Scope r) -> MSStatement r
- varDecDef :: SVariable r -> r (Scope r) -> SValue r -> MSStatement r
- listDec :: Integer -> SVariable r -> r (Scope r) -> MSStatement r
- listDecDef :: SVariable r -> r (Scope r) -> [SValue r] -> MSStatement r
- setDec :: SVariable r -> r (Scope r) -> MSStatement r
- setDecDef :: SVariable r -> r (Scope r) -> SValue r -> MSStatement r
- arrayDec :: Integer -> SVariable r -> r (Scope r) -> MSStatement r
- arrayDecDef :: SVariable r -> r (Scope r) -> [SValue r] -> MSStatement r
- constDecDef :: SVariable r -> r (Scope r) -> SValue r -> MSStatement r
- funcDecDef :: SVariable r -> r (Scope r) -> [SVariable r] -> MSBody r -> MSStatement r
- class (DeclStatement r, OOVariableSym r) => OODeclStatement r where
- objDecDef :: SVariable r -> r (Scope r) -> SValue r -> MSStatement r
- objDecNew :: SVariable r -> r (Scope r) -> [SValue r] -> MSStatement r
- extObjDecNew :: Library -> SVariable r -> r (Scope r) -> [SValue r] -> MSStatement r
- objDecNewNoParams :: OODeclStatement r => SVariable r -> r (Scope r) -> MSStatement r
- extObjDecNewNoParams :: OODeclStatement r => Library -> SVariable r -> r (Scope r) -> MSStatement r
- class (VariableSym r, StatementSym r) => IOStatement r where
- print :: SValue r -> MSStatement r
- printLn :: SValue r -> MSStatement r
- printStr :: String -> MSStatement r
- printStrLn :: String -> MSStatement r
- printFile :: SValue r -> SValue r -> MSStatement r
- printFileLn :: SValue r -> SValue r -> MSStatement r
- printFileStr :: SValue r -> String -> MSStatement r
- printFileStrLn :: SValue r -> String -> MSStatement r
- getInput :: SVariable r -> MSStatement r
- discardInput :: MSStatement r
- getFileInput :: SValue r -> SVariable r -> MSStatement r
- discardFileInput :: SValue r -> MSStatement r
- openFileR :: SVariable r -> SValue r -> MSStatement r
- openFileW :: SVariable r -> SValue r -> MSStatement r
- openFileA :: SVariable r -> SValue r -> MSStatement r
- closeFile :: SValue r -> MSStatement r
- getFileInputLine :: SValue r -> SVariable r -> MSStatement r
- discardFileLine :: SValue r -> MSStatement r
- getFileInputAll :: SValue r -> SVariable r -> MSStatement r
- class (VariableSym r, StatementSym r) => StringStatement r where
- stringSplit :: Char -> SVariable r -> SValue r -> MSStatement r
- stringListVals :: [SVariable r] -> SValue r -> MSStatement r
- stringListLists :: [SVariable r] -> SValue r -> MSStatement r
- class (VariableSym r, StatementSym r) => FuncAppStatement r where
- inOutCall :: InOutCall r
- extInOutCall :: Library -> InOutCall r
- class (FuncAppStatement r, OOVariableSym r) => OOFuncAppStatement r where
- selfInOutCall :: InOutCall r
- class StatementSym r => CommentStatement r where
- comment :: Comment -> MSStatement r
- initObserverList :: DeclStatement r => VSType r -> [SValue r] -> r (Scope r) -> MSStatement r
- addObserver :: (StatementSym r, OOVariableValue r, List r) => SValue r -> MSStatement r
- class (BodySym r, VariableSym r) => ControlStatement r where
- break :: MSStatement r
- continue :: MSStatement r
- returnStmt :: SValue r -> MSStatement r
- throw :: Label -> MSStatement r
- ifCond :: [(SValue r, MSBody r)] -> MSBody r -> MSStatement r
- switch :: SValue r -> [(SValue r, MSBody r)] -> MSBody r -> MSStatement r
- ifExists :: SValue r -> MSBody r -> MSBody r -> MSStatement r
- for :: MSStatement r -> SValue r -> MSStatement r -> MSBody r -> MSStatement r
- forRange :: SVariable r -> SValue r -> SValue r -> SValue r -> MSBody r -> MSStatement r
- forEach :: SVariable r -> SValue r -> MSBody r -> MSStatement r
- while :: SValue r -> MSBody r -> MSStatement r
- tryCatch :: MSBody r -> MSBody r -> MSStatement r
- assert :: SValue r -> SValue r -> MSStatement r
- ifNoElse :: ControlStatement r => [(SValue r, MSBody r)] -> MSStatement r
- switchAsIf :: (ControlStatement r, Comparison r) => SValue r -> [(SValue r, MSBody r)] -> MSBody r -> MSStatement r
- class TypeSym r => VariableSym r where
- class ScopeSym r where
- class (VariableSym r, OOTypeSym r) => OOVariableSym r where
- staticVar :: OOVariableSym r => Label -> VSType r -> SVariable r
- staticConst :: OOVariableSym r => Label -> VSType r -> SVariable r
- class VariableSym r => VariableElim r where
- variableName :: r (Variable r) -> String
- variableType :: r (Variable r) -> r (Type r)
- ($->) :: OOVariableSym r => SVariable r -> SVariable r -> SVariable r
- listOf :: VariableSym r => Label -> VSType r -> SVariable r
- listVar :: VariableSym r => Label -> VSType r -> SVariable r
- class TypeSym r => ValueSym r where
- class ValueSym r => Argument r where
- pointerArg :: SValue r -> SValue r
- class ValueSym r => Literal r where
- litTrue :: SValue r
- litFalse :: SValue r
- litChar :: Char -> SValue r
- litDouble :: Double -> SValue r
- litFloat :: Float -> SValue r
- litInt :: Integer -> SValue r
- litString :: String -> SValue r
- litArray :: VSType r -> [SValue r] -> SValue r
- litList :: VSType r -> [SValue r] -> SValue r
- litSet :: VSType r -> [SValue r] -> SValue r
- class ValueSym r => MathConstant r where
- class (VariableSym r, ValueSym r) => VariableValue r where
- class (VariableValue r, OOVariableSym r) => OOVariableValue r
- class ValueSym r => CommandLineArgs r where
- class ValueSym r => NumericExpression r where
- (#~) :: SValue r -> SValue r
- (#/^) :: SValue r -> SValue r
- (#|) :: SValue r -> SValue r
- (#+) :: SValue r -> SValue r -> SValue r
- (#-) :: SValue r -> SValue r -> SValue r
- (#*) :: SValue r -> SValue r -> SValue r
- (#/) :: SValue r -> SValue r -> SValue r
- (#%) :: SValue r -> SValue r -> SValue r
- (#^) :: SValue r -> SValue r -> SValue r
- log :: SValue r -> SValue r
- ln :: SValue r -> SValue r
- exp :: SValue r -> SValue r
- sin :: SValue r -> SValue r
- cos :: SValue r -> SValue r
- tan :: SValue r -> SValue r
- csc :: SValue r -> SValue r
- sec :: SValue r -> SValue r
- cot :: SValue r -> SValue r
- arcsin :: SValue r -> SValue r
- arccos :: SValue r -> SValue r
- arctan :: SValue r -> SValue r
- floor :: SValue r -> SValue r
- ceil :: SValue r -> SValue r
- class ValueSym r => BooleanExpression r where
- class ValueSym r => Comparison r where
- class (VariableSym r, ValueSym r) => ValueExpression r where
- class (ValueExpression r, OOVariableSym r, OOValueSym r) => OOValueExpression r where
- funcApp :: ValueExpression r => PosCall r
- funcAppNamedArgs :: ValueExpression r => Label -> VSType r -> NamedArgs r -> SValue r
- selfFuncApp :: OOValueExpression r => PosCall r
- extFuncApp :: ValueExpression r => Library -> PosCall r
- libFuncApp :: ValueExpression r => Library -> PosCall r
- newObj :: OOValueExpression r => PosCtorCall r
- extNewObj :: OOValueExpression r => Library -> PosCtorCall r
- libNewObj :: OOValueExpression r => Library -> PosCtorCall r
- exists :: ValueExpression r => SValue r -> SValue r
- objMethodCall :: InternalValueExp r => VSType r -> SValue r -> Label -> [SValue r] -> SValue r
- objMethodCallNamedArgs :: InternalValueExp r => VSType r -> SValue r -> Label -> NamedArgs r -> SValue r
- objMethodCallMixedArgs :: InternalValueExp r => VSType r -> SValue r -> Label -> [SValue r] -> NamedArgs r -> SValue r
- objMethodCallNoParams :: InternalValueExp r => VSType r -> SValue r -> Label -> SValue r
- class ValueSym r => FunctionSym r where
- type Function r
- class FunctionSym r => OOFunctionSym r where
- func :: Label -> VSType r -> [SValue r] -> VSFunction r
- objAccess :: SValue r -> VSFunction r -> SValue r
- ($.) :: OOFunctionSym r => SValue r -> VSFunction r -> SValue r
- selfAccess :: (OOVariableValue r, OOFunctionSym r) => VSFunction r -> SValue r
- class (ValueSym r, VariableSym r) => GetSet r where
- class ValueSym r => List r where
- intToIndex :: SValue r -> SValue r
- indexToInt :: SValue r -> SValue r
- listSize :: SValue r -> SValue r
- listAdd :: SValue r -> SValue r -> SValue r -> SValue r
- listAppend :: SValue r -> SValue r -> SValue r
- listAccess :: SValue r -> SValue r -> SValue r
- listSet :: SValue r -> SValue r -> SValue r -> SValue r
- indexOf :: SValue r -> SValue r -> SValue r
- class ValueSym r => Set r where
- listSlice :: InternalList r => SVariable r -> SValue r -> Maybe (SValue r) -> Maybe (SValue r) -> Maybe (SValue r) -> MSBlock r
- listIndexExists :: (List r, Comparison r) => SValue r -> SValue r -> SValue r
- at :: List r => SValue r -> SValue r -> SValue r
- class (StatementSym r, OOFunctionSym r) => ObserverPattern r where
- notifyObservers :: VSFunction r -> VSType r -> MSStatement r
- class (BodySym r, VariableSym r) => StrategyPattern r where
- class VisibilitySym r where
- type Visibility r
- private :: r (Visibility r)
- public :: r (Visibility r)
- class VariableSym r => ParameterSym r where
- type Parameter r
- param :: SVariable r -> MSParameter r
- pointerParam :: SVariable r -> MSParameter r
- class (BodySym r, ParameterSym r, VisibilitySym r) => MethodSym r where
- type Method r
- docMain :: MSBody r -> SMethod r
- function :: Label -> r (Visibility r) -> VSType r -> [MSParameter r] -> MSBody r -> SMethod r
- mainFunction :: MSBody r -> SMethod r
- docFunc :: String -> [String] -> Maybe String -> SMethod r -> SMethod r
- inOutFunc :: Label -> r (Visibility r) -> InOutFunc r
- docInOutFunc :: Label -> r (Visibility r) -> DocInOutFunc r
- class (MethodSym r, PermanenceSym r) => OOMethodSym r where
- method :: Label -> r (Visibility r) -> r (Permanence r) -> VSType r -> [MSParameter r] -> MSBody r -> SMethod r
- getMethod :: SVariable r -> SMethod r
- setMethod :: SVariable r -> SMethod r
- constructor :: [MSParameter r] -> Initializers r -> MSBody r -> SMethod r
- inOutMethod :: Label -> r (Visibility r) -> r (Permanence r) -> InOutFunc r
- docInOutMethod :: Label -> r (Visibility r) -> r (Permanence r) -> DocInOutFunc r
- privMethod :: OOMethodSym r => Label -> VSType r -> [MSParameter r] -> MSBody r -> SMethod r
- pubMethod :: OOMethodSym r => Label -> VSType r -> [MSParameter r] -> MSBody r -> SMethod r
- initializer :: OOMethodSym r => [MSParameter r] -> Initializers r -> SMethod r
- nonInitConstructor :: OOMethodSym r => [MSParameter r] -> MSBody r -> SMethod r
- class (VisibilitySym r, PermanenceSym r, VariableSym r) => StateVarSym r where
- type StateVar r
- stateVar :: r (Visibility r) -> r (Permanence r) -> SVariable r -> CSStateVar r
- stateVarDef :: r (Visibility r) -> r (Permanence r) -> SVariable r -> SValue r -> CSStateVar r
- constVar :: r (Visibility r) -> SVariable r -> SValue r -> CSStateVar r
- privDVar :: StateVarSym r => SVariable r -> CSStateVar r
- pubDVar :: StateVarSym r => SVariable r -> CSStateVar r
- pubSVar :: StateVarSym r => SVariable r -> CSStateVar r
- class (OOMethodSym r, StateVarSym r) => ClassSym r where
- type Class r
- buildClass :: Maybe Label -> [CSStateVar r] -> [SMethod r] -> [SMethod r] -> SClass r
- extraClass :: Label -> Maybe Label -> [CSStateVar r] -> [SMethod r] -> [SMethod r] -> SClass r
- implementingClass :: Label -> [Label] -> [CSStateVar r] -> [SMethod r] -> [SMethod r] -> SClass r
- docClass :: String -> SClass r -> SClass r
- class ClassSym r => ModuleSym r where
- convType :: TypeSym r => CodeType -> VSType r
- convTypeOO :: OOTypeSym r => CodeType -> VSType r
- data ProgData
- data FileData
- data ModData
- data VisibilityTag
- data CodeType
- data GOOLState = GS {}
- lensMStoVS :: Lens' MethodState ValueState
- headers :: Lens' GOOLState [FilePath]
- sources :: Lens' GOOLState [FilePath]
- mainMod :: Lens' GOOLState (Maybe FilePath)
- initialState :: GOOLState
- onStateValue :: (a -> b) -> State s a -> State s b
- onCodeList :: Monad m => ([a] -> b) -> [m a] -> m b
- unCI :: CodeInfoOO a -> a
- unPC :: PythonCode a -> a
- unJC :: JavaCode a -> a
- unCSC :: CSharpCode a -> a
- unCPPC :: CppCode CppSrcCode CppHdrCode a -> a
- unSC :: SwiftCode a -> a
- pyName :: String
- pyVersion :: String
- jName :: String
- jVersion :: String
- csName :: String
- csVersion :: String
- cppName :: String
- cppVersion :: String
- swiftName :: String
- swiftVersion :: String
Documentation
type VSFunction a = VS (a (Function a)) Source #
type MSStatement a = MS (a (Statement a)) Source #
type MSParameter a = MS (a (Parameter a)) Source #
type CSStateVar a = CS (a (StateVar a)) Source #
type Initializers r = [(SVariable r, SValue r)] Source #
class (VectorType r, VectorDecl r, VectorThunk r, VectorExpression r, ThunkAssign r, AssignStatement r, DeclStatement r, IOStatement r, StringStatement r, FunctionSym r, FuncAppStatement r, CommentStatement r, ControlStatement r, InternalList r, Argument r, Literal r, MathConstant r, VariableValue r, CommandLineArgs r, NumericExpression r, BooleanExpression r, Comparison r, ValueExpression r, List r, Set r, TypeElim r, VariableElim r, MethodSym r, ScopeSym r) => SharedProg r Source #
Instances
class (SharedProg r, ProgramSym r, OOVariableValue r, OODeclStatement r, OOFuncAppStatement r, OOValueExpression r, InternalValueExp r, GetSet r, ObserverPattern r, StrategyPattern r) => OOProg r Source #
Instances
OOProg CodeInfoOO Source # | |
Defined in Drasil.GOOL.CodeInfoOO | |
OOProg CSharpCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.CSharpRenderer | |
OOProg JavaCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.JavaRenderer | |
OOProg PythonCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.PythonRenderer | |
OOProg SwiftCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.SwiftRenderer | |
Pair p => OOProg (p CppSrcCode CppHdrCode) Source # | |
Defined in Drasil.GOOL.LanguageRenderer.CppRenderer |
class FileSym r => ProgramSym r where Source #
Instances
class ModuleSym r => FileSym r where Source #
Methods
fileDoc :: FSModule r -> SFile r Source #
docMod :: String -> [String] -> String -> SFile r -> SFile r Source #
Instances
class PermanenceSym r where Source #
Associated Types
type Permanence r Source #
Instances
class BlockSym r => BodySym r where Source #
Instances
bodyStatements :: BodySym r => [MSStatement r] -> MSBody r Source #
class StatementSym r => BlockSym r where Source #
Methods
block :: [MSStatement r] -> MSBlock r Source #
Instances
class TypeSym r where Source #
Methods
listType :: VSType r -> VSType r Source #
setType :: VSType r -> VSType r Source #
arrayType :: VSType r -> VSType r Source #
listInnerType :: VSType r -> VSType r Source #
Instances
class TypeSym r => OOTypeSym r where Source #
Instances
OOTypeSym CodeInfoOO Source # | |
Defined in Drasil.GOOL.CodeInfoOO | |
OOTypeSym CSharpCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.CSharpRenderer | |
OOTypeSym CppHdrCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.CppRenderer | |
OOTypeSym CppSrcCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.CppRenderer | |
OOTypeSym JavaCode Source # | |
OOTypeSym PythonCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.PythonRenderer | |
OOTypeSym SwiftCode Source # | |
Pair p => OOTypeSym (p CppSrcCode CppHdrCode) Source # | |
Defined in Drasil.GOOL.LanguageRenderer.CppRenderer Methods obj :: ClassName -> VSType (p CppSrcCode CppHdrCode) Source # |
class TypeSym r => TypeElim r where Source #
Instances
Instances
class TypeSym r => VectorType r where Source #
Instances
class DeclStatement r => VectorDecl r where Source #
Methods
vecDec :: Integer -> SVariable r -> r (Scope r) -> MSStatement r Source #
vecDecDef :: SVariable r -> r (Scope r) -> [SValue r] -> MSStatement r Source #
Instances
class (VariableSym r, ThunkSym r) => VectorThunk r where Source #
Instances
class (ThunkSym r, ValueSym r) => VectorExpression r where Source #
Methods
vecScale :: SValue r -> VSThunk r -> VSThunk r Source #
vecAdd :: VSThunk r -> VSThunk r -> VSThunk r Source #
Instances
class (VariableSym r, ThunkSym r, StatementSym r) => ThunkAssign r where Source #
Methods
thunkAssign :: SVariable r -> VSThunk r -> MSStatement r Source #
Instances
class ValueSym r => StatementSym r where Source #
Methods
valStmt :: SValue r -> MSStatement r Source #
emptyStmt :: MSStatement r Source #
multi :: [MSStatement r] -> MSStatement r Source #
Instances
class (VariableSym r, StatementSym r) => AssignStatement r where Source #
Methods
(&-=) :: SVariable r -> SValue r -> MSStatement r infixl 1 Source #
(&+=) :: SVariable r -> SValue r -> MSStatement r infixl 1 Source #
(&++) :: SVariable r -> MSStatement r infixl 8 Source #
(&--) :: SVariable r -> MSStatement r infixl 8 Source #
Instances
(&=) :: AssignStatement r => SVariable r -> SValue r -> MSStatement r infixr 1 Source #
assignToListIndex :: (StatementSym r, VariableValue r, List r) => SVariable r -> SValue r -> SValue r -> MSStatement r Source #
class (VariableSym r, StatementSym r, ScopeSym r) => DeclStatement r where Source #
Methods
varDec :: SVariable r -> r (Scope r) -> MSStatement r Source #
varDecDef :: SVariable r -> r (Scope r) -> SValue r -> MSStatement r Source #
listDec :: Integer -> SVariable r -> r (Scope r) -> MSStatement r Source #
listDecDef :: SVariable r -> r (Scope r) -> [SValue r] -> MSStatement r Source #
setDec :: SVariable r -> r (Scope r) -> MSStatement r Source #
setDecDef :: SVariable r -> r (Scope r) -> SValue r -> MSStatement r Source #
arrayDec :: Integer -> SVariable r -> r (Scope r) -> MSStatement r Source #
arrayDecDef :: SVariable r -> r (Scope r) -> [SValue r] -> MSStatement r Source #
constDecDef :: SVariable r -> r (Scope r) -> SValue r -> MSStatement r Source #
funcDecDef :: SVariable r -> r (Scope r) -> [SVariable r] -> MSBody r -> MSStatement r Source #
Instances
class (DeclStatement r, OOVariableSym r) => OODeclStatement r where Source #
Methods
objDecDef :: SVariable r -> r (Scope r) -> SValue r -> MSStatement r Source #
objDecNew :: SVariable r -> r (Scope r) -> [SValue r] -> MSStatement r Source #
extObjDecNew :: Library -> SVariable r -> r (Scope r) -> [SValue r] -> MSStatement r Source #
Instances
objDecNewNoParams :: OODeclStatement r => SVariable r -> r (Scope r) -> MSStatement r Source #
extObjDecNewNoParams :: OODeclStatement r => Library -> SVariable r -> r (Scope r) -> MSStatement r Source #
class (VariableSym r, StatementSym r) => IOStatement r where Source #
Methods
print :: SValue r -> MSStatement r Source #
printLn :: SValue r -> MSStatement r Source #
printStr :: String -> MSStatement r Source #
printStrLn :: String -> MSStatement r Source #
printFile :: SValue r -> SValue r -> MSStatement r Source #
printFileLn :: SValue r -> SValue r -> MSStatement r Source #
printFileStr :: SValue r -> String -> MSStatement r Source #
printFileStrLn :: SValue r -> String -> MSStatement r Source #
getInput :: SVariable r -> MSStatement r Source #
discardInput :: MSStatement r Source #
getFileInput :: SValue r -> SVariable r -> MSStatement r Source #
discardFileInput :: SValue r -> MSStatement r Source #
openFileR :: SVariable r -> SValue r -> MSStatement r Source #
openFileW :: SVariable r -> SValue r -> MSStatement r Source #
openFileA :: SVariable r -> SValue r -> MSStatement r Source #
closeFile :: SValue r -> MSStatement r Source #
getFileInputLine :: SValue r -> SVariable r -> MSStatement r Source #
discardFileLine :: SValue r -> MSStatement r Source #
getFileInputAll :: SValue r -> SVariable r -> MSStatement r Source #
Instances
class (VariableSym r, StatementSym r) => StringStatement r where Source #
Methods
stringSplit :: Char -> SVariable r -> SValue r -> MSStatement r Source #
stringListVals :: [SVariable r] -> SValue r -> MSStatement r Source #
stringListLists :: [SVariable r] -> SValue r -> MSStatement r Source #
Instances
class (VariableSym r, StatementSym r) => FuncAppStatement r where Source #
Instances
FuncAppStatement CodeInfoOO Source # | |
Defined in Drasil.GOOL.CodeInfoOO Methods | |
FuncAppStatement CodeInfoProc Source # | |
Defined in Drasil.GOOL.CodeInfoProc Methods | |
FuncAppStatement CSharpCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.CSharpRenderer Methods | |
FuncAppStatement CppHdrCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.CppRenderer Methods | |
FuncAppStatement CppSrcCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.CppRenderer Methods | |
FuncAppStatement JavaCode Source # | |
FuncAppStatement JuliaCode Source # | |
FuncAppStatement PythonCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.PythonRenderer Methods | |
FuncAppStatement SwiftCode Source # | |
Pair p => FuncAppStatement (p CppSrcCode CppHdrCode) Source # | |
Defined in Drasil.GOOL.LanguageRenderer.CppRenderer Methods inOutCall :: InOutCall (p CppSrcCode CppHdrCode) Source # extInOutCall :: Library -> InOutCall (p CppSrcCode CppHdrCode) Source # |
class (FuncAppStatement r, OOVariableSym r) => OOFuncAppStatement r where Source #
Methods
selfInOutCall :: InOutCall r Source #
Instances
OOFuncAppStatement CodeInfoOO Source # | |
Defined in Drasil.GOOL.CodeInfoOO Methods | |
OOFuncAppStatement CSharpCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.CSharpRenderer Methods | |
OOFuncAppStatement CppHdrCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.CppRenderer Methods | |
OOFuncAppStatement CppSrcCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.CppRenderer Methods | |
OOFuncAppStatement JavaCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.JavaRenderer Methods | |
OOFuncAppStatement PythonCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.PythonRenderer Methods | |
OOFuncAppStatement SwiftCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.SwiftRenderer Methods | |
Pair p => OOFuncAppStatement (p CppSrcCode CppHdrCode) Source # | |
Defined in Drasil.GOOL.LanguageRenderer.CppRenderer Methods selfInOutCall :: InOutCall (p CppSrcCode CppHdrCode) Source # |
class StatementSym r => CommentStatement r where Source #
Methods
comment :: Comment -> MSStatement r Source #
Instances
initObserverList :: DeclStatement r => VSType r -> [SValue r] -> r (Scope r) -> MSStatement r Source #
addObserver :: (StatementSym r, OOVariableValue r, List r) => SValue r -> MSStatement r Source #
class (BodySym r, VariableSym r) => ControlStatement r where Source #
Methods
break :: MSStatement r Source #
continue :: MSStatement r Source #
returnStmt :: SValue r -> MSStatement r Source #
throw :: Label -> MSStatement r Source #
ifCond :: [(SValue r, MSBody r)] -> MSBody r -> MSStatement r Source #
String of if-else statements. Arguments: List of predicates and bodies (if this then that), Body for else branch
switch :: SValue r -> [(SValue r, MSBody r)] -> MSBody r -> MSStatement r Source #
ifExists :: SValue r -> MSBody r -> MSBody r -> MSStatement r Source #
for :: MSStatement r -> SValue r -> MSStatement r -> MSBody r -> MSStatement r Source #
forRange :: SVariable r -> SValue r -> SValue r -> SValue r -> MSBody r -> MSStatement r Source #
forEach :: SVariable r -> SValue r -> MSBody r -> MSStatement r Source #
while :: SValue r -> MSBody r -> MSStatement r Source #
Instances
ifNoElse :: ControlStatement r => [(SValue r, MSBody r)] -> MSStatement r Source #
switchAsIf :: (ControlStatement r, Comparison r) => SValue r -> [(SValue r, MSBody r)] -> MSBody r -> MSStatement r Source #
class TypeSym r => VariableSym r where Source #
Methods
var :: Label -> VSType r -> SVariable r Source #
constant :: Label -> VSType r -> SVariable r Source #
extVar :: Library -> Label -> VSType r -> SVariable r Source #
Instances
class ScopeSym r where Source #
Instances
class (VariableSym r, OOTypeSym r) => OOVariableSym r where Source #
Methods
staticVar' :: Bool -> Label -> VSType r -> SVariable r Source #
classVar :: VSType r -> SVariable r -> SVariable r Source #
extClassVar :: VSType r -> SVariable r -> SVariable r Source #
objVar :: SVariable r -> SVariable r -> SVariable r Source #
objVarSelf :: SVariable r -> SVariable r Source #
Instances
staticConst :: OOVariableSym r => Label -> VSType r -> SVariable r Source #
class VariableSym r => VariableElim r where Source #
Methods
variableName :: r (Variable r) -> String Source #
variableType :: r (Variable r) -> r (Type r) Source #
Instances
class TypeSym r => ValueSym r where Source #
Instances
class ValueSym r => Argument r where Source #
Methods
pointerArg :: SValue r -> SValue r Source #
Instances
class ValueSym r => Literal r where Source #
Methods
litChar :: Char -> SValue r Source #
litDouble :: Double -> SValue r Source #
litFloat :: Float -> SValue r Source #
litInt :: Integer -> SValue r Source #
litString :: String -> SValue r Source #
litArray :: VSType r -> [SValue r] -> SValue r Source #
Instances
class ValueSym r => MathConstant r where Source #
Instances
MathConstant CodeInfoOO Source # | |
Defined in Drasil.GOOL.CodeInfoOO Methods pi :: SValue CodeInfoOO Source # | |
MathConstant CodeInfoProc Source # | |
Defined in Drasil.GOOL.CodeInfoProc Methods pi :: SValue CodeInfoProc Source # | |
MathConstant CSharpCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.CSharpRenderer Methods pi :: SValue CSharpCode Source # | |
MathConstant CppHdrCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.CppRenderer Methods pi :: SValue CppHdrCode Source # | |
MathConstant CppSrcCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.CppRenderer Methods pi :: SValue CppSrcCode Source # | |
MathConstant JavaCode Source # | |
MathConstant JuliaCode Source # | |
MathConstant PythonCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.PythonRenderer Methods pi :: SValue PythonCode Source # | |
MathConstant SwiftCode Source # | |
Pair p => MathConstant (p CppSrcCode CppHdrCode) Source # | |
Defined in Drasil.GOOL.LanguageRenderer.CppRenderer Methods pi :: SValue (p CppSrcCode CppHdrCode) Source # |
class (VariableSym r, ValueSym r) => VariableValue r where Source #
Instances
class (VariableValue r, OOVariableSym r) => OOVariableValue r Source #
Instances
class ValueSym r => CommandLineArgs r where Source #
Instances
CommandLineArgs CodeInfoOO Source # | |
Defined in Drasil.GOOL.CodeInfoOO | |
CommandLineArgs CodeInfoProc Source # | |
Defined in Drasil.GOOL.CodeInfoProc | |
CommandLineArgs CSharpCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.CSharpRenderer | |
CommandLineArgs CppHdrCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.CppRenderer | |
CommandLineArgs CppSrcCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.CppRenderer | |
CommandLineArgs JavaCode Source # | |
CommandLineArgs JuliaCode Source # | |
CommandLineArgs PythonCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.PythonRenderer | |
CommandLineArgs SwiftCode Source # | |
Pair p => CommandLineArgs (p CppSrcCode CppHdrCode) Source # | |
Defined in Drasil.GOOL.LanguageRenderer.CppRenderer Methods arg :: Integer -> SValue (p CppSrcCode CppHdrCode) Source # argsList :: SValue (p CppSrcCode CppHdrCode) Source # argExists :: Integer -> SValue (p CppSrcCode CppHdrCode) Source # |
class ValueSym r => NumericExpression r where Source #
Methods
(#~) :: SValue r -> SValue r infixl 8 Source #
(#/^) :: SValue r -> SValue r infixl 7 Source #
(#|) :: SValue r -> SValue r infixl 7 Source #
(#+) :: SValue r -> SValue r -> SValue r infixl 5 Source #
(#-) :: SValue r -> SValue r -> SValue r infixl 5 Source #
(#*) :: SValue r -> SValue r -> SValue r infixl 6 Source #
(#/) :: SValue r -> SValue r -> SValue r infixl 6 Source #
(#%) :: SValue r -> SValue r -> SValue r infixl 6 Source #
(#^) :: SValue r -> SValue r -> SValue r infixl 7 Source #
log :: SValue r -> SValue r Source #
ln :: SValue r -> SValue r Source #
exp :: SValue r -> SValue r Source #
sin :: SValue r -> SValue r Source #
cos :: SValue r -> SValue r Source #
tan :: SValue r -> SValue r Source #
csc :: SValue r -> SValue r Source #
sec :: SValue r -> SValue r Source #
cot :: SValue r -> SValue r Source #
arcsin :: SValue r -> SValue r Source #
arccos :: SValue r -> SValue r Source #
arctan :: SValue r -> SValue r Source #
Instances
class ValueSym r => BooleanExpression r where Source #
Methods
(?!) :: SValue r -> SValue r infixr 6 Source #
Instances
class ValueSym r => Comparison r where Source #
Methods
(?<) :: SValue r -> SValue r -> SValue r infixl 4 Source #
(?<=) :: SValue r -> SValue r -> SValue r infixl 4 Source #
(?>) :: SValue r -> SValue r -> SValue r infixl 4 Source #
(?>=) :: SValue r -> SValue r -> SValue r infixl 4 Source #
Instances
class (VariableSym r, ValueSym r) => ValueExpression r where Source #
Methods
inlineIf :: SValue r -> SValue r -> SValue r -> SValue r Source #
funcAppMixedArgs :: MixedCall r Source #
extFuncAppMixedArgs :: Library -> MixedCall r Source #
libFuncAppMixedArgs :: Library -> MixedCall r Source #
Instances
class (ValueExpression r, OOVariableSym r, OOValueSym r) => OOValueExpression r where Source #
Methods
selfFuncAppMixedArgs :: MixedCall r Source #
newObjMixedArgs :: MixedCtorCall r Source #
extNewObjMixedArgs :: Library -> MixedCtorCall r Source #
libNewObjMixedArgs :: Library -> MixedCtorCall r Source #
Instances
funcApp :: ValueExpression r => PosCall r Source #
funcAppNamedArgs :: ValueExpression r => Label -> VSType r -> NamedArgs r -> SValue r Source #
selfFuncApp :: OOValueExpression r => PosCall r Source #
extFuncApp :: ValueExpression r => Library -> PosCall r Source #
libFuncApp :: ValueExpression r => Library -> PosCall r Source #
newObj :: OOValueExpression r => PosCtorCall r Source #
extNewObj :: OOValueExpression r => Library -> PosCtorCall r Source #
libNewObj :: OOValueExpression r => Library -> PosCtorCall r Source #
objMethodCall :: InternalValueExp r => VSType r -> SValue r -> Label -> [SValue r] -> SValue r Source #
Calling a method. t is the return type of the method, o is the object, f is the method name, and ps is a list of positional arguments.
objMethodCallNamedArgs :: InternalValueExp r => VSType r -> SValue r -> Label -> NamedArgs r -> SValue r Source #
Calling a method with named arguments.
objMethodCallMixedArgs :: InternalValueExp r => VSType r -> SValue r -> Label -> [SValue r] -> NamedArgs r -> SValue r Source #
Calling a method with a mix of positional and named arguments.
objMethodCallNoParams :: InternalValueExp r => VSType r -> SValue r -> Label -> SValue r Source #
Calling a method with no parameters.
class ValueSym r => FunctionSym r Source #
Instances
class FunctionSym r => OOFunctionSym r where Source #
Instances
($.) :: OOFunctionSym r => SValue r -> VSFunction r -> SValue r infixl 9 Source #
selfAccess :: (OOVariableValue r, OOFunctionSym r) => VSFunction r -> SValue r Source #
class (ValueSym r, VariableSym r) => GetSet r where Source #
Methods
get :: SValue r -> SVariable r -> SValue r Source #
set :: SValue r -> SVariable r -> SValue r -> SValue r Source #
Instances
class ValueSym r => List r where Source #
Methods
intToIndex :: SValue r -> SValue r Source #
Does any necessary conversions from GOOL's zero-indexed assumptions to the target language's assumptions
indexToInt :: SValue r -> SValue r Source #
Does any necessary conversions from the target language's indexing assumptions assumptions to GOOL's zero-indexed assumptions
listSize :: SValue r -> SValue r Source #
Finds the size of a list. Arguments are: List
listAdd :: SValue r -> SValue r -> SValue r -> SValue r Source #
Inserts a value into a list. Arguments are: List, Index, Value
listAppend :: SValue r -> SValue r -> SValue r Source #
Appens a value to a list. Arguments are: List, Value
listAccess :: SValue r -> SValue r -> SValue r Source #
Gets the value of an index of a list. Arguments are: List, Index
listSet :: SValue r -> SValue r -> SValue r -> SValue r Source #
Sets the value of an index of a list. Arguments are: List, Index, Value
indexOf :: SValue r -> SValue r -> SValue r Source #
Finds the index of the first occurrence of a value in a list. Arguments are: List, Value
Instances
class ValueSym r => Set r where Source #
Methods
contains :: SValue r -> SValue r -> SValue r Source #
Checks membership Arguments are: Set, Value
setAdd :: SValue r -> SValue r -> SValue r Source #
Inserts a value into a set Arguments are: Set, Value
setRemove :: SValue r -> SValue r -> SValue r Source #
Removes a value from a set Arguments are: Set, Value
setUnion :: SValue r -> SValue r -> SValue r Source #
Removes a value from a set Arguments are: Set, Set
Instances
listSlice :: InternalList r => SVariable r -> SValue r -> Maybe (SValue r) -> Maybe (SValue r) -> Maybe (SValue r) -> MSBlock r Source #
Creates a slice of a list and assigns it to a variable. Arguments are: Variable to assign List to read from (optional) Start index inclusive. (if Nothing, then list start if step > 0, list end if step < 0) (optional) End index exclusive. (if Nothing, then list end if step > 0, list start if step > 0) (optional) Step (if Nothing, then defaults to 1)
listIndexExists :: (List r, Comparison r) => SValue r -> SValue r -> SValue r Source #
class (StatementSym r, OOFunctionSym r) => ObserverPattern r where Source #
Methods
notifyObservers :: VSFunction r -> VSType r -> MSStatement r Source #
Instances
class (BodySym r, VariableSym r) => StrategyPattern r where Source #
Methods
runStrategy :: Label -> [(Label, MSBody r)] -> Maybe (SValue r) -> Maybe (SVariable r) -> MSBlock r Source #
Instances
class VisibilitySym r where Source #
Associated Types
type Visibility r Source #
Instances
class VariableSym r => ParameterSym r where Source #
Methods
param :: SVariable r -> MSParameter r Source #
pointerParam :: SVariable r -> MSParameter r Source #
Instances
class (BodySym r, ParameterSym r, VisibilitySym r) => MethodSym r where Source #
Methods
docMain :: MSBody r -> SMethod r Source #
function :: Label -> r (Visibility r) -> VSType r -> [MSParameter r] -> MSBody r -> SMethod r Source #
mainFunction :: MSBody r -> SMethod r Source #
docFunc :: String -> [String] -> Maybe String -> SMethod r -> SMethod r Source #
inOutFunc :: Label -> r (Visibility r) -> InOutFunc r Source #
docInOutFunc :: Label -> r (Visibility r) -> DocInOutFunc r Source #
Instances
class (MethodSym r, PermanenceSym r) => OOMethodSym r where Source #
Methods
method :: Label -> r (Visibility r) -> r (Permanence r) -> VSType r -> [MSParameter r] -> MSBody r -> SMethod r Source #
getMethod :: SVariable r -> SMethod r Source #
setMethod :: SVariable r -> SMethod r Source #
constructor :: [MSParameter r] -> Initializers r -> MSBody r -> SMethod r Source #
inOutMethod :: Label -> r (Visibility r) -> r (Permanence r) -> InOutFunc r Source #
docInOutMethod :: Label -> r (Visibility r) -> r (Permanence r) -> DocInOutFunc r Source #
Instances
privMethod :: OOMethodSym r => Label -> VSType r -> [MSParameter r] -> MSBody r -> SMethod r Source #
pubMethod :: OOMethodSym r => Label -> VSType r -> [MSParameter r] -> MSBody r -> SMethod r Source #
initializer :: OOMethodSym r => [MSParameter r] -> Initializers r -> SMethod r Source #
nonInitConstructor :: OOMethodSym r => [MSParameter r] -> MSBody r -> SMethod r Source #
class (VisibilitySym r, PermanenceSym r, VariableSym r) => StateVarSym r where Source #
Methods
stateVar :: r (Visibility r) -> r (Permanence r) -> SVariable r -> CSStateVar r Source #
stateVarDef :: r (Visibility r) -> r (Permanence r) -> SVariable r -> SValue r -> CSStateVar r Source #
constVar :: r (Visibility r) -> SVariable r -> SValue r -> CSStateVar r Source #
Instances
privDVar :: StateVarSym r => SVariable r -> CSStateVar r Source #
pubDVar :: StateVarSym r => SVariable r -> CSStateVar r Source #
pubSVar :: StateVarSym r => SVariable r -> CSStateVar r Source #
class (OOMethodSym r, StateVarSym r) => ClassSym r where Source #
Methods
buildClass :: Maybe Label -> [CSStateVar r] -> [SMethod r] -> [SMethod r] -> SClass r Source #
Main external method for creating a class. Inputs: parent class, variables, constructor(s), methods
extraClass :: Label -> Maybe Label -> [CSStateVar r] -> [SMethod r] -> [SMethod r] -> SClass r Source #
Creates an extra class. Inputs: class name, the rest are the same as buildClass.
implementingClass :: Label -> [Label] -> [CSStateVar r] -> [SMethod r] -> [SMethod r] -> SClass r Source #
Creates a class implementing interfaces. Inputs: class name, interface names, variables, constructor(s), methods
Instances
class ClassSym r => ModuleSym r where Source #
Instances
data VisibilityTag Source #
Instances
Eq VisibilityTag Source # | |
Defined in Drasil.GOOL.AST Methods (==) :: VisibilityTag -> VisibilityTag -> Bool # (/=) :: VisibilityTag -> VisibilityTag -> Bool # |
Constructors
Boolean | |
Integer | |
Float | |
Double | |
Char | |
String | |
InFile | |
OutFile | |
List CodeType | |
Set CodeType | |
Array CodeType | |
Object ClassName | |
Func [CodeType] CodeType | |
Void |
Instances
Constructors
GS | |
Fields
|
lensMStoVS :: Lens' MethodState ValueState Source #
onStateValue :: (a -> b) -> State s a -> State s b Source #
onCodeList :: Monad m => ([a] -> b) -> [m a] -> m b Source #
unCI :: CodeInfoOO a -> a Source #
unPC :: PythonCode a -> a Source #
unCSC :: CSharpCode a -> a Source #
unCPPC :: CppCode CppSrcCode CppHdrCode a -> a Source #
cppVersion :: String Source #