Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- type Label = String
- type Library = String
- type MSBody a = MS (a (Body a))
- type MSBlock a = MS (a (Block a))
- type VSFunction a = VS (a (Function a))
- type VSType a = VS (a (Type a))
- type SVariable a = VS (a (Variable a))
- type SValue a = VS (a (Value a))
- type VSThunk a = VS (a (Thunk a))
- type MSStatement a = MS (a (Statement a))
- type MSParameter a = MS (a (Parameter a))
- type SMethod a = MS (a (Method a))
- type NamedArgs r = [(SVariable r, SValue r)]
- type MixedCall r = Label -> VSType r -> [SValue r] -> NamedArgs r -> SValue r
- type MixedCtorCall r = VSType r -> [SValue r] -> NamedArgs r -> SValue r
- type PosCall r = Label -> VSType r -> [SValue r] -> SValue r
- type PosCtorCall r = VSType r -> [SValue r] -> SValue r
- type InOutCall r = Label -> [SValue r] -> [SVariable r] -> [SVariable r] -> MSStatement r
- type InOutFunc r = [SVariable r] -> [SVariable r] -> [SVariable r] -> MSBody r -> SMethod r
- type DocInOutFunc r = String -> [(String, SVariable r)] -> [(String, SVariable r)] -> [(String, SVariable r)] -> MSBody r -> SMethod 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 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 => TypeElim r where
- class TypeSym r => VariableSym r where
- class ScopeSym r where
- convScope :: ScopeSym r => ScopeData -> r (Scope r)
- class VariableSym r => VariableElim r where
- variableName :: r (Variable r) -> String
- variableType :: r (Variable r) -> r (Type 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
- litZero :: (TypeElim r, Literal r) => VSType r -> SValue r
- class ValueSym r => MathConstant r where
- class (VariableSym r, ValueSym r) => VariableValue r where
- 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
- funcApp :: ValueExpression r => PosCall r
- funcAppNamedArgs :: ValueExpression r => Label -> VSType r -> NamedArgs r -> SValue r
- extFuncApp :: ValueExpression r => Library -> PosCall r
- libFuncApp :: ValueExpression r => Library -> PosCall r
- exists :: ValueExpression r => SValue r -> SValue r
- 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
- class ValueSym r => InternalList 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 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 (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 ValueSym r => FunctionSym r where
- type Function r
- class (VariableSym r, StatementSym r) => FuncAppStatement r where
- inOutCall :: InOutCall r
- extInOutCall :: Library -> InOutCall r
- class StatementSym r => CommentStatement r where
- comment :: Comment -> 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 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
- convType :: TypeSym r => CodeType -> VSType r
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 InOutFunc r = [SVariable r] -> [SVariable r] -> [SVariable r] -> MSBody r -> SMethod r Source #
type DocInOutFunc r = String -> [(String, SVariable r)] -> [(String, SVariable r)] -> [(String, SVariable r)] -> MSBody r -> SMethod 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 BlockSym r => BodySym r where Source #
Instances
bodyStatements :: BodySym r => [MSStatement r] -> MSBody r Source #
class StatementSym r => BlockSym r where Source #
block :: [MSStatement r] -> MSBlock r Source #
Instances
class TypeSym r where Source #
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 => TypeElim r where Source #
Instances
class TypeSym r => VariableSym r where Source #
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 => VariableElim r where Source #
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 #
pointerArg :: SValue r -> SValue r Source #
Instances
Argument CodeInfoOO Source # | |
Defined in Drasil.GOOL.CodeInfoOO | |
Argument CodeInfoProc Source # | |
Defined in Drasil.GOOL.CodeInfoProc | |
Argument CSharpCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.CSharpRenderer | |
Argument CppHdrCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.CppRenderer | |
Argument CppSrcCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.CppRenderer | |
Argument JavaCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.JavaRenderer | |
Argument JuliaCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.JuliaRenderer | |
Argument PythonCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.PythonRenderer | |
Argument SwiftCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.SwiftRenderer | |
Pair p => Argument (p CppSrcCode CppHdrCode) Source # | |
Defined in Drasil.GOOL.LanguageRenderer.CppRenderer pointerArg :: SValue (p CppSrcCode CppHdrCode) -> SValue (p CppSrcCode CppHdrCode) Source # |
class ValueSym r => Literal r where Source #
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 pi :: SValue CodeInfoOO Source # | |
MathConstant CodeInfoProc Source # | |
Defined in Drasil.GOOL.CodeInfoProc pi :: SValue CodeInfoProc Source # | |
MathConstant CSharpCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.CSharpRenderer pi :: SValue CSharpCode Source # | |
MathConstant CppHdrCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.CppRenderer pi :: SValue CppHdrCode Source # | |
MathConstant CppSrcCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.CppRenderer pi :: SValue CppSrcCode Source # | |
MathConstant JavaCode Source # | |
MathConstant JuliaCode Source # | |
MathConstant PythonCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.PythonRenderer pi :: SValue PythonCode Source # | |
MathConstant SwiftCode Source # | |
Pair p => MathConstant (p CppSrcCode CppHdrCode) Source # | |
Defined in Drasil.GOOL.LanguageRenderer.CppRenderer pi :: SValue (p CppSrcCode CppHdrCode) Source # |
class (VariableSym r, ValueSym r) => VariableValue r where Source #
Instances
class ValueSym r => CommandLineArgs r where Source #
Instances
class ValueSym r => NumericExpression r where Source #
(#~) :: 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 #
(?!) :: SValue r -> SValue r infixr 6 Source #
Instances
class ValueSym r => Comparison r where 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 #
(?>=) :: SValue r -> SValue r -> SValue r infixl 4 Source #
Instances
class (VariableSym r, ValueSym r) => ValueExpression r where Source #
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
funcApp :: ValueExpression r => PosCall r Source #
funcAppNamedArgs :: ValueExpression r => Label -> VSType r -> NamedArgs r -> SValue r Source #
extFuncApp :: ValueExpression r => Library -> PosCall r Source #
libFuncApp :: ValueExpression r => Library -> PosCall r Source #
class ValueSym r => List r where Source #
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 #
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
class ValueSym r => InternalList r where Source #
listSlice' :: Maybe (SValue r) -> Maybe (SValue r) -> Maybe (SValue r) -> SVariable r -> SValue r -> MSBlock r Source #
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 #
Instances
class TypeSym r => VectorType r where Source #
Instances
class DeclStatement r => VectorDecl r where Source #
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
VectorThunk CodeInfoOO Source # | |
Defined in Drasil.GOOL.CodeInfoOO | |
VectorThunk CodeInfoProc Source # | |
Defined in Drasil.GOOL.CodeInfoProc | |
VectorThunk CSharpCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.CSharpRenderer | |
VectorThunk CppHdrCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.CppRenderer | |
VectorThunk CppSrcCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.CppRenderer | |
VectorThunk JavaCode Source # | |
VectorThunk JuliaCode Source # | |
VectorThunk PythonCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.PythonRenderer | |
VectorThunk SwiftCode Source # | |
Pair p => VectorThunk (p CppSrcCode CppHdrCode) Source # | |
Defined in Drasil.GOOL.LanguageRenderer.CppRenderer vecThunk :: SVariable (p CppSrcCode CppHdrCode) -> VSThunk (p CppSrcCode CppHdrCode) Source # |
class (ThunkSym r, ValueSym r) => VectorExpression r where Source #
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 #
thunkAssign :: SVariable r -> VSThunk r -> MSStatement r Source #
Instances
ThunkAssign CodeInfoOO Source # | |
Defined in Drasil.GOOL.CodeInfoOO | |
ThunkAssign CodeInfoProc Source # | |
Defined in Drasil.GOOL.CodeInfoProc | |
ThunkAssign CSharpCode Source # | |
ThunkAssign CppHdrCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.CppRenderer | |
ThunkAssign CppSrcCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.CppRenderer | |
ThunkAssign JavaCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.JavaRenderer | |
ThunkAssign JuliaCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.JuliaRenderer | |
ThunkAssign PythonCode Source # | |
ThunkAssign SwiftCode Source # | |
Defined in Drasil.GOOL.LanguageRenderer.SwiftRenderer | |
Pair p => ThunkAssign (p CppSrcCode CppHdrCode) Source # | |
Defined in Drasil.GOOL.LanguageRenderer.CppRenderer thunkAssign :: SVariable (p CppSrcCode CppHdrCode) -> VSThunk (p CppSrcCode CppHdrCode) -> MSStatement (p CppSrcCode CppHdrCode) Source # |
class ValueSym r => StatementSym r where Source #
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 #
(&-=) :: 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 #
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 (VariableSym r, StatementSym r) => IOStatement r where Source #
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 #
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 ValueSym r => FunctionSym r Source #
Instances
class (VariableSym r, StatementSym r) => FuncAppStatement r where Source #
Instances
class StatementSym r => CommentStatement r where Source #
comment :: Comment -> MSStatement r Source #
Instances
class (BodySym r, VariableSym r) => ControlStatement r where Source #
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 VisibilitySym r where Source #
type Visibility r Source #
private :: r (Visibility r) Source #
public :: r (Visibility r) Source #
Instances
class VariableSym r => ParameterSym r where Source #
param :: SVariable r -> MSParameter r Source #
pointerParam :: SVariable r -> MSParameter r Source #
Instances
class (BodySym r, ParameterSym r, VisibilitySym r) => MethodSym r where Source #
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 #