{-# LANGUAGE Safe #-}
module Types.Procedure (
ArgValues(..),
Assignable(..),
AssignmentType(..),
ExecutableProcedure(..),
Expression(..),
ExpressionStart(..),
ExpressionType,
FunctionCall(..),
FunctionQualifier(..),
FunctionSpec(..),
IfElifElse(..),
InputValue(..),
InstanceOrInferred(..),
IteratedLoop(..),
MacroExpression(..),
MacroName(..),
Operator(..),
OutputValue(..),
PragmaProcedure(..),
Procedure(..),
ReturnValues(..),
ScopedBlock(..),
Statement(..),
TestProcedure(..),
TraceType(..),
ValueCallType(..),
ValueLiteral(..),
ValueOperation(..),
VariableName(..),
VoidExpression(..),
assignableName,
getExpressionContext,
getOperatorContext,
getOperatorName,
getStatementContext,
inputValueName,
isAssignableDiscard,
isDiscardedInput,
isFunctionOperator,
isNoTrace,
isTraceCreation,
isRawCodeLine,
isUnnamedReturns,
) where
import Data.List (intercalate)
import Base.Positional
import Types.Builtin
import Types.TypeCategory
import Types.TypeInstance
data ExecutableProcedure c =
ExecutableProcedure {
forall c. ExecutableProcedure c -> [c]
epContext :: [c],
forall c. ExecutableProcedure c -> [PragmaProcedure c]
epPragmas :: [PragmaProcedure c],
forall c. ExecutableProcedure c -> [c]
epEnd :: [c],
forall c. ExecutableProcedure c -> FunctionName
epName :: FunctionName,
forall c. ExecutableProcedure c -> ArgValues c
epArgs :: ArgValues c,
forall c. ExecutableProcedure c -> ReturnValues c
epReturns :: ReturnValues c,
forall c. ExecutableProcedure c -> Procedure c
epProcedure :: Procedure c
}
deriving (Int -> ExecutableProcedure c -> ShowS
[ExecutableProcedure c] -> ShowS
ExecutableProcedure c -> String
(Int -> ExecutableProcedure c -> ShowS)
-> (ExecutableProcedure c -> String)
-> ([ExecutableProcedure c] -> ShowS)
-> Show (ExecutableProcedure c)
forall c. Show c => Int -> ExecutableProcedure c -> ShowS
forall c. Show c => [ExecutableProcedure c] -> ShowS
forall c. Show c => ExecutableProcedure c -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall c. Show c => Int -> ExecutableProcedure c -> ShowS
showsPrec :: Int -> ExecutableProcedure c -> ShowS
$cshow :: forall c. Show c => ExecutableProcedure c -> String
show :: ExecutableProcedure c -> String
$cshowList :: forall c. Show c => [ExecutableProcedure c] -> ShowS
showList :: [ExecutableProcedure c] -> ShowS
Show)
data ArgValues c =
ArgValues {
forall c. ArgValues c -> [c]
avContext :: [c],
forall c. ArgValues c -> Positional (InputValue c)
avNames :: Positional (InputValue c)
}
instance Show c => Show (ArgValues c) where
show :: ArgValues c -> String
show (ArgValues [c]
c Positional (InputValue c)
v) =
String
"(" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
",\n" ((InputValue c -> String) -> [InputValue c] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map InputValue c -> String
forall a. Show a => a -> String
show ([InputValue c] -> [String]) -> [InputValue c] -> [String]
forall a b. (a -> b) -> a -> b
$ Positional (InputValue c) -> [InputValue c]
forall a. Positional a -> [a]
pValues Positional (InputValue c)
v) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
")" String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
" /*" String -> ShowS
forall a. [a] -> [a] -> [a]
++ [c] -> String
forall a. Show a => [a] -> String
formatFullContext [c]
c String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"*/"
data ReturnValues c =
NamedReturns {
forall c. ReturnValues c -> [c]
nrContext :: [c],
forall c. ReturnValues c -> Positional (OutputValue c)
nrNames :: Positional (OutputValue c)
} |
UnnamedReturns {
forall c. ReturnValues c -> [c]
urContext :: [c]
}
isUnnamedReturns :: ReturnValues c -> Bool
isUnnamedReturns :: forall c. ReturnValues c -> Bool
isUnnamedReturns (UnnamedReturns [c]
_) = Bool
True
isUnnamedReturns ReturnValues c
_ = Bool
False
instance Show c => Show (ReturnValues c) where
show :: ReturnValues c -> String
show (NamedReturns [c]
c Positional (OutputValue c)
v) =
String
"(" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
",\n" ((OutputValue c -> String) -> [OutputValue c] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map OutputValue c -> String
forall a. Show a => a -> String
show ([OutputValue c] -> [String]) -> [OutputValue c] -> [String]
forall a b. (a -> b) -> a -> b
$ Positional (OutputValue c) -> [OutputValue c]
forall a. Positional a -> [a]
pValues Positional (OutputValue c)
v) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
")" String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
" /*" String -> ShowS
forall a. [a] -> [a] -> [a]
++ [c] -> String
forall a. Show a => [a] -> String
formatFullContext [c]
c String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"*/"
show (UnnamedReturns [c]
c) = String
"/*unnamed returns: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ [c] -> String
forall a. Show a => [a] -> String
formatFullContext [c]
c String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"*/"
data VariableName =
VariableName {
VariableName -> String
vnName :: String
} |
VariableSelf
deriving (VariableName -> VariableName -> Bool
(VariableName -> VariableName -> Bool)
-> (VariableName -> VariableName -> Bool) -> Eq VariableName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VariableName -> VariableName -> Bool
== :: VariableName -> VariableName -> Bool
$c/= :: VariableName -> VariableName -> Bool
/= :: VariableName -> VariableName -> Bool
Eq,Eq VariableName
Eq VariableName =>
(VariableName -> VariableName -> Ordering)
-> (VariableName -> VariableName -> Bool)
-> (VariableName -> VariableName -> Bool)
-> (VariableName -> VariableName -> Bool)
-> (VariableName -> VariableName -> Bool)
-> (VariableName -> VariableName -> VariableName)
-> (VariableName -> VariableName -> VariableName)
-> Ord VariableName
VariableName -> VariableName -> Bool
VariableName -> VariableName -> Ordering
VariableName -> VariableName -> VariableName
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: VariableName -> VariableName -> Ordering
compare :: VariableName -> VariableName -> Ordering
$c< :: VariableName -> VariableName -> Bool
< :: VariableName -> VariableName -> Bool
$c<= :: VariableName -> VariableName -> Bool
<= :: VariableName -> VariableName -> Bool
$c> :: VariableName -> VariableName -> Bool
> :: VariableName -> VariableName -> Bool
$c>= :: VariableName -> VariableName -> Bool
>= :: VariableName -> VariableName -> Bool
$cmax :: VariableName -> VariableName -> VariableName
max :: VariableName -> VariableName -> VariableName
$cmin :: VariableName -> VariableName -> VariableName
min :: VariableName -> VariableName -> VariableName
Ord)
instance Show VariableName where
show :: VariableName -> String
show (VariableName String
n) = String
n
show VariableName
VariableSelf = String
"self"
data InputValue c =
InputValue {
forall c. InputValue c -> [c]
ivContext :: [c],
forall c. InputValue c -> VariableName
ivName :: VariableName
} |
DiscardInput {
forall c. InputValue c -> [c]
iiContext :: [c]
}
inputValueName :: InputValue c -> VariableName
inputValueName :: forall c. InputValue c -> VariableName
inputValueName (DiscardInput [c]
_) = VariableName
discardInputName
inputValueName (InputValue [c]
_ VariableName
n) = VariableName
n
isDiscardedInput :: InputValue c -> Bool
isDiscardedInput :: forall c. InputValue c -> Bool
isDiscardedInput (DiscardInput [c]
_) = Bool
True
isDiscardedInput InputValue c
_ = Bool
False
discardInputName :: VariableName
discardInputName :: VariableName
discardInputName = String -> VariableName
VariableName String
"_"
instance Show c => Show (InputValue c) where
show :: InputValue c -> String
show (InputValue [c]
c VariableName
v) = VariableName -> String
forall a. Show a => a -> String
show VariableName
v String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" /*" String -> ShowS
forall a. [a] -> [a] -> [a]
++ [c] -> String
forall a. Show a => [a] -> String
formatFullContext [c]
c String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"*/"
show (DiscardInput [c]
c) = String
"_" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" /*" String -> ShowS
forall a. [a] -> [a] -> [a]
++ [c] -> String
forall a. Show a => [a] -> String
formatFullContext [c]
c String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"*/"
data OutputValue c =
OutputValue {
forall c. OutputValue c -> [c]
ovContext :: [c],
forall c. OutputValue c -> VariableName
ovName :: VariableName
}
instance Show c => Show (OutputValue c) where
show :: OutputValue c -> String
show (OutputValue [c]
c VariableName
v) = VariableName -> String
forall a. Show a => a -> String
show VariableName
v String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" /*" String -> ShowS
forall a. [a] -> [a] -> [a]
++ [c] -> String
forall a. Show a => [a] -> String
formatFullContext [c]
c String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"*/"
data TestProcedure c =
TestProcedure {
forall c. TestProcedure c -> [c]
tpContext :: [c],
forall c. TestProcedure c -> FunctionName
tpName :: FunctionName,
forall c. TestProcedure c -> Bool
tpDisableCoverage :: Bool,
forall c. TestProcedure c -> Procedure c
tpProcedure :: Procedure c
}
deriving (Int -> TestProcedure c -> ShowS
[TestProcedure c] -> ShowS
TestProcedure c -> String
(Int -> TestProcedure c -> ShowS)
-> (TestProcedure c -> String)
-> ([TestProcedure c] -> ShowS)
-> Show (TestProcedure c)
forall c. Show c => Int -> TestProcedure c -> ShowS
forall c. Show c => [TestProcedure c] -> ShowS
forall c. Show c => TestProcedure c -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall c. Show c => Int -> TestProcedure c -> ShowS
showsPrec :: Int -> TestProcedure c -> ShowS
$cshow :: forall c. Show c => TestProcedure c -> String
show :: TestProcedure c -> String
$cshowList :: forall c. Show c => [TestProcedure c] -> ShowS
showList :: [TestProcedure c] -> ShowS
Show)
data Procedure c =
Procedure [c] [Statement c]
deriving (Int -> Procedure c -> ShowS
[Procedure c] -> ShowS
Procedure c -> String
(Int -> Procedure c -> ShowS)
-> (Procedure c -> String)
-> ([Procedure c] -> ShowS)
-> Show (Procedure c)
forall c. Show c => Int -> Procedure c -> ShowS
forall c. Show c => [Procedure c] -> ShowS
forall c. Show c => Procedure c -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall c. Show c => Int -> Procedure c -> ShowS
showsPrec :: Int -> Procedure c -> ShowS
$cshow :: forall c. Show c => Procedure c -> String
show :: Procedure c -> String
$cshowList :: forall c. Show c => [Procedure c] -> ShowS
showList :: [Procedure c] -> ShowS
Show)
data Statement c =
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
deriving (Int -> Statement c -> ShowS
[Statement c] -> ShowS
Statement c -> String
(Int -> Statement c -> ShowS)
-> (Statement c -> String)
-> ([Statement c] -> ShowS)
-> Show (Statement c)
forall c. Show c => Int -> Statement c -> ShowS
forall c. Show c => [Statement c] -> ShowS
forall c. Show c => Statement c -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall c. Show c => Int -> Statement c -> ShowS
showsPrec :: Int -> Statement c -> ShowS
$cshow :: forall c. Show c => Statement c -> String
show :: Statement c -> String
$cshowList :: forall c. Show c => [Statement c] -> ShowS
showList :: [Statement c] -> ShowS
Show)
isRawCodeLine :: Statement c -> Bool
isRawCodeLine :: forall c. Statement c -> Bool
isRawCodeLine (RawCodeLine String
_) = Bool
True
isRawCodeLine Statement c
_ = Bool
False
getStatementContext :: Statement c -> [c]
getStatementContext :: forall c. Statement c -> [c]
getStatementContext (EmptyReturn [c]
c) = [c]
c
getStatementContext (ExplicitReturn [c]
c Positional (Expression c)
_) = [c]
c
getStatementContext (LoopBreak [c]
c) = [c]
c
getStatementContext (LoopContinue [c]
c) = [c]
c
getStatementContext (FailCall [c]
c Expression c
_) = [c]
c
getStatementContext (ExitCall [c]
c Expression c
_) = [c]
c
getStatementContext (RawFailCall String
_) = []
getStatementContext (IgnoreValues [c]
c Expression c
_) = [c]
c
getStatementContext (Assignment [c]
c Positional (Assignable c)
_ Expression c
_) = [c]
c
getStatementContext (AssignmentEmpty [c]
c VariableName
_ Expression c
_) = [c]
c
getStatementContext (VariableSwap [c]
c OutputValue c
_ OutputValue c
_) = [c]
c
getStatementContext (DeferredVariables [c]
c [Assignable c]
_) = [c]
c
getStatementContext (NoValueExpression [c]
c VoidExpression c
_) = [c]
c
getStatementContext (MarkReadOnly [c]
c [VariableName]
_) = [c]
c
getStatementContext (MarkHidden [c]
c [VariableName]
_) = [c]
c
getStatementContext (ValidateRefs [c]
c [VariableName]
_) = [c]
c
getStatementContext (ShowVariable [c]
_ ValueType
_ VariableName
_) = []
getStatementContext (RawCodeLine String
_) = []
data Assignable c =
CreateVariable [c] ValueType VariableName |
ExistingVariable (InputValue c)
deriving (Int -> Assignable c -> ShowS
[Assignable c] -> ShowS
Assignable c -> String
(Int -> Assignable c -> ShowS)
-> (Assignable c -> String)
-> ([Assignable c] -> ShowS)
-> Show (Assignable c)
forall c. Show c => Int -> Assignable c -> ShowS
forall c. Show c => [Assignable c] -> ShowS
forall c. Show c => Assignable c -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall c. Show c => Int -> Assignable c -> ShowS
showsPrec :: Int -> Assignable c -> ShowS
$cshow :: forall c. Show c => Assignable c -> String
show :: Assignable c -> String
$cshowList :: forall c. Show c => [Assignable c] -> ShowS
showList :: [Assignable c] -> ShowS
Show)
assignableName :: Assignable c -> VariableName
assignableName :: forall c. Assignable c -> VariableName
assignableName (CreateVariable [c]
_ ValueType
_ VariableName
n) = VariableName
n
assignableName (ExistingVariable (InputValue [c]
_ VariableName
n)) = VariableName
n
assignableName Assignable c
_ = VariableName
discardInputName
isAssignableDiscard :: Assignable c -> Bool
isAssignableDiscard :: forall c. Assignable c -> Bool
isAssignableDiscard (CreateVariable [c]
_ ValueType
_ VariableName
_) = Bool
False
isAssignableDiscard (ExistingVariable InputValue c
v) = InputValue c -> Bool
forall c. InputValue c -> Bool
isDiscardedInput InputValue c
v
data VoidExpression c =
Conditional (IfElifElse c) |
Loop (IteratedLoop c) |
WithScope (ScopedBlock c) |
Unconditional (Procedure c) |
String
deriving (Int -> VoidExpression c -> ShowS
[VoidExpression c] -> ShowS
VoidExpression c -> String
(Int -> VoidExpression c -> ShowS)
-> (VoidExpression c -> String)
-> ([VoidExpression c] -> ShowS)
-> Show (VoidExpression c)
forall c. Show c => Int -> VoidExpression c -> ShowS
forall c. Show c => [VoidExpression c] -> ShowS
forall c. Show c => VoidExpression c -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall c. Show c => Int -> VoidExpression c -> ShowS
showsPrec :: Int -> VoidExpression c -> ShowS
$cshow :: forall c. Show c => VoidExpression c -> String
show :: VoidExpression c -> String
$cshowList :: forall c. Show c => [VoidExpression c] -> ShowS
showList :: [VoidExpression c] -> ShowS
Show)
data IfElifElse c =
IfStatement [c] (Expression c) (Procedure c) (IfElifElse c) |
ElseStatement [c] (Procedure c) |
TerminateConditional
deriving (Int -> IfElifElse c -> ShowS
[IfElifElse c] -> ShowS
IfElifElse c -> String
(Int -> IfElifElse c -> ShowS)
-> (IfElifElse c -> String)
-> ([IfElifElse c] -> ShowS)
-> Show (IfElifElse c)
forall c. Show c => Int -> IfElifElse c -> ShowS
forall c. Show c => [IfElifElse c] -> ShowS
forall c. Show c => IfElifElse c -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall c. Show c => Int -> IfElifElse c -> ShowS
showsPrec :: Int -> IfElifElse c -> ShowS
$cshow :: forall c. Show c => IfElifElse c -> String
show :: IfElifElse c -> String
$cshowList :: forall c. Show c => [IfElifElse c] -> ShowS
showList :: [IfElifElse c] -> ShowS
Show)
data IteratedLoop c =
WhileLoop [c] (Expression c) (Procedure c) (Maybe (Procedure c)) |
TraverseLoop [c] (Expression c) [c] (Assignable c) (Procedure c) (Maybe (Procedure c))
deriving (Int -> IteratedLoop c -> ShowS
[IteratedLoop c] -> ShowS
IteratedLoop c -> String
(Int -> IteratedLoop c -> ShowS)
-> (IteratedLoop c -> String)
-> ([IteratedLoop c] -> ShowS)
-> Show (IteratedLoop c)
forall c. Show c => Int -> IteratedLoop c -> ShowS
forall c. Show c => [IteratedLoop c] -> ShowS
forall c. Show c => IteratedLoop c -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall c. Show c => Int -> IteratedLoop c -> ShowS
showsPrec :: Int -> IteratedLoop c -> ShowS
$cshow :: forall c. Show c => IteratedLoop c -> String
show :: IteratedLoop c -> String
$cshowList :: forall c. Show c => [IteratedLoop c] -> ShowS
showList :: [IteratedLoop c] -> ShowS
Show)
data ScopedBlock c =
ScopedBlock [c] (Procedure c) (Maybe (Procedure c)) [c] (Statement c)
deriving (Int -> ScopedBlock c -> ShowS
[ScopedBlock c] -> ShowS
ScopedBlock c -> String
(Int -> ScopedBlock c -> ShowS)
-> (ScopedBlock c -> String)
-> ([ScopedBlock c] -> ShowS)
-> Show (ScopedBlock c)
forall c. Show c => Int -> ScopedBlock c -> ShowS
forall c. Show c => [ScopedBlock c] -> ShowS
forall c. Show c => ScopedBlock c -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall c. Show c => Int -> ScopedBlock c -> ShowS
showsPrec :: Int -> ScopedBlock c -> ShowS
$cshow :: forall c. Show c => ScopedBlock c -> String
show :: ScopedBlock c -> String
$cshowList :: forall c. Show c => [ScopedBlock c] -> ShowS
showList :: [ScopedBlock c] -> ShowS
Show)
data Expression c =
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)
deriving (Int -> Expression c -> ShowS
[Expression c] -> ShowS
Expression c -> String
(Int -> Expression c -> ShowS)
-> (Expression c -> String)
-> ([Expression c] -> ShowS)
-> Show (Expression c)
forall c. Show c => Int -> Expression c -> ShowS
forall c. Show c => [Expression c] -> ShowS
forall c. Show c => Expression c -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall c. Show c => Int -> Expression c -> ShowS
showsPrec :: Int -> Expression c -> ShowS
$cshow :: forall c. Show c => Expression c -> String
show :: Expression c -> String
$cshowList :: forall c. Show c => [Expression c] -> ShowS
showList :: [Expression c] -> ShowS
Show)
type ExpressionType = Positional ValueType
data FunctionQualifier c =
CategoryFunction [c] CategoryName |
TypeFunction [c] TypeInstanceOrParam |
ValueFunction [c] ValueCallType (Expression c) |
UnqualifiedFunction
deriving (Int -> FunctionQualifier c -> ShowS
[FunctionQualifier c] -> ShowS
FunctionQualifier c -> String
(Int -> FunctionQualifier c -> ShowS)
-> (FunctionQualifier c -> String)
-> ([FunctionQualifier c] -> ShowS)
-> Show (FunctionQualifier c)
forall c. Show c => Int -> FunctionQualifier c -> ShowS
forall c. Show c => [FunctionQualifier c] -> ShowS
forall c. Show c => FunctionQualifier c -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall c. Show c => Int -> FunctionQualifier c -> ShowS
showsPrec :: Int -> FunctionQualifier c -> ShowS
$cshow :: forall c. Show c => FunctionQualifier c -> String
show :: FunctionQualifier c -> String
$cshowList :: forall c. Show c => [FunctionQualifier c] -> ShowS
showList :: [FunctionQualifier c] -> ShowS
Show)
data InstanceOrInferred c =
AssignedInstance [c] GeneralInstance |
InferredInstance [c]
instance Show c => Show (InstanceOrInferred c) where
show :: InstanceOrInferred c -> String
show (AssignedInstance [c]
_ GeneralInstance
t) = GeneralInstance -> String
forall a. Show a => a -> String
show GeneralInstance
t
show (InferredInstance [c]
_) = String
"?"
data FunctionSpec c =
FunctionSpec [c] (FunctionQualifier c) FunctionName (Positional (InstanceOrInferred c))
deriving (Int -> FunctionSpec c -> ShowS
[FunctionSpec c] -> ShowS
FunctionSpec c -> String
(Int -> FunctionSpec c -> ShowS)
-> (FunctionSpec c -> String)
-> ([FunctionSpec c] -> ShowS)
-> Show (FunctionSpec c)
forall c. Show c => Int -> FunctionSpec c -> ShowS
forall c. Show c => [FunctionSpec c] -> ShowS
forall c. Show c => FunctionSpec c -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall c. Show c => Int -> FunctionSpec c -> ShowS
showsPrec :: Int -> FunctionSpec c -> ShowS
$cshow :: forall c. Show c => FunctionSpec c -> String
show :: FunctionSpec c -> String
$cshowList :: forall c. Show c => [FunctionSpec c] -> ShowS
showList :: [FunctionSpec c] -> ShowS
Show)
data Operator c =
NamedOperator [c] String |
FunctionOperator [c] (FunctionSpec c)
deriving (Int -> Operator c -> ShowS
[Operator c] -> ShowS
Operator c -> String
(Int -> Operator c -> ShowS)
-> (Operator c -> String)
-> ([Operator c] -> ShowS)
-> Show (Operator c)
forall c. Show c => Int -> Operator c -> ShowS
forall c. Show c => [Operator c] -> ShowS
forall c. Show c => Operator c -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall c. Show c => Int -> Operator c -> ShowS
showsPrec :: Int -> Operator c -> ShowS
$cshow :: forall c. Show c => Operator c -> String
show :: Operator c -> String
$cshowList :: forall c. Show c => [Operator c] -> ShowS
showList :: [Operator c] -> ShowS
Show)
getOperatorContext :: Operator c -> [c]
getOperatorContext :: forall c. Operator c -> [c]
getOperatorContext (NamedOperator [c]
c String
_) = [c]
c
getOperatorContext (FunctionOperator [c]
c FunctionSpec c
_) = [c]
c
isFunctionOperator :: Operator c -> Bool
isFunctionOperator :: forall c. Operator c -> Bool
isFunctionOperator (FunctionOperator [c]
_ FunctionSpec c
_) = Bool
True
isFunctionOperator Operator c
_ = Bool
False
getOperatorName :: Operator c -> FunctionName
getOperatorName :: forall c. Operator c -> FunctionName
getOperatorName (NamedOperator [c]
_ String
n) = String -> FunctionName
FunctionName String
n
getOperatorName (FunctionOperator [c]
_ (FunctionSpec [c]
_ FunctionQualifier c
_ FunctionName
n Positional (InstanceOrInferred c)
_)) = FunctionName
n
getExpressionContext :: Expression c -> [c]
getExpressionContext :: forall c. Expression c -> [c]
getExpressionContext (Expression [c]
c ExpressionStart c
_ [ValueOperation c]
_) = [c]
c
getExpressionContext (Literal ValueLiteral c
l) = ValueLiteral c -> [c]
forall c. ValueLiteral c -> [c]
getValueLiteralContext ValueLiteral c
l
getExpressionContext (UnaryExpression [c]
c Operator c
_ Expression c
_) = [c]
c
getExpressionContext (InfixExpression [c]
c Expression c
_ Operator c
_ Expression c
_) = [c]
c
getExpressionContext (RawExpression ExpressionType
_ ExpressionValue
_) = []
getExpressionContext (DelegatedFunctionCall [c]
c FunctionSpec c
_) = [c]
c
getExpressionContext (DelegatedInitializeValue [c]
c Maybe TypeInstance
_) = [c]
c
data FunctionCall c =
FunctionCall [c] FunctionName (Positional (InstanceOrInferred c)) (Positional (Maybe (CallArgLabel c), Expression c))
deriving (Int -> FunctionCall c -> ShowS
[FunctionCall c] -> ShowS
FunctionCall c -> String
(Int -> FunctionCall c -> ShowS)
-> (FunctionCall c -> String)
-> ([FunctionCall c] -> ShowS)
-> Show (FunctionCall c)
forall c. Show c => Int -> FunctionCall c -> ShowS
forall c. Show c => [FunctionCall c] -> ShowS
forall c. Show c => FunctionCall c -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall c. Show c => Int -> FunctionCall c -> ShowS
showsPrec :: Int -> FunctionCall c -> ShowS
$cshow :: forall c. Show c => FunctionCall c -> String
show :: FunctionCall c -> String
$cshowList :: forall c. Show c => [FunctionCall c] -> ShowS
showList :: [FunctionCall c] -> ShowS
Show)
data AssignmentType =
AlwaysAssign |
AssignIfEmpty
deriving (AssignmentType -> AssignmentType -> Bool
(AssignmentType -> AssignmentType -> Bool)
-> (AssignmentType -> AssignmentType -> Bool) -> Eq AssignmentType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AssignmentType -> AssignmentType -> Bool
== :: AssignmentType -> AssignmentType -> Bool
$c/= :: AssignmentType -> AssignmentType -> Bool
/= :: AssignmentType -> AssignmentType -> Bool
Eq,Int -> AssignmentType -> ShowS
[AssignmentType] -> ShowS
AssignmentType -> String
(Int -> AssignmentType -> ShowS)
-> (AssignmentType -> String)
-> ([AssignmentType] -> ShowS)
-> Show AssignmentType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AssignmentType -> ShowS
showsPrec :: Int -> AssignmentType -> ShowS
$cshow :: AssignmentType -> String
show :: AssignmentType -> String
$cshowList :: [AssignmentType] -> ShowS
showList :: [AssignmentType] -> ShowS
Show)
data ExpressionStart c =
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)
deriving (Int -> ExpressionStart c -> ShowS
[ExpressionStart c] -> ShowS
ExpressionStart c -> String
(Int -> ExpressionStart c -> ShowS)
-> (ExpressionStart c -> String)
-> ([ExpressionStart c] -> ShowS)
-> Show (ExpressionStart c)
forall c. Show c => Int -> ExpressionStart c -> ShowS
forall c. Show c => [ExpressionStart c] -> ShowS
forall c. Show c => ExpressionStart c -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall c. Show c => Int -> ExpressionStart c -> ShowS
showsPrec :: Int -> ExpressionStart c -> ShowS
$cshow :: forall c. Show c => ExpressionStart c -> String
show :: ExpressionStart c -> String
$cshowList :: forall c. Show c => [ExpressionStart c] -> ShowS
showList :: [ExpressionStart c] -> ShowS
Show)
data ValueLiteral c =
StringLiteral [c] String |
CharLiteral [c] Char |
IntegerLiteral [c] Bool Integer |
DecimalLiteral [c] Integer Integer Integer |
BoolLiteral [c] Bool |
EmptyLiteral [c]
deriving (Int -> ValueLiteral c -> ShowS
[ValueLiteral c] -> ShowS
ValueLiteral c -> String
(Int -> ValueLiteral c -> ShowS)
-> (ValueLiteral c -> String)
-> ([ValueLiteral c] -> ShowS)
-> Show (ValueLiteral c)
forall c. Show c => Int -> ValueLiteral c -> ShowS
forall c. Show c => [ValueLiteral c] -> ShowS
forall c. Show c => ValueLiteral c -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall c. Show c => Int -> ValueLiteral c -> ShowS
showsPrec :: Int -> ValueLiteral c -> ShowS
$cshow :: forall c. Show c => ValueLiteral c -> String
show :: ValueLiteral c -> String
$cshowList :: forall c. Show c => [ValueLiteral c] -> ShowS
showList :: [ValueLiteral c] -> ShowS
Show)
getValueLiteralContext :: ValueLiteral c -> [c]
getValueLiteralContext :: forall c. ValueLiteral c -> [c]
getValueLiteralContext (StringLiteral [c]
c String
_) = [c]
c
getValueLiteralContext (CharLiteral [c]
c Char
_) = [c]
c
getValueLiteralContext (IntegerLiteral [c]
c Bool
_ Integer
_) = [c]
c
getValueLiteralContext (DecimalLiteral [c]
c Integer
_ Integer
_ Integer
_) = [c]
c
getValueLiteralContext (BoolLiteral [c]
c Bool
_) = [c]
c
getValueLiteralContext (EmptyLiteral [c]
c) = [c]
c
data ValueCallType =
AlwaysCall |
CallUnlessEmpty
deriving (ValueCallType -> ValueCallType -> Bool
(ValueCallType -> ValueCallType -> Bool)
-> (ValueCallType -> ValueCallType -> Bool) -> Eq ValueCallType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ValueCallType -> ValueCallType -> Bool
== :: ValueCallType -> ValueCallType -> Bool
$c/= :: ValueCallType -> ValueCallType -> Bool
/= :: ValueCallType -> ValueCallType -> Bool
Eq,Int -> ValueCallType -> ShowS
[ValueCallType] -> ShowS
ValueCallType -> String
(Int -> ValueCallType -> ShowS)
-> (ValueCallType -> String)
-> ([ValueCallType] -> ShowS)
-> Show ValueCallType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ValueCallType -> ShowS
showsPrec :: Int -> ValueCallType -> ShowS
$cshow :: ValueCallType -> String
show :: ValueCallType -> String
$cshowList :: [ValueCallType] -> ShowS
showList :: [ValueCallType] -> ShowS
Show)
data ValueOperation c =
TypeConversion [c] GeneralInstance |
ValueCall [c] ValueCallType (FunctionCall c) |
SelectReturn [c] Int
deriving (Int -> ValueOperation c -> ShowS
[ValueOperation c] -> ShowS
ValueOperation c -> String
(Int -> ValueOperation c -> ShowS)
-> (ValueOperation c -> String)
-> ([ValueOperation c] -> ShowS)
-> Show (ValueOperation c)
forall c. Show c => Int -> ValueOperation c -> ShowS
forall c. Show c => [ValueOperation c] -> ShowS
forall c. Show c => ValueOperation c -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall c. Show c => Int -> ValueOperation c -> ShowS
showsPrec :: Int -> ValueOperation c -> ShowS
$cshow :: forall c. Show c => ValueOperation c -> String
show :: ValueOperation c -> String
$cshowList :: forall c. Show c => [ValueOperation c] -> ShowS
showList :: [ValueOperation c] -> ShowS
Show)
newtype MacroName =
MacroName {
MacroName -> String
mnName :: String
}
deriving (MacroName -> MacroName -> Bool
(MacroName -> MacroName -> Bool)
-> (MacroName -> MacroName -> Bool) -> Eq MacroName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MacroName -> MacroName -> Bool
== :: MacroName -> MacroName -> Bool
$c/= :: MacroName -> MacroName -> Bool
/= :: MacroName -> MacroName -> Bool
Eq,Eq MacroName
Eq MacroName =>
(MacroName -> MacroName -> Ordering)
-> (MacroName -> MacroName -> Bool)
-> (MacroName -> MacroName -> Bool)
-> (MacroName -> MacroName -> Bool)
-> (MacroName -> MacroName -> Bool)
-> (MacroName -> MacroName -> MacroName)
-> (MacroName -> MacroName -> MacroName)
-> Ord MacroName
MacroName -> MacroName -> Bool
MacroName -> MacroName -> Ordering
MacroName -> MacroName -> MacroName
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: MacroName -> MacroName -> Ordering
compare :: MacroName -> MacroName -> Ordering
$c< :: MacroName -> MacroName -> Bool
< :: MacroName -> MacroName -> Bool
$c<= :: MacroName -> MacroName -> Bool
<= :: MacroName -> MacroName -> Bool
$c> :: MacroName -> MacroName -> Bool
> :: MacroName -> MacroName -> Bool
$c>= :: MacroName -> MacroName -> Bool
>= :: MacroName -> MacroName -> Bool
$cmax :: MacroName -> MacroName -> MacroName
max :: MacroName -> MacroName -> MacroName
$cmin :: MacroName -> MacroName -> MacroName
min :: MacroName -> MacroName -> MacroName
Ord)
instance Show MacroName where
show :: MacroName -> String
show = MacroName -> String
mnName
data TraceType = NoTrace | TraceCreation deriving (Int -> TraceType -> ShowS
[TraceType] -> ShowS
TraceType -> String
(Int -> TraceType -> ShowS)
-> (TraceType -> String)
-> ([TraceType] -> ShowS)
-> Show TraceType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TraceType -> ShowS
showsPrec :: Int -> TraceType -> ShowS
$cshow :: TraceType -> String
show :: TraceType -> String
$cshowList :: [TraceType] -> ShowS
showList :: [TraceType] -> ShowS
Show)
data MacroExpression =
MacroCallTrace
deriving (Int -> MacroExpression -> ShowS
[MacroExpression] -> ShowS
MacroExpression -> String
(Int -> MacroExpression -> ShowS)
-> (MacroExpression -> String)
-> ([MacroExpression] -> ShowS)
-> Show MacroExpression
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MacroExpression -> ShowS
showsPrec :: Int -> MacroExpression -> ShowS
$cshow :: MacroExpression -> String
show :: MacroExpression -> String
$cshowList :: [MacroExpression] -> ShowS
showList :: [MacroExpression] -> ShowS
Show)
data PragmaProcedure c =
PragmaTracing {
forall c. PragmaProcedure c -> [c]
ptContext :: [c],
forall c. PragmaProcedure c -> TraceType
ptType :: TraceType
}
deriving (Int -> PragmaProcedure c -> ShowS
[PragmaProcedure c] -> ShowS
PragmaProcedure c -> String
(Int -> PragmaProcedure c -> ShowS)
-> (PragmaProcedure c -> String)
-> ([PragmaProcedure c] -> ShowS)
-> Show (PragmaProcedure c)
forall c. Show c => Int -> PragmaProcedure c -> ShowS
forall c. Show c => [PragmaProcedure c] -> ShowS
forall c. Show c => PragmaProcedure c -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall c. Show c => Int -> PragmaProcedure c -> ShowS
showsPrec :: Int -> PragmaProcedure c -> ShowS
$cshow :: forall c. Show c => PragmaProcedure c -> String
show :: PragmaProcedure c -> String
$cshowList :: forall c. Show c => [PragmaProcedure c] -> ShowS
showList :: [PragmaProcedure c] -> ShowS
Show)
isNoTrace :: PragmaProcedure c -> Bool
isNoTrace :: forall c. PragmaProcedure c -> Bool
isNoTrace (PragmaTracing [c]
_ TraceType
NoTrace) = Bool
True
isNoTrace PragmaProcedure c
_ = Bool
False
isTraceCreation :: PragmaProcedure c -> Bool
isTraceCreation :: forall c. PragmaProcedure c -> Bool
isTraceCreation (PragmaTracing [c]
_ TraceType
TraceCreation) = Bool
True
isTraceCreation PragmaProcedure c
_ = Bool
False