Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Documentation
ArgValues | |
|
data Assignable c Source #
Instances
Show c => Show (Assignable c) Source # | |
Defined in Types.Procedure showsPrec :: Int -> Assignable c -> ShowS # show :: Assignable c -> String # showList :: [Assignable c] -> ShowS # | |
ParseFromSource (Assignable SourcePos) Source # | |
Defined in Parser.Procedure |
data ExecutableProcedure c Source #
ExecutableProcedure | |
|
Instances
Show c => Show (ExecutableProcedure c) Source # | |
Defined in Types.Procedure showsPrec :: Int -> ExecutableProcedure c -> ShowS # show :: ExecutableProcedure c -> String # showList :: [ExecutableProcedure c] -> ShowS # | |
ParseFromSource (ExecutableProcedure SourcePos) Source # | |
Defined in Parser.Procedure |
data Expression c Source #
Expression [c] (ExpressionStart c) [ValueOperation c] | |
Literal (ValueLiteral c) | |
UnaryExpression [c] (Operator c) (Expression c) | |
InfixExpression [c] (Expression c) (Operator c) (Expression c) | |
InitializeValue [c] TypeInstance (Positional GeneralInstance) (Positional (Expression c)) |
Instances
Show c => Show (Expression c) Source # | |
Defined in Types.Procedure showsPrec :: Int -> Expression c -> ShowS # show :: Expression c -> String # showList :: [Expression c] -> ShowS # | |
ParseFromSource (Expression SourcePos) Source # | |
Defined in Parser.Procedure |
data ExpressionStart c Source #
NamedVariable (OutputValue c) | |
NamedMacro [c] String | |
CategoryCall [c] CategoryName (FunctionCall c) | |
TypeCall [c] TypeInstanceOrParam (FunctionCall c) | |
UnqualifiedCall [c] (FunctionCall c) | |
BuiltinCall [c] (FunctionCall c) | |
ParensExpression [c] (Expression c) | |
InlineAssignment [c] VariableName (Expression c) |
Instances
Show c => Show (ExpressionStart c) Source # | |
Defined in Types.Procedure showsPrec :: Int -> ExpressionStart c -> ShowS # show :: ExpressionStart c -> String # showList :: [ExpressionStart c] -> ShowS # | |
ParseFromSource (ExpressionStart SourcePos) Source # | |
Defined in Parser.Procedure |
data FunctionCall c Source #
Instances
Show c => Show (FunctionCall c) Source # | |
Defined in Types.Procedure showsPrec :: Int -> FunctionCall c -> ShowS # show :: FunctionCall c -> String # showList :: [FunctionCall c] -> ShowS # |
data FunctionQualifier c Source #
CategoryFunction [c] CategoryName | |
TypeFunction [c] TypeInstanceOrParam | |
ValueFunction [c] (Expression c) | |
UnqualifiedFunction |
Instances
Show c => Show (FunctionQualifier c) Source # | |
Defined in Types.Procedure showsPrec :: Int -> FunctionQualifier c -> ShowS # show :: FunctionQualifier c -> String # showList :: [FunctionQualifier c] -> ShowS # | |
ParseFromSource (FunctionQualifier SourcePos) Source # | |
Defined in Parser.Procedure |
data FunctionSpec c Source #
Instances
Show c => Show (FunctionSpec c) Source # | |
Defined in Types.Procedure showsPrec :: Int -> FunctionSpec c -> ShowS # show :: FunctionSpec c -> String # showList :: [FunctionSpec c] -> ShowS # | |
ParseFromSource (FunctionSpec SourcePos) Source # | |
Defined in Parser.Procedure |
data IfElifElse c Source #
IfStatement [c] (Expression c) (Procedure c) (IfElifElse c) | |
ElseStatement [c] (Procedure c) | |
TerminateConditional |
Instances
Show c => Show (IfElifElse c) Source # | |
Defined in Types.Procedure showsPrec :: Int -> IfElifElse c -> ShowS # show :: IfElifElse c -> String # showList :: [IfElifElse c] -> ShowS # | |
ParseFromSource (IfElifElse SourcePos) Source # | |
Defined in Parser.Procedure |
data InputValue c Source #
InputValue | |
| |
DiscardInput | |
|
Instances
Show c => Show (InputValue c) Source # | |
Defined in Types.Procedure showsPrec :: Int -> InputValue c -> ShowS # show :: InputValue c -> String # showList :: [InputValue c] -> ShowS # | |
ParseFromSource (InputValue SourcePos) Source # | |
Defined in Parser.Procedure |
data OutputValue c Source #
OutputValue | |
|
Instances
Show c => Show (OutputValue c) Source # | |
Defined in Types.Procedure showsPrec :: Int -> OutputValue c -> ShowS # show :: OutputValue c -> String # showList :: [OutputValue c] -> ShowS # | |
ParseFromSource (OutputValue SourcePos) Source # | |
Defined in Parser.Procedure |
data ReturnValues c Source #
NamedReturns | |
| |
UnnamedReturns | |
|
Instances
Show c => Show (ReturnValues c) Source # | |
Defined in Types.Procedure showsPrec :: Int -> ReturnValues c -> ShowS # show :: ReturnValues c -> String # showList :: [ReturnValues c] -> ShowS # | |
ParseFromSource (ReturnValues SourcePos) Source # | |
Defined in Parser.Procedure |
data ScopedBlock c Source #
ScopedBlock [c] (Procedure c) (Maybe (Procedure c)) (Statement c) |
Instances
Show c => Show (ScopedBlock c) Source # | |
Defined in Types.Procedure showsPrec :: Int -> ScopedBlock c -> ShowS # show :: ScopedBlock c -> String # showList :: [ScopedBlock c] -> ShowS # | |
ParseFromSource (ScopedBlock SourcePos) Source # | |
Defined in Parser.Procedure |
EmptyReturn [c] | |
ExplicitReturn [c] (Positional (Expression c)) | |
LoopBreak [c] | |
LoopContinue [c] | |
FailCall [c] (Expression c) | |
IgnoreValues [c] (Expression c) | |
Assignment [c] (Positional (Assignable c)) (Expression c) | |
NoValueExpression [c] (VoidExpression c) |
data ValueLiteral c Source #
StringLiteral [c] String | |
CharLiteral [c] Char | |
IntegerLiteral [c] Bool Integer | |
DecimalLiteral [c] Integer Integer | |
BoolLiteral [c] Bool | |
EmptyLiteral [c] |
Instances
Show c => Show (ValueLiteral c) Source # | |
Defined in Types.Procedure showsPrec :: Int -> ValueLiteral c -> ShowS # show :: ValueLiteral c -> String # showList :: [ValueLiteral c] -> ShowS # | |
ParseFromSource (ValueLiteral SourcePos) Source # | |
Defined in Parser.Procedure |
data ValueOperation c Source #
ConvertedCall [c] TypeInstance (FunctionCall c) | |
ValueCall [c] (FunctionCall c) |
Instances
Show c => Show (ValueOperation c) Source # | |
Defined in Types.Procedure showsPrec :: Int -> ValueOperation c -> ShowS # show :: ValueOperation c -> String # showList :: [ValueOperation c] -> ShowS # | |
ParseFromSource (ValueOperation SourcePos) Source # | |
Defined in Parser.Procedure |
data VariableName Source #
Instances
Eq VariableName Source # | |
Defined in Types.Procedure (==) :: VariableName -> VariableName -> Bool # (/=) :: VariableName -> VariableName -> Bool # | |
Ord VariableName Source # | |
Defined in Types.Procedure compare :: VariableName -> VariableName -> Ordering # (<) :: VariableName -> VariableName -> Bool # (<=) :: VariableName -> VariableName -> Bool # (>) :: VariableName -> VariableName -> Bool # (>=) :: VariableName -> VariableName -> Bool # max :: VariableName -> VariableName -> VariableName # min :: VariableName -> VariableName -> VariableName # | |
Show VariableName Source # | |
Defined in Types.Procedure showsPrec :: Int -> VariableName -> ShowS # show :: VariableName -> String # showList :: [VariableName] -> ShowS # | |
ParseFromSource VariableName Source # | |
Defined in Parser.Procedure |
data VoidExpression c Source #
Conditional (IfElifElse c) | |
Loop (WhileLoop c) | |
WithScope (ScopedBlock c) | |
Unconditional (Procedure c) | |
LineComment String |
Instances
Show c => Show (VoidExpression c) Source # | |
Defined in Types.Procedure showsPrec :: Int -> VoidExpression c -> ShowS # show :: VoidExpression c -> String # showList :: [VoidExpression c] -> ShowS # | |
ParseFromSource (VoidExpression SourcePos) Source # | |
Defined in Parser.Procedure |
WhileLoop [c] (Expression c) (Procedure c) (Maybe (Procedure c)) |
assignableName :: Assignable c -> VariableName Source #
getExpressionContext :: Expression c -> [c] Source #
getStatementContext :: Statement c -> [c] Source #
isDiscardedInput :: InputValue c -> Bool Source #
isUnnamedReturns :: ReturnValues c -> Bool Source #