Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Documentation
ArgValues | |
|
Instances
Show c => Show (ArgValues c) Source # | |
ParseFromSource (ArgValues SourceContext) Source # | |
Defined in Parser.Procedure |
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 SourceContext) Source # | |
Defined in Parser.Procedure |
data AssignmentType Source #
Instances
Show AssignmentType Source # | |
Defined in Types.Procedure showsPrec :: Int -> AssignmentType -> ShowS # show :: AssignmentType -> String # showList :: [AssignmentType] -> ShowS # | |
Eq AssignmentType Source # | |
Defined in Types.Procedure (==) :: AssignmentType -> AssignmentType -> Bool # (/=) :: AssignmentType -> AssignmentType -> Bool # |
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 SourceContext) 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) | |
RawExpression ExpressionType ExpressionValue | |
DelegatedFunctionCall [c] (FunctionSpec c) | |
DelegatedInitializeValue [c] (Maybe TypeInstance) |
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 SourceContext) Source # | |
Defined in Parser.Procedure |
data ExpressionStart c Source #
NamedVariable (OutputValue c) | |
NamedMacro [c] MacroName | |
ExpressionMacro [c] MacroExpression | |
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 AssignmentType (Expression c) | |
InitializeValue [c] (Maybe TypeInstance) (Positional (Expression c)) | |
UnambiguousLiteral (ValueLiteral 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 SourceContext) Source # | |
Defined in Parser.Procedure |
type ExpressionType = Positional ValueType Source #
data FunctionCall c Source #
FunctionCall [c] FunctionName (Positional (InstanceOrInferred c)) (Positional (Maybe (CallArgLabel c), Expression c)) |
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] ValueCallType (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 SourceContext) Source # | |
Defined in Parser.Procedure |
data FunctionSpec c Source #
FunctionSpec [c] (FunctionQualifier c) FunctionName (Positional (InstanceOrInferred c)) |
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 SourceContext) 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 SourceContext) 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 SourceContext) Source # | |
Defined in Parser.Procedure |
data InstanceOrInferred c Source #
Instances
Show c => Show (InstanceOrInferred c) Source # | |
Defined in Types.Procedure showsPrec :: Int -> InstanceOrInferred c -> ShowS # show :: InstanceOrInferred c -> String # showList :: [InstanceOrInferred c] -> ShowS # | |
ParseFromSource (InstanceOrInferred SourceContext) Source # | |
Defined in Parser.Procedure |
data IteratedLoop c Source #
WhileLoop [c] (Expression c) (Procedure c) (Maybe (Procedure c)) | |
TraverseLoop [c] (Expression c) [c] (Assignable c) (Procedure c) (Maybe (Procedure c)) |
Instances
Show c => Show (IteratedLoop c) Source # | |
Defined in Types.Procedure showsPrec :: Int -> IteratedLoop c -> ShowS # show :: IteratedLoop c -> String # showList :: [IteratedLoop c] -> ShowS # | |
ParseFromSource (IteratedLoop SourceContext) Source # | |
Defined in Parser.Procedure |
data MacroExpression Source #
Instances
Show MacroExpression Source # | |
Defined in Types.Procedure showsPrec :: Int -> MacroExpression -> ShowS # show :: MacroExpression -> String # showList :: [MacroExpression] -> ShowS # |
NamedOperator [c] String | |
FunctionOperator [c] (FunctionSpec c) |
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 SourceContext) Source # | |
Defined in Parser.Procedure |
data PragmaProcedure c Source #
Instances
Show c => Show (PragmaProcedure c) Source # | |
Defined in Types.Procedure showsPrec :: Int -> PragmaProcedure c -> ShowS # show :: PragmaProcedure c -> String # showList :: [PragmaProcedure c] -> ShowS # |
Instances
Show c => Show (Procedure c) Source # | |
ParseFromSource (Procedure SourceContext) 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 SourceContext) Source # | |
Defined in Parser.Procedure |
data ScopedBlock c Source #
ScopedBlock [c] (Procedure c) (Maybe (Procedure c)) [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 SourceContext) Source # | |
Defined in Parser.Procedure |
EmptyReturn [c] | |
ExplicitReturn [c] (Positional (Expression c)) | |
LoopBreak [c] | |
LoopContinue [c] | |
FailCall [c] (Expression c) | |
ExitCall [c] (Expression c) | |
RawFailCall String | |
IgnoreValues [c] (Expression c) | |
Assignment [c] (Positional (Assignable c)) (Expression c) | |
AssignmentEmpty [c] VariableName (Expression c) | |
VariableSwap [c] (OutputValue c) (OutputValue c) | |
DeferredVariables [c] [Assignable c] | |
NoValueExpression [c] (VoidExpression c) | |
MarkReadOnly [c] [VariableName] | |
MarkHidden [c] [VariableName] | |
ValidateRefs [c] [VariableName] | |
ShowVariable [c] ValueType VariableName | |
RawCodeLine String |
Instances
Show c => Show (Statement c) Source # | |
ParseFromSource (Statement SourceContext) Source # | |
Defined in Parser.Procedure |
data TestProcedure c Source #
TestProcedure | |
|
Instances
Show c => Show (TestProcedure c) Source # | |
Defined in Types.Procedure showsPrec :: Int -> TestProcedure c -> ShowS # show :: TestProcedure c -> String # showList :: [TestProcedure c] -> ShowS # | |
ParseFromSource (TestProcedure SourceContext) Source # | |
Defined in Parser.Procedure |
data ValueCallType Source #
Instances
Show ValueCallType Source # | |
Defined in Types.Procedure showsPrec :: Int -> ValueCallType -> ShowS # show :: ValueCallType -> String # showList :: [ValueCallType] -> ShowS # | |
Eq ValueCallType Source # | |
Defined in Types.Procedure (==) :: ValueCallType -> ValueCallType -> Bool # (/=) :: ValueCallType -> ValueCallType -> Bool # |
data ValueLiteral c Source #
StringLiteral [c] String | |
CharLiteral [c] Char | |
IntegerLiteral [c] Bool Integer | |
DecimalLiteral [c] Integer 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 SourceContext) Source # | |
Defined in Parser.Procedure |
data ValueOperation c Source #
TypeConversion [c] GeneralInstance | |
ValueCall [c] ValueCallType (FunctionCall c) | |
SelectReturn [c] Int |
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 SourceContext) Source # | |
Defined in Parser.Procedure |
data VariableName Source #
Instances
Show VariableName Source # | |
Defined in Types.Procedure showsPrec :: Int -> VariableName -> ShowS # show :: VariableName -> String # showList :: [VariableName] -> ShowS # | |
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 # | |
ParseFromSource VariableName Source # | |
Defined in Parser.Procedure |
data VoidExpression c Source #
Conditional (IfElifElse c) | |
Loop (IteratedLoop 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 SourceContext) Source # | |
Defined in Parser.Procedure |
assignableName :: Assignable c -> VariableName Source #
getExpressionContext :: Expression c -> [c] Source #
getOperatorContext :: Operator c -> [c] Source #
getOperatorName :: Operator c -> FunctionName Source #
getStatementContext :: Statement c -> [c] Source #
inputValueName :: InputValue c -> VariableName Source #
isAssignableDiscard :: Assignable c -> Bool Source #
isDiscardedInput :: InputValue c -> Bool Source #
isFunctionOperator :: Operator c -> Bool Source #
isNoTrace :: PragmaProcedure c -> Bool Source #
isTraceCreation :: PragmaProcedure c -> Bool Source #
isRawCodeLine :: Statement c -> Bool Source #
isUnnamedReturns :: ReturnValues c -> Bool Source #