{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE OverloadedStrings #-}
module Bitcode
where
import Fqn
import Location
import qualified Token
import Data.Aeson
import GHC.Generics
import Data.Set ( Set )
import qualified Data.Set
data Instruction
= Instruction
{
Instruction -> Location
location :: Location,
Instruction -> InstructionContent
instructionContent :: InstructionContent
}
deriving ( Int -> Instruction -> ShowS
[Instruction] -> ShowS
Instruction -> String
(Int -> Instruction -> ShowS)
-> (Instruction -> String)
-> ([Instruction] -> ShowS)
-> Show Instruction
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Instruction -> ShowS
showsPrec :: Int -> Instruction -> ShowS
$cshow :: Instruction -> String
show :: Instruction -> String
$cshowList :: [Instruction] -> ShowS
showList :: [Instruction] -> ShowS
Show, Instruction -> Instruction -> Bool
(Instruction -> Instruction -> Bool)
-> (Instruction -> Instruction -> Bool) -> Eq Instruction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Instruction -> Instruction -> Bool
== :: Instruction -> Instruction -> Bool
$c/= :: Instruction -> Instruction -> Bool
/= :: Instruction -> Instruction -> Bool
Eq, (forall x. Instruction -> Rep Instruction x)
-> (forall x. Rep Instruction x -> Instruction)
-> Generic Instruction
forall x. Rep Instruction x -> Instruction
forall x. Instruction -> Rep Instruction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Instruction -> Rep Instruction x
from :: forall x. Instruction -> Rep Instruction x
$cto :: forall x. Rep Instruction x -> Instruction
to :: forall x. Rep Instruction x -> Instruction
Generic, [Instruction] -> Value
[Instruction] -> Encoding
Instruction -> Bool
Instruction -> Value
Instruction -> Encoding
(Instruction -> Value)
-> (Instruction -> Encoding)
-> ([Instruction] -> Value)
-> ([Instruction] -> Encoding)
-> (Instruction -> Bool)
-> ToJSON Instruction
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Instruction -> Value
toJSON :: Instruction -> Value
$ctoEncoding :: Instruction -> Encoding
toEncoding :: Instruction -> Encoding
$ctoJSONList :: [Instruction] -> Value
toJSONList :: [Instruction] -> Value
$ctoEncodingList :: [Instruction] -> Encoding
toEncodingList :: [Instruction] -> Encoding
$comitField :: Instruction -> Bool
omitField :: Instruction -> Bool
ToJSON, Maybe Instruction
Value -> Parser [Instruction]
Value -> Parser Instruction
(Value -> Parser Instruction)
-> (Value -> Parser [Instruction])
-> Maybe Instruction
-> FromJSON Instruction
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Instruction
parseJSON :: Value -> Parser Instruction
$cparseJSONList :: Value -> Parser [Instruction]
parseJSONList :: Value -> Parser [Instruction]
$comittedField :: Maybe Instruction
omittedField :: Maybe Instruction
FromJSON, Eq Instruction
Eq Instruction
-> (Instruction -> Instruction -> Ordering)
-> (Instruction -> Instruction -> Bool)
-> (Instruction -> Instruction -> Bool)
-> (Instruction -> Instruction -> Bool)
-> (Instruction -> Instruction -> Bool)
-> (Instruction -> Instruction -> Instruction)
-> (Instruction -> Instruction -> Instruction)
-> Ord Instruction
Instruction -> Instruction -> Bool
Instruction -> Instruction -> Ordering
Instruction -> Instruction -> Instruction
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 :: Instruction -> Instruction -> Ordering
compare :: Instruction -> Instruction -> Ordering
$c< :: Instruction -> Instruction -> Bool
< :: Instruction -> Instruction -> Bool
$c<= :: Instruction -> Instruction -> Bool
<= :: Instruction -> Instruction -> Bool
$c> :: Instruction -> Instruction -> Bool
> :: Instruction -> Instruction -> Bool
$c>= :: Instruction -> Instruction -> Bool
>= :: Instruction -> Instruction -> Bool
$cmax :: Instruction -> Instruction -> Instruction
max :: Instruction -> Instruction -> Instruction
$cmin :: Instruction -> Instruction -> Instruction
min :: Instruction -> Instruction -> Instruction
Ord )
data InstructionContent
= Nop
| Call CallContent
| Unop UnopContent
| Binop BinopContent
| Assume AssumeContent
| Return ReturnContent
| Assign AssignContent
| LoadImmStr StrContent
| LoadImmInt IntContent
| LoadImmBool BoolContent
| ParamDecl ParamDeclContent
| FieldRead FieldReadContent
| FieldWrite FieldWriteContent
| SubscriptRead SubscriptReadContent
| SubscriptWrite SubscriptWriteContent
deriving ( Int -> InstructionContent -> ShowS
[InstructionContent] -> ShowS
InstructionContent -> String
(Int -> InstructionContent -> ShowS)
-> (InstructionContent -> String)
-> ([InstructionContent] -> ShowS)
-> Show InstructionContent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InstructionContent -> ShowS
showsPrec :: Int -> InstructionContent -> ShowS
$cshow :: InstructionContent -> String
show :: InstructionContent -> String
$cshowList :: [InstructionContent] -> ShowS
showList :: [InstructionContent] -> ShowS
Show, InstructionContent -> InstructionContent -> Bool
(InstructionContent -> InstructionContent -> Bool)
-> (InstructionContent -> InstructionContent -> Bool)
-> Eq InstructionContent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InstructionContent -> InstructionContent -> Bool
== :: InstructionContent -> InstructionContent -> Bool
$c/= :: InstructionContent -> InstructionContent -> Bool
/= :: InstructionContent -> InstructionContent -> Bool
Eq, (forall x. InstructionContent -> Rep InstructionContent x)
-> (forall x. Rep InstructionContent x -> InstructionContent)
-> Generic InstructionContent
forall x. Rep InstructionContent x -> InstructionContent
forall x. InstructionContent -> Rep InstructionContent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. InstructionContent -> Rep InstructionContent x
from :: forall x. InstructionContent -> Rep InstructionContent x
$cto :: forall x. Rep InstructionContent x -> InstructionContent
to :: forall x. Rep InstructionContent x -> InstructionContent
Generic, [InstructionContent] -> Value
[InstructionContent] -> Encoding
InstructionContent -> Bool
InstructionContent -> Value
InstructionContent -> Encoding
(InstructionContent -> Value)
-> (InstructionContent -> Encoding)
-> ([InstructionContent] -> Value)
-> ([InstructionContent] -> Encoding)
-> (InstructionContent -> Bool)
-> ToJSON InstructionContent
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: InstructionContent -> Value
toJSON :: InstructionContent -> Value
$ctoEncoding :: InstructionContent -> Encoding
toEncoding :: InstructionContent -> Encoding
$ctoJSONList :: [InstructionContent] -> Value
toJSONList :: [InstructionContent] -> Value
$ctoEncodingList :: [InstructionContent] -> Encoding
toEncodingList :: [InstructionContent] -> Encoding
$comitField :: InstructionContent -> Bool
omitField :: InstructionContent -> Bool
ToJSON, Maybe InstructionContent
Value -> Parser [InstructionContent]
Value -> Parser InstructionContent
(Value -> Parser InstructionContent)
-> (Value -> Parser [InstructionContent])
-> Maybe InstructionContent
-> FromJSON InstructionContent
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser InstructionContent
parseJSON :: Value -> Parser InstructionContent
$cparseJSONList :: Value -> Parser [InstructionContent]
parseJSONList :: Value -> Parser [InstructionContent]
$comittedField :: Maybe InstructionContent
omittedField :: Maybe InstructionContent
FromJSON, Eq InstructionContent
Eq InstructionContent
-> (InstructionContent -> InstructionContent -> Ordering)
-> (InstructionContent -> InstructionContent -> Bool)
-> (InstructionContent -> InstructionContent -> Bool)
-> (InstructionContent -> InstructionContent -> Bool)
-> (InstructionContent -> InstructionContent -> Bool)
-> (InstructionContent -> InstructionContent -> InstructionContent)
-> (InstructionContent -> InstructionContent -> InstructionContent)
-> Ord InstructionContent
InstructionContent -> InstructionContent -> Bool
InstructionContent -> InstructionContent -> Ordering
InstructionContent -> InstructionContent -> InstructionContent
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 :: InstructionContent -> InstructionContent -> Ordering
compare :: InstructionContent -> InstructionContent -> Ordering
$c< :: InstructionContent -> InstructionContent -> Bool
< :: InstructionContent -> InstructionContent -> Bool
$c<= :: InstructionContent -> InstructionContent -> Bool
<= :: InstructionContent -> InstructionContent -> Bool
$c> :: InstructionContent -> InstructionContent -> Bool
> :: InstructionContent -> InstructionContent -> Bool
$c>= :: InstructionContent -> InstructionContent -> Bool
>= :: InstructionContent -> InstructionContent -> Bool
$cmax :: InstructionContent -> InstructionContent -> InstructionContent
max :: InstructionContent -> InstructionContent -> InstructionContent
$cmin :: InstructionContent -> InstructionContent -> InstructionContent
min :: InstructionContent -> InstructionContent -> InstructionContent
Ord )
mkNopInstruction :: Location -> Instruction
mkNopInstruction :: Location -> Instruction
mkNopInstruction Location
l = Instruction { location :: Location
location = Location
l, instructionContent :: InstructionContent
instructionContent = InstructionContent
Nop }
data TmpVariable
= TmpVariable
{
TmpVariable -> Fqn
tmpVariableFqn :: Fqn,
TmpVariable -> Location
tmpVariableLocation :: Location
}
deriving ( Int -> TmpVariable -> ShowS
[TmpVariable] -> ShowS
TmpVariable -> String
(Int -> TmpVariable -> ShowS)
-> (TmpVariable -> String)
-> ([TmpVariable] -> ShowS)
-> Show TmpVariable
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TmpVariable -> ShowS
showsPrec :: Int -> TmpVariable -> ShowS
$cshow :: TmpVariable -> String
show :: TmpVariable -> String
$cshowList :: [TmpVariable] -> ShowS
showList :: [TmpVariable] -> ShowS
Show, TmpVariable -> TmpVariable -> Bool
(TmpVariable -> TmpVariable -> Bool)
-> (TmpVariable -> TmpVariable -> Bool) -> Eq TmpVariable
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TmpVariable -> TmpVariable -> Bool
== :: TmpVariable -> TmpVariable -> Bool
$c/= :: TmpVariable -> TmpVariable -> Bool
/= :: TmpVariable -> TmpVariable -> Bool
Eq, Eq TmpVariable
Eq TmpVariable
-> (TmpVariable -> TmpVariable -> Ordering)
-> (TmpVariable -> TmpVariable -> Bool)
-> (TmpVariable -> TmpVariable -> Bool)
-> (TmpVariable -> TmpVariable -> Bool)
-> (TmpVariable -> TmpVariable -> Bool)
-> (TmpVariable -> TmpVariable -> TmpVariable)
-> (TmpVariable -> TmpVariable -> TmpVariable)
-> Ord TmpVariable
TmpVariable -> TmpVariable -> Bool
TmpVariable -> TmpVariable -> Ordering
TmpVariable -> TmpVariable -> TmpVariable
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 :: TmpVariable -> TmpVariable -> Ordering
compare :: TmpVariable -> TmpVariable -> Ordering
$c< :: TmpVariable -> TmpVariable -> Bool
< :: TmpVariable -> TmpVariable -> Bool
$c<= :: TmpVariable -> TmpVariable -> Bool
<= :: TmpVariable -> TmpVariable -> Bool
$c> :: TmpVariable -> TmpVariable -> Bool
> :: TmpVariable -> TmpVariable -> Bool
$c>= :: TmpVariable -> TmpVariable -> Bool
>= :: TmpVariable -> TmpVariable -> Bool
$cmax :: TmpVariable -> TmpVariable -> TmpVariable
max :: TmpVariable -> TmpVariable -> TmpVariable
$cmin :: TmpVariable -> TmpVariable -> TmpVariable
min :: TmpVariable -> TmpVariable -> TmpVariable
Ord, (forall x. TmpVariable -> Rep TmpVariable x)
-> (forall x. Rep TmpVariable x -> TmpVariable)
-> Generic TmpVariable
forall x. Rep TmpVariable x -> TmpVariable
forall x. TmpVariable -> Rep TmpVariable x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TmpVariable -> Rep TmpVariable x
from :: forall x. TmpVariable -> Rep TmpVariable x
$cto :: forall x. Rep TmpVariable x -> TmpVariable
to :: forall x. Rep TmpVariable x -> TmpVariable
Generic, [TmpVariable] -> Value
[TmpVariable] -> Encoding
TmpVariable -> Bool
TmpVariable -> Value
TmpVariable -> Encoding
(TmpVariable -> Value)
-> (TmpVariable -> Encoding)
-> ([TmpVariable] -> Value)
-> ([TmpVariable] -> Encoding)
-> (TmpVariable -> Bool)
-> ToJSON TmpVariable
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: TmpVariable -> Value
toJSON :: TmpVariable -> Value
$ctoEncoding :: TmpVariable -> Encoding
toEncoding :: TmpVariable -> Encoding
$ctoJSONList :: [TmpVariable] -> Value
toJSONList :: [TmpVariable] -> Value
$ctoEncodingList :: [TmpVariable] -> Encoding
toEncodingList :: [TmpVariable] -> Encoding
$comitField :: TmpVariable -> Bool
omitField :: TmpVariable -> Bool
ToJSON, Maybe TmpVariable
Value -> Parser [TmpVariable]
Value -> Parser TmpVariable
(Value -> Parser TmpVariable)
-> (Value -> Parser [TmpVariable])
-> Maybe TmpVariable
-> FromJSON TmpVariable
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser TmpVariable
parseJSON :: Value -> Parser TmpVariable
$cparseJSONList :: Value -> Parser [TmpVariable]
parseJSONList :: Value -> Parser [TmpVariable]
$comittedField :: Maybe TmpVariable
omittedField :: Maybe TmpVariable
FromJSON )
data SrcVariable
= SrcVariable
{
SrcVariable -> Fqn
srcVariableFqn :: Fqn,
SrcVariable -> VarName
srcVariableToken :: Token.VarName
}
deriving ( Int -> SrcVariable -> ShowS
[SrcVariable] -> ShowS
SrcVariable -> String
(Int -> SrcVariable -> ShowS)
-> (SrcVariable -> String)
-> ([SrcVariable] -> ShowS)
-> Show SrcVariable
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SrcVariable -> ShowS
showsPrec :: Int -> SrcVariable -> ShowS
$cshow :: SrcVariable -> String
show :: SrcVariable -> String
$cshowList :: [SrcVariable] -> ShowS
showList :: [SrcVariable] -> ShowS
Show, SrcVariable -> SrcVariable -> Bool
(SrcVariable -> SrcVariable -> Bool)
-> (SrcVariable -> SrcVariable -> Bool) -> Eq SrcVariable
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SrcVariable -> SrcVariable -> Bool
== :: SrcVariable -> SrcVariable -> Bool
$c/= :: SrcVariable -> SrcVariable -> Bool
/= :: SrcVariable -> SrcVariable -> Bool
Eq, Eq SrcVariable
Eq SrcVariable
-> (SrcVariable -> SrcVariable -> Ordering)
-> (SrcVariable -> SrcVariable -> Bool)
-> (SrcVariable -> SrcVariable -> Bool)
-> (SrcVariable -> SrcVariable -> Bool)
-> (SrcVariable -> SrcVariable -> Bool)
-> (SrcVariable -> SrcVariable -> SrcVariable)
-> (SrcVariable -> SrcVariable -> SrcVariable)
-> Ord SrcVariable
SrcVariable -> SrcVariable -> Bool
SrcVariable -> SrcVariable -> Ordering
SrcVariable -> SrcVariable -> SrcVariable
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 :: SrcVariable -> SrcVariable -> Ordering
compare :: SrcVariable -> SrcVariable -> Ordering
$c< :: SrcVariable -> SrcVariable -> Bool
< :: SrcVariable -> SrcVariable -> Bool
$c<= :: SrcVariable -> SrcVariable -> Bool
<= :: SrcVariable -> SrcVariable -> Bool
$c> :: SrcVariable -> SrcVariable -> Bool
> :: SrcVariable -> SrcVariable -> Bool
$c>= :: SrcVariable -> SrcVariable -> Bool
>= :: SrcVariable -> SrcVariable -> Bool
$cmax :: SrcVariable -> SrcVariable -> SrcVariable
max :: SrcVariable -> SrcVariable -> SrcVariable
$cmin :: SrcVariable -> SrcVariable -> SrcVariable
min :: SrcVariable -> SrcVariable -> SrcVariable
Ord, (forall x. SrcVariable -> Rep SrcVariable x)
-> (forall x. Rep SrcVariable x -> SrcVariable)
-> Generic SrcVariable
forall x. Rep SrcVariable x -> SrcVariable
forall x. SrcVariable -> Rep SrcVariable x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SrcVariable -> Rep SrcVariable x
from :: forall x. SrcVariable -> Rep SrcVariable x
$cto :: forall x. Rep SrcVariable x -> SrcVariable
to :: forall x. Rep SrcVariable x -> SrcVariable
Generic, [SrcVariable] -> Value
[SrcVariable] -> Encoding
SrcVariable -> Bool
SrcVariable -> Value
SrcVariable -> Encoding
(SrcVariable -> Value)
-> (SrcVariable -> Encoding)
-> ([SrcVariable] -> Value)
-> ([SrcVariable] -> Encoding)
-> (SrcVariable -> Bool)
-> ToJSON SrcVariable
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: SrcVariable -> Value
toJSON :: SrcVariable -> Value
$ctoEncoding :: SrcVariable -> Encoding
toEncoding :: SrcVariable -> Encoding
$ctoJSONList :: [SrcVariable] -> Value
toJSONList :: [SrcVariable] -> Value
$ctoEncodingList :: [SrcVariable] -> Encoding
toEncodingList :: [SrcVariable] -> Encoding
$comitField :: SrcVariable -> Bool
omitField :: SrcVariable -> Bool
ToJSON, Maybe SrcVariable
Value -> Parser [SrcVariable]
Value -> Parser SrcVariable
(Value -> Parser SrcVariable)
-> (Value -> Parser [SrcVariable])
-> Maybe SrcVariable
-> FromJSON SrcVariable
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser SrcVariable
parseJSON :: Value -> Parser SrcVariable
$cparseJSONList :: Value -> Parser [SrcVariable]
parseJSONList :: Value -> Parser [SrcVariable]
$comittedField :: Maybe SrcVariable
omittedField :: Maybe SrcVariable
FromJSON )
data ArgContent
= ArgContent
{
ArgContent -> Fqn
argVariableFqn :: Fqn,
ArgContent -> Word
argVariableSerialIdx :: Word,
ArgContent -> Location
argVariableMyAwesomeCallContext :: Location
}
deriving ( Int -> ArgContent -> ShowS
[ArgContent] -> ShowS
ArgContent -> String
(Int -> ArgContent -> ShowS)
-> (ArgContent -> String)
-> ([ArgContent] -> ShowS)
-> Show ArgContent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ArgContent -> ShowS
showsPrec :: Int -> ArgContent -> ShowS
$cshow :: ArgContent -> String
show :: ArgContent -> String
$cshowList :: [ArgContent] -> ShowS
showList :: [ArgContent] -> ShowS
Show, ArgContent -> ArgContent -> Bool
(ArgContent -> ArgContent -> Bool)
-> (ArgContent -> ArgContent -> Bool) -> Eq ArgContent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ArgContent -> ArgContent -> Bool
== :: ArgContent -> ArgContent -> Bool
$c/= :: ArgContent -> ArgContent -> Bool
/= :: ArgContent -> ArgContent -> Bool
Eq, Eq ArgContent
Eq ArgContent
-> (ArgContent -> ArgContent -> Ordering)
-> (ArgContent -> ArgContent -> Bool)
-> (ArgContent -> ArgContent -> Bool)
-> (ArgContent -> ArgContent -> Bool)
-> (ArgContent -> ArgContent -> Bool)
-> (ArgContent -> ArgContent -> ArgContent)
-> (ArgContent -> ArgContent -> ArgContent)
-> Ord ArgContent
ArgContent -> ArgContent -> Bool
ArgContent -> ArgContent -> Ordering
ArgContent -> ArgContent -> ArgContent
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 :: ArgContent -> ArgContent -> Ordering
compare :: ArgContent -> ArgContent -> Ordering
$c< :: ArgContent -> ArgContent -> Bool
< :: ArgContent -> ArgContent -> Bool
$c<= :: ArgContent -> ArgContent -> Bool
<= :: ArgContent -> ArgContent -> Bool
$c> :: ArgContent -> ArgContent -> Bool
> :: ArgContent -> ArgContent -> Bool
$c>= :: ArgContent -> ArgContent -> Bool
>= :: ArgContent -> ArgContent -> Bool
$cmax :: ArgContent -> ArgContent -> ArgContent
max :: ArgContent -> ArgContent -> ArgContent
$cmin :: ArgContent -> ArgContent -> ArgContent
min :: ArgContent -> ArgContent -> ArgContent
Ord, (forall x. ArgContent -> Rep ArgContent x)
-> (forall x. Rep ArgContent x -> ArgContent) -> Generic ArgContent
forall x. Rep ArgContent x -> ArgContent
forall x. ArgContent -> Rep ArgContent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ArgContent -> Rep ArgContent x
from :: forall x. ArgContent -> Rep ArgContent x
$cto :: forall x. Rep ArgContent x -> ArgContent
to :: forall x. Rep ArgContent x -> ArgContent
Generic, [ArgContent] -> Value
[ArgContent] -> Encoding
ArgContent -> Bool
ArgContent -> Value
ArgContent -> Encoding
(ArgContent -> Value)
-> (ArgContent -> Encoding)
-> ([ArgContent] -> Value)
-> ([ArgContent] -> Encoding)
-> (ArgContent -> Bool)
-> ToJSON ArgContent
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: ArgContent -> Value
toJSON :: ArgContent -> Value
$ctoEncoding :: ArgContent -> Encoding
toEncoding :: ArgContent -> Encoding
$ctoJSONList :: [ArgContent] -> Value
toJSONList :: [ArgContent] -> Value
$ctoEncodingList :: [ArgContent] -> Encoding
toEncodingList :: [ArgContent] -> Encoding
$comitField :: ArgContent -> Bool
omitField :: ArgContent -> Bool
ToJSON, Maybe ArgContent
Value -> Parser [ArgContent]
Value -> Parser ArgContent
(Value -> Parser ArgContent)
-> (Value -> Parser [ArgContent])
-> Maybe ArgContent
-> FromJSON ArgContent
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser ArgContent
parseJSON :: Value -> Parser ArgContent
$cparseJSONList :: Value -> Parser [ArgContent]
parseJSONList :: Value -> Parser [ArgContent]
$comittedField :: Maybe ArgContent
omittedField :: Maybe ArgContent
FromJSON )
data ParamVariable
= ParamVariable
{
ParamVariable -> Fqn
paramVariableFqn :: Fqn,
ParamVariable -> Word
paramVariableSerialIdx :: Word,
ParamVariable -> ParamName
paramVariableToken :: Token.ParamName
}
deriving ( Int -> ParamVariable -> ShowS
[ParamVariable] -> ShowS
ParamVariable -> String
(Int -> ParamVariable -> ShowS)
-> (ParamVariable -> String)
-> ([ParamVariable] -> ShowS)
-> Show ParamVariable
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ParamVariable -> ShowS
showsPrec :: Int -> ParamVariable -> ShowS
$cshow :: ParamVariable -> String
show :: ParamVariable -> String
$cshowList :: [ParamVariable] -> ShowS
showList :: [ParamVariable] -> ShowS
Show, ParamVariable -> ParamVariable -> Bool
(ParamVariable -> ParamVariable -> Bool)
-> (ParamVariable -> ParamVariable -> Bool) -> Eq ParamVariable
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ParamVariable -> ParamVariable -> Bool
== :: ParamVariable -> ParamVariable -> Bool
$c/= :: ParamVariable -> ParamVariable -> Bool
/= :: ParamVariable -> ParamVariable -> Bool
Eq, Eq ParamVariable
Eq ParamVariable
-> (ParamVariable -> ParamVariable -> Ordering)
-> (ParamVariable -> ParamVariable -> Bool)
-> (ParamVariable -> ParamVariable -> Bool)
-> (ParamVariable -> ParamVariable -> Bool)
-> (ParamVariable -> ParamVariable -> Bool)
-> (ParamVariable -> ParamVariable -> ParamVariable)
-> (ParamVariable -> ParamVariable -> ParamVariable)
-> Ord ParamVariable
ParamVariable -> ParamVariable -> Bool
ParamVariable -> ParamVariable -> Ordering
ParamVariable -> ParamVariable -> ParamVariable
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 :: ParamVariable -> ParamVariable -> Ordering
compare :: ParamVariable -> ParamVariable -> Ordering
$c< :: ParamVariable -> ParamVariable -> Bool
< :: ParamVariable -> ParamVariable -> Bool
$c<= :: ParamVariable -> ParamVariable -> Bool
<= :: ParamVariable -> ParamVariable -> Bool
$c> :: ParamVariable -> ParamVariable -> Bool
> :: ParamVariable -> ParamVariable -> Bool
$c>= :: ParamVariable -> ParamVariable -> Bool
>= :: ParamVariable -> ParamVariable -> Bool
$cmax :: ParamVariable -> ParamVariable -> ParamVariable
max :: ParamVariable -> ParamVariable -> ParamVariable
$cmin :: ParamVariable -> ParamVariable -> ParamVariable
min :: ParamVariable -> ParamVariable -> ParamVariable
Ord, (forall x. ParamVariable -> Rep ParamVariable x)
-> (forall x. Rep ParamVariable x -> ParamVariable)
-> Generic ParamVariable
forall x. Rep ParamVariable x -> ParamVariable
forall x. ParamVariable -> Rep ParamVariable x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ParamVariable -> Rep ParamVariable x
from :: forall x. ParamVariable -> Rep ParamVariable x
$cto :: forall x. Rep ParamVariable x -> ParamVariable
to :: forall x. Rep ParamVariable x -> ParamVariable
Generic, [ParamVariable] -> Value
[ParamVariable] -> Encoding
ParamVariable -> Bool
ParamVariable -> Value
ParamVariable -> Encoding
(ParamVariable -> Value)
-> (ParamVariable -> Encoding)
-> ([ParamVariable] -> Value)
-> ([ParamVariable] -> Encoding)
-> (ParamVariable -> Bool)
-> ToJSON ParamVariable
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: ParamVariable -> Value
toJSON :: ParamVariable -> Value
$ctoEncoding :: ParamVariable -> Encoding
toEncoding :: ParamVariable -> Encoding
$ctoJSONList :: [ParamVariable] -> Value
toJSONList :: [ParamVariable] -> Value
$ctoEncodingList :: [ParamVariable] -> Encoding
toEncodingList :: [ParamVariable] -> Encoding
$comitField :: ParamVariable -> Bool
omitField :: ParamVariable -> Bool
ToJSON, Maybe ParamVariable
Value -> Parser [ParamVariable]
Value -> Parser ParamVariable
(Value -> Parser ParamVariable)
-> (Value -> Parser [ParamVariable])
-> Maybe ParamVariable
-> FromJSON ParamVariable
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser ParamVariable
parseJSON :: Value -> Parser ParamVariable
$cparseJSONList :: Value -> Parser [ParamVariable]
parseJSONList :: Value -> Parser [ParamVariable]
$comittedField :: Maybe ParamVariable
omittedField :: Maybe ParamVariable
FromJSON )
data Variable
= TmpVariableCtor TmpVariable
| SrcVariableCtor SrcVariable
| ParamVariableCtor ParamVariable
| Arg ArgContent
deriving ( Int -> Variable -> ShowS
[Variable] -> ShowS
Variable -> String
(Int -> Variable -> ShowS)
-> (Variable -> String) -> ([Variable] -> ShowS) -> Show Variable
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Variable -> ShowS
showsPrec :: Int -> Variable -> ShowS
$cshow :: Variable -> String
show :: Variable -> String
$cshowList :: [Variable] -> ShowS
showList :: [Variable] -> ShowS
Show, Variable -> Variable -> Bool
(Variable -> Variable -> Bool)
-> (Variable -> Variable -> Bool) -> Eq Variable
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Variable -> Variable -> Bool
== :: Variable -> Variable -> Bool
$c/= :: Variable -> Variable -> Bool
/= :: Variable -> Variable -> Bool
Eq, Eq Variable
Eq Variable
-> (Variable -> Variable -> Ordering)
-> (Variable -> Variable -> Bool)
-> (Variable -> Variable -> Bool)
-> (Variable -> Variable -> Bool)
-> (Variable -> Variable -> Bool)
-> (Variable -> Variable -> Variable)
-> (Variable -> Variable -> Variable)
-> Ord Variable
Variable -> Variable -> Bool
Variable -> Variable -> Ordering
Variable -> Variable -> Variable
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 :: Variable -> Variable -> Ordering
compare :: Variable -> Variable -> Ordering
$c< :: Variable -> Variable -> Bool
< :: Variable -> Variable -> Bool
$c<= :: Variable -> Variable -> Bool
<= :: Variable -> Variable -> Bool
$c> :: Variable -> Variable -> Bool
> :: Variable -> Variable -> Bool
$c>= :: Variable -> Variable -> Bool
>= :: Variable -> Variable -> Bool
$cmax :: Variable -> Variable -> Variable
max :: Variable -> Variable -> Variable
$cmin :: Variable -> Variable -> Variable
min :: Variable -> Variable -> Variable
Ord, (forall x. Variable -> Rep Variable x)
-> (forall x. Rep Variable x -> Variable) -> Generic Variable
forall x. Rep Variable x -> Variable
forall x. Variable -> Rep Variable x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Variable -> Rep Variable x
from :: forall x. Variable -> Rep Variable x
$cto :: forall x. Rep Variable x -> Variable
to :: forall x. Rep Variable x -> Variable
Generic, [Variable] -> Value
[Variable] -> Encoding
Variable -> Bool
Variable -> Value
Variable -> Encoding
(Variable -> Value)
-> (Variable -> Encoding)
-> ([Variable] -> Value)
-> ([Variable] -> Encoding)
-> (Variable -> Bool)
-> ToJSON Variable
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Variable -> Value
toJSON :: Variable -> Value
$ctoEncoding :: Variable -> Encoding
toEncoding :: Variable -> Encoding
$ctoJSONList :: [Variable] -> Value
toJSONList :: [Variable] -> Value
$ctoEncodingList :: [Variable] -> Encoding
toEncodingList :: [Variable] -> Encoding
$comitField :: Variable -> Bool
omitField :: Variable -> Bool
ToJSON, Maybe Variable
Value -> Parser [Variable]
Value -> Parser Variable
(Value -> Parser Variable)
-> (Value -> Parser [Variable])
-> Maybe Variable
-> FromJSON Variable
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Variable
parseJSON :: Value -> Parser Variable
$cparseJSONList :: Value -> Parser [Variable]
parseJSONList :: Value -> Parser [Variable]
$comittedField :: Maybe Variable
omittedField :: Maybe Variable
FromJSON )
variableFqn :: Variable -> Fqn
variableFqn :: Variable -> Fqn
variableFqn (TmpVariableCtor (TmpVariable Fqn
fqn Location
_ )) = Fqn
fqn
variableFqn (SrcVariableCtor (SrcVariable Fqn
fqn VarName
_ )) = Fqn
fqn
variableFqn (ParamVariableCtor (ParamVariable Fqn
fqn Word
_ ParamName
_ )) = Fqn
fqn
variableFqn Variable
_ = String -> Fqn
Fqn String
"blah"
data Variables = Variables { Variables -> Set Variable
actualVariables :: Set Variable } deriving ( Int -> Variables -> ShowS
[Variables] -> ShowS
Variables -> String
(Int -> Variables -> ShowS)
-> (Variables -> String)
-> ([Variables] -> ShowS)
-> Show Variables
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Variables -> ShowS
showsPrec :: Int -> Variables -> ShowS
$cshow :: Variables -> String
show :: Variables -> String
$cshowList :: [Variables] -> ShowS
showList :: [Variables] -> ShowS
Show, Variables -> Variables -> Bool
(Variables -> Variables -> Bool)
-> (Variables -> Variables -> Bool) -> Eq Variables
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Variables -> Variables -> Bool
== :: Variables -> Variables -> Bool
$c/= :: Variables -> Variables -> Bool
/= :: Variables -> Variables -> Bool
Eq, Eq Variables
Eq Variables
-> (Variables -> Variables -> Ordering)
-> (Variables -> Variables -> Bool)
-> (Variables -> Variables -> Bool)
-> (Variables -> Variables -> Bool)
-> (Variables -> Variables -> Bool)
-> (Variables -> Variables -> Variables)
-> (Variables -> Variables -> Variables)
-> Ord Variables
Variables -> Variables -> Bool
Variables -> Variables -> Ordering
Variables -> Variables -> Variables
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 :: Variables -> Variables -> Ordering
compare :: Variables -> Variables -> Ordering
$c< :: Variables -> Variables -> Bool
< :: Variables -> Variables -> Bool
$c<= :: Variables -> Variables -> Bool
<= :: Variables -> Variables -> Bool
$c> :: Variables -> Variables -> Bool
> :: Variables -> Variables -> Bool
$c>= :: Variables -> Variables -> Bool
>= :: Variables -> Variables -> Bool
$cmax :: Variables -> Variables -> Variables
max :: Variables -> Variables -> Variables
$cmin :: Variables -> Variables -> Variables
min :: Variables -> Variables -> Variables
Ord )
data SrcVariables = SrcVariables { SrcVariables -> Set SrcVariable
actualSrcVariables :: Set SrcVariable } deriving ( Int -> SrcVariables -> ShowS
[SrcVariables] -> ShowS
SrcVariables -> String
(Int -> SrcVariables -> ShowS)
-> (SrcVariables -> String)
-> ([SrcVariables] -> ShowS)
-> Show SrcVariables
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SrcVariables -> ShowS
showsPrec :: Int -> SrcVariables -> ShowS
$cshow :: SrcVariables -> String
show :: SrcVariables -> String
$cshowList :: [SrcVariables] -> ShowS
showList :: [SrcVariables] -> ShowS
Show, SrcVariables -> SrcVariables -> Bool
(SrcVariables -> SrcVariables -> Bool)
-> (SrcVariables -> SrcVariables -> Bool) -> Eq SrcVariables
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SrcVariables -> SrcVariables -> Bool
== :: SrcVariables -> SrcVariables -> Bool
$c/= :: SrcVariables -> SrcVariables -> Bool
/= :: SrcVariables -> SrcVariables -> Bool
Eq, Eq SrcVariables
Eq SrcVariables
-> (SrcVariables -> SrcVariables -> Ordering)
-> (SrcVariables -> SrcVariables -> Bool)
-> (SrcVariables -> SrcVariables -> Bool)
-> (SrcVariables -> SrcVariables -> Bool)
-> (SrcVariables -> SrcVariables -> Bool)
-> (SrcVariables -> SrcVariables -> SrcVariables)
-> (SrcVariables -> SrcVariables -> SrcVariables)
-> Ord SrcVariables
SrcVariables -> SrcVariables -> Bool
SrcVariables -> SrcVariables -> Ordering
SrcVariables -> SrcVariables -> SrcVariables
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 :: SrcVariables -> SrcVariables -> Ordering
compare :: SrcVariables -> SrcVariables -> Ordering
$c< :: SrcVariables -> SrcVariables -> Bool
< :: SrcVariables -> SrcVariables -> Bool
$c<= :: SrcVariables -> SrcVariables -> Bool
<= :: SrcVariables -> SrcVariables -> Bool
$c> :: SrcVariables -> SrcVariables -> Bool
> :: SrcVariables -> SrcVariables -> Bool
$c>= :: SrcVariables -> SrcVariables -> Bool
>= :: SrcVariables -> SrcVariables -> Bool
$cmax :: SrcVariables -> SrcVariables -> SrcVariables
max :: SrcVariables -> SrcVariables -> SrcVariables
$cmin :: SrcVariables -> SrcVariables -> SrcVariables
min :: SrcVariables -> SrcVariables -> SrcVariables
Ord )
createEmptyCollectionOfGlobalVariables :: SrcVariables
createEmptyCollectionOfGlobalVariables :: SrcVariables
createEmptyCollectionOfGlobalVariables = SrcVariables { actualSrcVariables :: Set SrcVariable
actualSrcVariables = Set SrcVariable
forall a. Set a
Data.Set.empty }
data TmpVariables = TmpVariables { TmpVariables -> Set TmpVariable
actualTmpVariables :: Set TmpVariable } deriving ( Int -> TmpVariables -> ShowS
[TmpVariables] -> ShowS
TmpVariables -> String
(Int -> TmpVariables -> ShowS)
-> (TmpVariables -> String)
-> ([TmpVariables] -> ShowS)
-> Show TmpVariables
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TmpVariables -> ShowS
showsPrec :: Int -> TmpVariables -> ShowS
$cshow :: TmpVariables -> String
show :: TmpVariables -> String
$cshowList :: [TmpVariables] -> ShowS
showList :: [TmpVariables] -> ShowS
Show, TmpVariables -> TmpVariables -> Bool
(TmpVariables -> TmpVariables -> Bool)
-> (TmpVariables -> TmpVariables -> Bool) -> Eq TmpVariables
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TmpVariables -> TmpVariables -> Bool
== :: TmpVariables -> TmpVariables -> Bool
$c/= :: TmpVariables -> TmpVariables -> Bool
/= :: TmpVariables -> TmpVariables -> Bool
Eq, Eq TmpVariables
Eq TmpVariables
-> (TmpVariables -> TmpVariables -> Ordering)
-> (TmpVariables -> TmpVariables -> Bool)
-> (TmpVariables -> TmpVariables -> Bool)
-> (TmpVariables -> TmpVariables -> Bool)
-> (TmpVariables -> TmpVariables -> Bool)
-> (TmpVariables -> TmpVariables -> TmpVariables)
-> (TmpVariables -> TmpVariables -> TmpVariables)
-> Ord TmpVariables
TmpVariables -> TmpVariables -> Bool
TmpVariables -> TmpVariables -> Ordering
TmpVariables -> TmpVariables -> TmpVariables
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 :: TmpVariables -> TmpVariables -> Ordering
compare :: TmpVariables -> TmpVariables -> Ordering
$c< :: TmpVariables -> TmpVariables -> Bool
< :: TmpVariables -> TmpVariables -> Bool
$c<= :: TmpVariables -> TmpVariables -> Bool
<= :: TmpVariables -> TmpVariables -> Bool
$c> :: TmpVariables -> TmpVariables -> Bool
> :: TmpVariables -> TmpVariables -> Bool
$c>= :: TmpVariables -> TmpVariables -> Bool
>= :: TmpVariables -> TmpVariables -> Bool
$cmax :: TmpVariables -> TmpVariables -> TmpVariables
max :: TmpVariables -> TmpVariables -> TmpVariables
$cmin :: TmpVariables -> TmpVariables -> TmpVariables
min :: TmpVariables -> TmpVariables -> TmpVariables
Ord )
locationVariable :: Variable -> Location
locationVariable :: Variable -> Location
locationVariable Variable
v = case Variable
v of
(TmpVariableCtor TmpVariable
tmpVariable) -> TmpVariable -> Location
tmpVariableLocation TmpVariable
tmpVariable
(SrcVariableCtor SrcVariable
srcVariable) -> VarName -> Location
Token.getVarNameLocation (VarName -> Location) -> VarName -> Location
forall a b. (a -> b) -> a -> b
$ SrcVariable -> VarName
srcVariableToken SrcVariable
srcVariable
(ParamVariableCtor ParamVariable
_paramVariable) -> ParamName -> Location
Token.getParamNameLocation (ParamName -> Location) -> ParamName -> Location
forall a b. (a -> b) -> a -> b
$ ParamVariable -> ParamName
paramVariableToken ParamVariable
_paramVariable
(Arg ArgContent
argContent) -> ArgContent -> Location
argVariableMyAwesomeCallContext ArgContent
argContent
data CallContent
= CallContent
{
CallContent -> Variable
callOutput :: Variable,
CallContent -> Variable
callee :: Variable,
CallContent -> [Variable]
args :: [ Variable ],
CallContent -> Location
callLocation :: Location
}
deriving ( Int -> CallContent -> ShowS
[CallContent] -> ShowS
CallContent -> String
(Int -> CallContent -> ShowS)
-> (CallContent -> String)
-> ([CallContent] -> ShowS)
-> Show CallContent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CallContent -> ShowS
showsPrec :: Int -> CallContent -> ShowS
$cshow :: CallContent -> String
show :: CallContent -> String
$cshowList :: [CallContent] -> ShowS
showList :: [CallContent] -> ShowS
Show, CallContent -> CallContent -> Bool
(CallContent -> CallContent -> Bool)
-> (CallContent -> CallContent -> Bool) -> Eq CallContent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CallContent -> CallContent -> Bool
== :: CallContent -> CallContent -> Bool
$c/= :: CallContent -> CallContent -> Bool
/= :: CallContent -> CallContent -> Bool
Eq, (forall x. CallContent -> Rep CallContent x)
-> (forall x. Rep CallContent x -> CallContent)
-> Generic CallContent
forall x. Rep CallContent x -> CallContent
forall x. CallContent -> Rep CallContent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CallContent -> Rep CallContent x
from :: forall x. CallContent -> Rep CallContent x
$cto :: forall x. Rep CallContent x -> CallContent
to :: forall x. Rep CallContent x -> CallContent
Generic, [CallContent] -> Value
[CallContent] -> Encoding
CallContent -> Bool
CallContent -> Value
CallContent -> Encoding
(CallContent -> Value)
-> (CallContent -> Encoding)
-> ([CallContent] -> Value)
-> ([CallContent] -> Encoding)
-> (CallContent -> Bool)
-> ToJSON CallContent
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: CallContent -> Value
toJSON :: CallContent -> Value
$ctoEncoding :: CallContent -> Encoding
toEncoding :: CallContent -> Encoding
$ctoJSONList :: [CallContent] -> Value
toJSONList :: [CallContent] -> Value
$ctoEncodingList :: [CallContent] -> Encoding
toEncodingList :: [CallContent] -> Encoding
$comitField :: CallContent -> Bool
omitField :: CallContent -> Bool
ToJSON, Maybe CallContent
Value -> Parser [CallContent]
Value -> Parser CallContent
(Value -> Parser CallContent)
-> (Value -> Parser [CallContent])
-> Maybe CallContent
-> FromJSON CallContent
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser CallContent
parseJSON :: Value -> Parser CallContent
$cparseJSONList :: Value -> Parser [CallContent]
parseJSONList :: Value -> Parser [CallContent]
$comittedField :: Maybe CallContent
omittedField :: Maybe CallContent
FromJSON, Eq CallContent
Eq CallContent
-> (CallContent -> CallContent -> Ordering)
-> (CallContent -> CallContent -> Bool)
-> (CallContent -> CallContent -> Bool)
-> (CallContent -> CallContent -> Bool)
-> (CallContent -> CallContent -> Bool)
-> (CallContent -> CallContent -> CallContent)
-> (CallContent -> CallContent -> CallContent)
-> Ord CallContent
CallContent -> CallContent -> Bool
CallContent -> CallContent -> Ordering
CallContent -> CallContent -> CallContent
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 :: CallContent -> CallContent -> Ordering
compare :: CallContent -> CallContent -> Ordering
$c< :: CallContent -> CallContent -> Bool
< :: CallContent -> CallContent -> Bool
$c<= :: CallContent -> CallContent -> Bool
<= :: CallContent -> CallContent -> Bool
$c> :: CallContent -> CallContent -> Bool
> :: CallContent -> CallContent -> Bool
$c>= :: CallContent -> CallContent -> Bool
>= :: CallContent -> CallContent -> Bool
$cmax :: CallContent -> CallContent -> CallContent
max :: CallContent -> CallContent -> CallContent
$cmin :: CallContent -> CallContent -> CallContent
min :: CallContent -> CallContent -> CallContent
Ord )
data BinopContent
= BinopContent
{
BinopContent -> Variable
binopOutput :: Variable,
BinopContent -> Variable
binopLhs :: Variable,
BinopContent -> Variable
binopRhs :: Variable
}
deriving ( Int -> BinopContent -> ShowS
[BinopContent] -> ShowS
BinopContent -> String
(Int -> BinopContent -> ShowS)
-> (BinopContent -> String)
-> ([BinopContent] -> ShowS)
-> Show BinopContent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BinopContent -> ShowS
showsPrec :: Int -> BinopContent -> ShowS
$cshow :: BinopContent -> String
show :: BinopContent -> String
$cshowList :: [BinopContent] -> ShowS
showList :: [BinopContent] -> ShowS
Show, BinopContent -> BinopContent -> Bool
(BinopContent -> BinopContent -> Bool)
-> (BinopContent -> BinopContent -> Bool) -> Eq BinopContent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BinopContent -> BinopContent -> Bool
== :: BinopContent -> BinopContent -> Bool
$c/= :: BinopContent -> BinopContent -> Bool
/= :: BinopContent -> BinopContent -> Bool
Eq, (forall x. BinopContent -> Rep BinopContent x)
-> (forall x. Rep BinopContent x -> BinopContent)
-> Generic BinopContent
forall x. Rep BinopContent x -> BinopContent
forall x. BinopContent -> Rep BinopContent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. BinopContent -> Rep BinopContent x
from :: forall x. BinopContent -> Rep BinopContent x
$cto :: forall x. Rep BinopContent x -> BinopContent
to :: forall x. Rep BinopContent x -> BinopContent
Generic, [BinopContent] -> Value
[BinopContent] -> Encoding
BinopContent -> Bool
BinopContent -> Value
BinopContent -> Encoding
(BinopContent -> Value)
-> (BinopContent -> Encoding)
-> ([BinopContent] -> Value)
-> ([BinopContent] -> Encoding)
-> (BinopContent -> Bool)
-> ToJSON BinopContent
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: BinopContent -> Value
toJSON :: BinopContent -> Value
$ctoEncoding :: BinopContent -> Encoding
toEncoding :: BinopContent -> Encoding
$ctoJSONList :: [BinopContent] -> Value
toJSONList :: [BinopContent] -> Value
$ctoEncodingList :: [BinopContent] -> Encoding
toEncodingList :: [BinopContent] -> Encoding
$comitField :: BinopContent -> Bool
omitField :: BinopContent -> Bool
ToJSON, Maybe BinopContent
Value -> Parser [BinopContent]
Value -> Parser BinopContent
(Value -> Parser BinopContent)
-> (Value -> Parser [BinopContent])
-> Maybe BinopContent
-> FromJSON BinopContent
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser BinopContent
parseJSON :: Value -> Parser BinopContent
$cparseJSONList :: Value -> Parser [BinopContent]
parseJSONList :: Value -> Parser [BinopContent]
$comittedField :: Maybe BinopContent
omittedField :: Maybe BinopContent
FromJSON, Eq BinopContent
Eq BinopContent
-> (BinopContent -> BinopContent -> Ordering)
-> (BinopContent -> BinopContent -> Bool)
-> (BinopContent -> BinopContent -> Bool)
-> (BinopContent -> BinopContent -> Bool)
-> (BinopContent -> BinopContent -> Bool)
-> (BinopContent -> BinopContent -> BinopContent)
-> (BinopContent -> BinopContent -> BinopContent)
-> Ord BinopContent
BinopContent -> BinopContent -> Bool
BinopContent -> BinopContent -> Ordering
BinopContent -> BinopContent -> BinopContent
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 :: BinopContent -> BinopContent -> Ordering
compare :: BinopContent -> BinopContent -> Ordering
$c< :: BinopContent -> BinopContent -> Bool
< :: BinopContent -> BinopContent -> Bool
$c<= :: BinopContent -> BinopContent -> Bool
<= :: BinopContent -> BinopContent -> Bool
$c> :: BinopContent -> BinopContent -> Bool
> :: BinopContent -> BinopContent -> Bool
$c>= :: BinopContent -> BinopContent -> Bool
>= :: BinopContent -> BinopContent -> Bool
$cmax :: BinopContent -> BinopContent -> BinopContent
max :: BinopContent -> BinopContent -> BinopContent
$cmin :: BinopContent -> BinopContent -> BinopContent
min :: BinopContent -> BinopContent -> BinopContent
Ord )
data UnopContent
= UnopContent
{
UnopContent -> Variable
unopOutput :: Variable,
UnopContent -> Variable
unopLhs :: Variable
}
deriving ( Int -> UnopContent -> ShowS
[UnopContent] -> ShowS
UnopContent -> String
(Int -> UnopContent -> ShowS)
-> (UnopContent -> String)
-> ([UnopContent] -> ShowS)
-> Show UnopContent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UnopContent -> ShowS
showsPrec :: Int -> UnopContent -> ShowS
$cshow :: UnopContent -> String
show :: UnopContent -> String
$cshowList :: [UnopContent] -> ShowS
showList :: [UnopContent] -> ShowS
Show, UnopContent -> UnopContent -> Bool
(UnopContent -> UnopContent -> Bool)
-> (UnopContent -> UnopContent -> Bool) -> Eq UnopContent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UnopContent -> UnopContent -> Bool
== :: UnopContent -> UnopContent -> Bool
$c/= :: UnopContent -> UnopContent -> Bool
/= :: UnopContent -> UnopContent -> Bool
Eq, (forall x. UnopContent -> Rep UnopContent x)
-> (forall x. Rep UnopContent x -> UnopContent)
-> Generic UnopContent
forall x. Rep UnopContent x -> UnopContent
forall x. UnopContent -> Rep UnopContent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. UnopContent -> Rep UnopContent x
from :: forall x. UnopContent -> Rep UnopContent x
$cto :: forall x. Rep UnopContent x -> UnopContent
to :: forall x. Rep UnopContent x -> UnopContent
Generic, [UnopContent] -> Value
[UnopContent] -> Encoding
UnopContent -> Bool
UnopContent -> Value
UnopContent -> Encoding
(UnopContent -> Value)
-> (UnopContent -> Encoding)
-> ([UnopContent] -> Value)
-> ([UnopContent] -> Encoding)
-> (UnopContent -> Bool)
-> ToJSON UnopContent
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: UnopContent -> Value
toJSON :: UnopContent -> Value
$ctoEncoding :: UnopContent -> Encoding
toEncoding :: UnopContent -> Encoding
$ctoJSONList :: [UnopContent] -> Value
toJSONList :: [UnopContent] -> Value
$ctoEncodingList :: [UnopContent] -> Encoding
toEncodingList :: [UnopContent] -> Encoding
$comitField :: UnopContent -> Bool
omitField :: UnopContent -> Bool
ToJSON, Maybe UnopContent
Value -> Parser [UnopContent]
Value -> Parser UnopContent
(Value -> Parser UnopContent)
-> (Value -> Parser [UnopContent])
-> Maybe UnopContent
-> FromJSON UnopContent
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser UnopContent
parseJSON :: Value -> Parser UnopContent
$cparseJSONList :: Value -> Parser [UnopContent]
parseJSONList :: Value -> Parser [UnopContent]
$comittedField :: Maybe UnopContent
omittedField :: Maybe UnopContent
FromJSON, Eq UnopContent
Eq UnopContent
-> (UnopContent -> UnopContent -> Ordering)
-> (UnopContent -> UnopContent -> Bool)
-> (UnopContent -> UnopContent -> Bool)
-> (UnopContent -> UnopContent -> Bool)
-> (UnopContent -> UnopContent -> Bool)
-> (UnopContent -> UnopContent -> UnopContent)
-> (UnopContent -> UnopContent -> UnopContent)
-> Ord UnopContent
UnopContent -> UnopContent -> Bool
UnopContent -> UnopContent -> Ordering
UnopContent -> UnopContent -> UnopContent
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 :: UnopContent -> UnopContent -> Ordering
compare :: UnopContent -> UnopContent -> Ordering
$c< :: UnopContent -> UnopContent -> Bool
< :: UnopContent -> UnopContent -> Bool
$c<= :: UnopContent -> UnopContent -> Bool
<= :: UnopContent -> UnopContent -> Bool
$c> :: UnopContent -> UnopContent -> Bool
> :: UnopContent -> UnopContent -> Bool
$c>= :: UnopContent -> UnopContent -> Bool
>= :: UnopContent -> UnopContent -> Bool
$cmax :: UnopContent -> UnopContent -> UnopContent
max :: UnopContent -> UnopContent -> UnopContent
$cmin :: UnopContent -> UnopContent -> UnopContent
min :: UnopContent -> UnopContent -> UnopContent
Ord )
data AssumeContent
= AssumeContent
{
AssumeContent -> Variable
assumeVariable :: Variable,
AssumeContent -> Bool
assumedValue :: Bool
}
deriving ( Int -> AssumeContent -> ShowS
[AssumeContent] -> ShowS
AssumeContent -> String
(Int -> AssumeContent -> ShowS)
-> (AssumeContent -> String)
-> ([AssumeContent] -> ShowS)
-> Show AssumeContent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AssumeContent -> ShowS
showsPrec :: Int -> AssumeContent -> ShowS
$cshow :: AssumeContent -> String
show :: AssumeContent -> String
$cshowList :: [AssumeContent] -> ShowS
showList :: [AssumeContent] -> ShowS
Show, AssumeContent -> AssumeContent -> Bool
(AssumeContent -> AssumeContent -> Bool)
-> (AssumeContent -> AssumeContent -> Bool) -> Eq AssumeContent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AssumeContent -> AssumeContent -> Bool
== :: AssumeContent -> AssumeContent -> Bool
$c/= :: AssumeContent -> AssumeContent -> Bool
/= :: AssumeContent -> AssumeContent -> Bool
Eq, (forall x. AssumeContent -> Rep AssumeContent x)
-> (forall x. Rep AssumeContent x -> AssumeContent)
-> Generic AssumeContent
forall x. Rep AssumeContent x -> AssumeContent
forall x. AssumeContent -> Rep AssumeContent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AssumeContent -> Rep AssumeContent x
from :: forall x. AssumeContent -> Rep AssumeContent x
$cto :: forall x. Rep AssumeContent x -> AssumeContent
to :: forall x. Rep AssumeContent x -> AssumeContent
Generic, [AssumeContent] -> Value
[AssumeContent] -> Encoding
AssumeContent -> Bool
AssumeContent -> Value
AssumeContent -> Encoding
(AssumeContent -> Value)
-> (AssumeContent -> Encoding)
-> ([AssumeContent] -> Value)
-> ([AssumeContent] -> Encoding)
-> (AssumeContent -> Bool)
-> ToJSON AssumeContent
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: AssumeContent -> Value
toJSON :: AssumeContent -> Value
$ctoEncoding :: AssumeContent -> Encoding
toEncoding :: AssumeContent -> Encoding
$ctoJSONList :: [AssumeContent] -> Value
toJSONList :: [AssumeContent] -> Value
$ctoEncodingList :: [AssumeContent] -> Encoding
toEncodingList :: [AssumeContent] -> Encoding
$comitField :: AssumeContent -> Bool
omitField :: AssumeContent -> Bool
ToJSON, Maybe AssumeContent
Value -> Parser [AssumeContent]
Value -> Parser AssumeContent
(Value -> Parser AssumeContent)
-> (Value -> Parser [AssumeContent])
-> Maybe AssumeContent
-> FromJSON AssumeContent
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser AssumeContent
parseJSON :: Value -> Parser AssumeContent
$cparseJSONList :: Value -> Parser [AssumeContent]
parseJSONList :: Value -> Parser [AssumeContent]
$comittedField :: Maybe AssumeContent
omittedField :: Maybe AssumeContent
FromJSON, Eq AssumeContent
Eq AssumeContent
-> (AssumeContent -> AssumeContent -> Ordering)
-> (AssumeContent -> AssumeContent -> Bool)
-> (AssumeContent -> AssumeContent -> Bool)
-> (AssumeContent -> AssumeContent -> Bool)
-> (AssumeContent -> AssumeContent -> Bool)
-> (AssumeContent -> AssumeContent -> AssumeContent)
-> (AssumeContent -> AssumeContent -> AssumeContent)
-> Ord AssumeContent
AssumeContent -> AssumeContent -> Bool
AssumeContent -> AssumeContent -> Ordering
AssumeContent -> AssumeContent -> AssumeContent
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 :: AssumeContent -> AssumeContent -> Ordering
compare :: AssumeContent -> AssumeContent -> Ordering
$c< :: AssumeContent -> AssumeContent -> Bool
< :: AssumeContent -> AssumeContent -> Bool
$c<= :: AssumeContent -> AssumeContent -> Bool
<= :: AssumeContent -> AssumeContent -> Bool
$c> :: AssumeContent -> AssumeContent -> Bool
> :: AssumeContent -> AssumeContent -> Bool
$c>= :: AssumeContent -> AssumeContent -> Bool
>= :: AssumeContent -> AssumeContent -> Bool
$cmax :: AssumeContent -> AssumeContent -> AssumeContent
max :: AssumeContent -> AssumeContent -> AssumeContent
$cmin :: AssumeContent -> AssumeContent -> AssumeContent
min :: AssumeContent -> AssumeContent -> AssumeContent
Ord )
mkAssumeInstruction :: Variable -> Bool -> Instruction
mkAssumeInstruction :: Variable -> Bool -> Instruction
mkAssumeInstruction Variable
v Bool
b = Location -> InstructionContent -> Instruction
Instruction (Variable -> Location
locationVariable Variable
v) (AssumeContent -> InstructionContent
Assume (Variable -> Bool -> AssumeContent
AssumeContent Variable
v Bool
b))
data ReturnContent
= ReturnContent
{
ReturnContent -> Maybe Variable
returnValue :: Maybe Variable
}
deriving ( Int -> ReturnContent -> ShowS
[ReturnContent] -> ShowS
ReturnContent -> String
(Int -> ReturnContent -> ShowS)
-> (ReturnContent -> String)
-> ([ReturnContent] -> ShowS)
-> Show ReturnContent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ReturnContent -> ShowS
showsPrec :: Int -> ReturnContent -> ShowS
$cshow :: ReturnContent -> String
show :: ReturnContent -> String
$cshowList :: [ReturnContent] -> ShowS
showList :: [ReturnContent] -> ShowS
Show, ReturnContent -> ReturnContent -> Bool
(ReturnContent -> ReturnContent -> Bool)
-> (ReturnContent -> ReturnContent -> Bool) -> Eq ReturnContent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ReturnContent -> ReturnContent -> Bool
== :: ReturnContent -> ReturnContent -> Bool
$c/= :: ReturnContent -> ReturnContent -> Bool
/= :: ReturnContent -> ReturnContent -> Bool
Eq, (forall x. ReturnContent -> Rep ReturnContent x)
-> (forall x. Rep ReturnContent x -> ReturnContent)
-> Generic ReturnContent
forall x. Rep ReturnContent x -> ReturnContent
forall x. ReturnContent -> Rep ReturnContent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ReturnContent -> Rep ReturnContent x
from :: forall x. ReturnContent -> Rep ReturnContent x
$cto :: forall x. Rep ReturnContent x -> ReturnContent
to :: forall x. Rep ReturnContent x -> ReturnContent
Generic, [ReturnContent] -> Value
[ReturnContent] -> Encoding
ReturnContent -> Bool
ReturnContent -> Value
ReturnContent -> Encoding
(ReturnContent -> Value)
-> (ReturnContent -> Encoding)
-> ([ReturnContent] -> Value)
-> ([ReturnContent] -> Encoding)
-> (ReturnContent -> Bool)
-> ToJSON ReturnContent
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: ReturnContent -> Value
toJSON :: ReturnContent -> Value
$ctoEncoding :: ReturnContent -> Encoding
toEncoding :: ReturnContent -> Encoding
$ctoJSONList :: [ReturnContent] -> Value
toJSONList :: [ReturnContent] -> Value
$ctoEncodingList :: [ReturnContent] -> Encoding
toEncodingList :: [ReturnContent] -> Encoding
$comitField :: ReturnContent -> Bool
omitField :: ReturnContent -> Bool
ToJSON, Maybe ReturnContent
Value -> Parser [ReturnContent]
Value -> Parser ReturnContent
(Value -> Parser ReturnContent)
-> (Value -> Parser [ReturnContent])
-> Maybe ReturnContent
-> FromJSON ReturnContent
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser ReturnContent
parseJSON :: Value -> Parser ReturnContent
$cparseJSONList :: Value -> Parser [ReturnContent]
parseJSONList :: Value -> Parser [ReturnContent]
$comittedField :: Maybe ReturnContent
omittedField :: Maybe ReturnContent
FromJSON, Eq ReturnContent
Eq ReturnContent
-> (ReturnContent -> ReturnContent -> Ordering)
-> (ReturnContent -> ReturnContent -> Bool)
-> (ReturnContent -> ReturnContent -> Bool)
-> (ReturnContent -> ReturnContent -> Bool)
-> (ReturnContent -> ReturnContent -> Bool)
-> (ReturnContent -> ReturnContent -> ReturnContent)
-> (ReturnContent -> ReturnContent -> ReturnContent)
-> Ord ReturnContent
ReturnContent -> ReturnContent -> Bool
ReturnContent -> ReturnContent -> Ordering
ReturnContent -> ReturnContent -> ReturnContent
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 :: ReturnContent -> ReturnContent -> Ordering
compare :: ReturnContent -> ReturnContent -> Ordering
$c< :: ReturnContent -> ReturnContent -> Bool
< :: ReturnContent -> ReturnContent -> Bool
$c<= :: ReturnContent -> ReturnContent -> Bool
<= :: ReturnContent -> ReturnContent -> Bool
$c> :: ReturnContent -> ReturnContent -> Bool
> :: ReturnContent -> ReturnContent -> Bool
$c>= :: ReturnContent -> ReturnContent -> Bool
>= :: ReturnContent -> ReturnContent -> Bool
$cmax :: ReturnContent -> ReturnContent -> ReturnContent
max :: ReturnContent -> ReturnContent -> ReturnContent
$cmin :: ReturnContent -> ReturnContent -> ReturnContent
min :: ReturnContent -> ReturnContent -> ReturnContent
Ord )
data AssignContent
= AssignContent
{
AssignContent -> Variable
assignOutput :: Variable,
AssignContent -> Variable
assignInput :: Variable
}
deriving ( Int -> AssignContent -> ShowS
[AssignContent] -> ShowS
AssignContent -> String
(Int -> AssignContent -> ShowS)
-> (AssignContent -> String)
-> ([AssignContent] -> ShowS)
-> Show AssignContent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AssignContent -> ShowS
showsPrec :: Int -> AssignContent -> ShowS
$cshow :: AssignContent -> String
show :: AssignContent -> String
$cshowList :: [AssignContent] -> ShowS
showList :: [AssignContent] -> ShowS
Show, AssignContent -> AssignContent -> Bool
(AssignContent -> AssignContent -> Bool)
-> (AssignContent -> AssignContent -> Bool) -> Eq AssignContent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AssignContent -> AssignContent -> Bool
== :: AssignContent -> AssignContent -> Bool
$c/= :: AssignContent -> AssignContent -> Bool
/= :: AssignContent -> AssignContent -> Bool
Eq, (forall x. AssignContent -> Rep AssignContent x)
-> (forall x. Rep AssignContent x -> AssignContent)
-> Generic AssignContent
forall x. Rep AssignContent x -> AssignContent
forall x. AssignContent -> Rep AssignContent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AssignContent -> Rep AssignContent x
from :: forall x. AssignContent -> Rep AssignContent x
$cto :: forall x. Rep AssignContent x -> AssignContent
to :: forall x. Rep AssignContent x -> AssignContent
Generic, [AssignContent] -> Value
[AssignContent] -> Encoding
AssignContent -> Bool
AssignContent -> Value
AssignContent -> Encoding
(AssignContent -> Value)
-> (AssignContent -> Encoding)
-> ([AssignContent] -> Value)
-> ([AssignContent] -> Encoding)
-> (AssignContent -> Bool)
-> ToJSON AssignContent
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: AssignContent -> Value
toJSON :: AssignContent -> Value
$ctoEncoding :: AssignContent -> Encoding
toEncoding :: AssignContent -> Encoding
$ctoJSONList :: [AssignContent] -> Value
toJSONList :: [AssignContent] -> Value
$ctoEncodingList :: [AssignContent] -> Encoding
toEncodingList :: [AssignContent] -> Encoding
$comitField :: AssignContent -> Bool
omitField :: AssignContent -> Bool
ToJSON, Maybe AssignContent
Value -> Parser [AssignContent]
Value -> Parser AssignContent
(Value -> Parser AssignContent)
-> (Value -> Parser [AssignContent])
-> Maybe AssignContent
-> FromJSON AssignContent
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser AssignContent
parseJSON :: Value -> Parser AssignContent
$cparseJSONList :: Value -> Parser [AssignContent]
parseJSONList :: Value -> Parser [AssignContent]
$comittedField :: Maybe AssignContent
omittedField :: Maybe AssignContent
FromJSON, Eq AssignContent
Eq AssignContent
-> (AssignContent -> AssignContent -> Ordering)
-> (AssignContent -> AssignContent -> Bool)
-> (AssignContent -> AssignContent -> Bool)
-> (AssignContent -> AssignContent -> Bool)
-> (AssignContent -> AssignContent -> Bool)
-> (AssignContent -> AssignContent -> AssignContent)
-> (AssignContent -> AssignContent -> AssignContent)
-> Ord AssignContent
AssignContent -> AssignContent -> Bool
AssignContent -> AssignContent -> Ordering
AssignContent -> AssignContent -> AssignContent
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 :: AssignContent -> AssignContent -> Ordering
compare :: AssignContent -> AssignContent -> Ordering
$c< :: AssignContent -> AssignContent -> Bool
< :: AssignContent -> AssignContent -> Bool
$c<= :: AssignContent -> AssignContent -> Bool
<= :: AssignContent -> AssignContent -> Bool
$c> :: AssignContent -> AssignContent -> Bool
> :: AssignContent -> AssignContent -> Bool
$c>= :: AssignContent -> AssignContent -> Bool
>= :: AssignContent -> AssignContent -> Bool
$cmax :: AssignContent -> AssignContent -> AssignContent
max :: AssignContent -> AssignContent -> AssignContent
$cmin :: AssignContent -> AssignContent -> AssignContent
min :: AssignContent -> AssignContent -> AssignContent
Ord )
data IntContent
= IntContent
{
IntContent -> TmpVariable
loadImmIntOutput :: TmpVariable,
IntContent -> ConstInt
loadImmIntValue :: Token.ConstInt
}
deriving ( Int -> IntContent -> ShowS
[IntContent] -> ShowS
IntContent -> String
(Int -> IntContent -> ShowS)
-> (IntContent -> String)
-> ([IntContent] -> ShowS)
-> Show IntContent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IntContent -> ShowS
showsPrec :: Int -> IntContent -> ShowS
$cshow :: IntContent -> String
show :: IntContent -> String
$cshowList :: [IntContent] -> ShowS
showList :: [IntContent] -> ShowS
Show, IntContent -> IntContent -> Bool
(IntContent -> IntContent -> Bool)
-> (IntContent -> IntContent -> Bool) -> Eq IntContent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IntContent -> IntContent -> Bool
== :: IntContent -> IntContent -> Bool
$c/= :: IntContent -> IntContent -> Bool
/= :: IntContent -> IntContent -> Bool
Eq, (forall x. IntContent -> Rep IntContent x)
-> (forall x. Rep IntContent x -> IntContent) -> Generic IntContent
forall x. Rep IntContent x -> IntContent
forall x. IntContent -> Rep IntContent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. IntContent -> Rep IntContent x
from :: forall x. IntContent -> Rep IntContent x
$cto :: forall x. Rep IntContent x -> IntContent
to :: forall x. Rep IntContent x -> IntContent
Generic, [IntContent] -> Value
[IntContent] -> Encoding
IntContent -> Bool
IntContent -> Value
IntContent -> Encoding
(IntContent -> Value)
-> (IntContent -> Encoding)
-> ([IntContent] -> Value)
-> ([IntContent] -> Encoding)
-> (IntContent -> Bool)
-> ToJSON IntContent
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: IntContent -> Value
toJSON :: IntContent -> Value
$ctoEncoding :: IntContent -> Encoding
toEncoding :: IntContent -> Encoding
$ctoJSONList :: [IntContent] -> Value
toJSONList :: [IntContent] -> Value
$ctoEncodingList :: [IntContent] -> Encoding
toEncodingList :: [IntContent] -> Encoding
$comitField :: IntContent -> Bool
omitField :: IntContent -> Bool
ToJSON, Maybe IntContent
Value -> Parser [IntContent]
Value -> Parser IntContent
(Value -> Parser IntContent)
-> (Value -> Parser [IntContent])
-> Maybe IntContent
-> FromJSON IntContent
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser IntContent
parseJSON :: Value -> Parser IntContent
$cparseJSONList :: Value -> Parser [IntContent]
parseJSONList :: Value -> Parser [IntContent]
$comittedField :: Maybe IntContent
omittedField :: Maybe IntContent
FromJSON, Eq IntContent
Eq IntContent
-> (IntContent -> IntContent -> Ordering)
-> (IntContent -> IntContent -> Bool)
-> (IntContent -> IntContent -> Bool)
-> (IntContent -> IntContent -> Bool)
-> (IntContent -> IntContent -> Bool)
-> (IntContent -> IntContent -> IntContent)
-> (IntContent -> IntContent -> IntContent)
-> Ord IntContent
IntContent -> IntContent -> Bool
IntContent -> IntContent -> Ordering
IntContent -> IntContent -> IntContent
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 :: IntContent -> IntContent -> Ordering
compare :: IntContent -> IntContent -> Ordering
$c< :: IntContent -> IntContent -> Bool
< :: IntContent -> IntContent -> Bool
$c<= :: IntContent -> IntContent -> Bool
<= :: IntContent -> IntContent -> Bool
$c> :: IntContent -> IntContent -> Bool
> :: IntContent -> IntContent -> Bool
$c>= :: IntContent -> IntContent -> Bool
>= :: IntContent -> IntContent -> Bool
$cmax :: IntContent -> IntContent -> IntContent
max :: IntContent -> IntContent -> IntContent
$cmin :: IntContent -> IntContent -> IntContent
min :: IntContent -> IntContent -> IntContent
Ord )
data StrContent
= StrContent
{
StrContent -> TmpVariable
loadImmStrOutput :: TmpVariable,
StrContent -> ConstStr
loadImmStrValue :: Token.ConstStr
}
deriving ( Int -> StrContent -> ShowS
[StrContent] -> ShowS
StrContent -> String
(Int -> StrContent -> ShowS)
-> (StrContent -> String)
-> ([StrContent] -> ShowS)
-> Show StrContent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StrContent -> ShowS
showsPrec :: Int -> StrContent -> ShowS
$cshow :: StrContent -> String
show :: StrContent -> String
$cshowList :: [StrContent] -> ShowS
showList :: [StrContent] -> ShowS
Show, StrContent -> StrContent -> Bool
(StrContent -> StrContent -> Bool)
-> (StrContent -> StrContent -> Bool) -> Eq StrContent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StrContent -> StrContent -> Bool
== :: StrContent -> StrContent -> Bool
$c/= :: StrContent -> StrContent -> Bool
/= :: StrContent -> StrContent -> Bool
Eq, (forall x. StrContent -> Rep StrContent x)
-> (forall x. Rep StrContent x -> StrContent) -> Generic StrContent
forall x. Rep StrContent x -> StrContent
forall x. StrContent -> Rep StrContent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. StrContent -> Rep StrContent x
from :: forall x. StrContent -> Rep StrContent x
$cto :: forall x. Rep StrContent x -> StrContent
to :: forall x. Rep StrContent x -> StrContent
Generic, [StrContent] -> Value
[StrContent] -> Encoding
StrContent -> Bool
StrContent -> Value
StrContent -> Encoding
(StrContent -> Value)
-> (StrContent -> Encoding)
-> ([StrContent] -> Value)
-> ([StrContent] -> Encoding)
-> (StrContent -> Bool)
-> ToJSON StrContent
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: StrContent -> Value
toJSON :: StrContent -> Value
$ctoEncoding :: StrContent -> Encoding
toEncoding :: StrContent -> Encoding
$ctoJSONList :: [StrContent] -> Value
toJSONList :: [StrContent] -> Value
$ctoEncodingList :: [StrContent] -> Encoding
toEncodingList :: [StrContent] -> Encoding
$comitField :: StrContent -> Bool
omitField :: StrContent -> Bool
ToJSON, Maybe StrContent
Value -> Parser [StrContent]
Value -> Parser StrContent
(Value -> Parser StrContent)
-> (Value -> Parser [StrContent])
-> Maybe StrContent
-> FromJSON StrContent
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser StrContent
parseJSON :: Value -> Parser StrContent
$cparseJSONList :: Value -> Parser [StrContent]
parseJSONList :: Value -> Parser [StrContent]
$comittedField :: Maybe StrContent
omittedField :: Maybe StrContent
FromJSON, Eq StrContent
Eq StrContent
-> (StrContent -> StrContent -> Ordering)
-> (StrContent -> StrContent -> Bool)
-> (StrContent -> StrContent -> Bool)
-> (StrContent -> StrContent -> Bool)
-> (StrContent -> StrContent -> Bool)
-> (StrContent -> StrContent -> StrContent)
-> (StrContent -> StrContent -> StrContent)
-> Ord StrContent
StrContent -> StrContent -> Bool
StrContent -> StrContent -> Ordering
StrContent -> StrContent -> StrContent
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 :: StrContent -> StrContent -> Ordering
compare :: StrContent -> StrContent -> Ordering
$c< :: StrContent -> StrContent -> Bool
< :: StrContent -> StrContent -> Bool
$c<= :: StrContent -> StrContent -> Bool
<= :: StrContent -> StrContent -> Bool
$c> :: StrContent -> StrContent -> Bool
> :: StrContent -> StrContent -> Bool
$c>= :: StrContent -> StrContent -> Bool
>= :: StrContent -> StrContent -> Bool
$cmax :: StrContent -> StrContent -> StrContent
max :: StrContent -> StrContent -> StrContent
$cmin :: StrContent -> StrContent -> StrContent
min :: StrContent -> StrContent -> StrContent
Ord )
data BoolContent
= BoolContent
{
BoolContent -> TmpVariable
loadImmBoolOutput :: TmpVariable,
BoolContent -> ConstBool
loadImmBoolValue :: Token.ConstBool
}
deriving ( Int -> BoolContent -> ShowS
[BoolContent] -> ShowS
BoolContent -> String
(Int -> BoolContent -> ShowS)
-> (BoolContent -> String)
-> ([BoolContent] -> ShowS)
-> Show BoolContent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BoolContent -> ShowS
showsPrec :: Int -> BoolContent -> ShowS
$cshow :: BoolContent -> String
show :: BoolContent -> String
$cshowList :: [BoolContent] -> ShowS
showList :: [BoolContent] -> ShowS
Show, BoolContent -> BoolContent -> Bool
(BoolContent -> BoolContent -> Bool)
-> (BoolContent -> BoolContent -> Bool) -> Eq BoolContent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BoolContent -> BoolContent -> Bool
== :: BoolContent -> BoolContent -> Bool
$c/= :: BoolContent -> BoolContent -> Bool
/= :: BoolContent -> BoolContent -> Bool
Eq, (forall x. BoolContent -> Rep BoolContent x)
-> (forall x. Rep BoolContent x -> BoolContent)
-> Generic BoolContent
forall x. Rep BoolContent x -> BoolContent
forall x. BoolContent -> Rep BoolContent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. BoolContent -> Rep BoolContent x
from :: forall x. BoolContent -> Rep BoolContent x
$cto :: forall x. Rep BoolContent x -> BoolContent
to :: forall x. Rep BoolContent x -> BoolContent
Generic, [BoolContent] -> Value
[BoolContent] -> Encoding
BoolContent -> Bool
BoolContent -> Value
BoolContent -> Encoding
(BoolContent -> Value)
-> (BoolContent -> Encoding)
-> ([BoolContent] -> Value)
-> ([BoolContent] -> Encoding)
-> (BoolContent -> Bool)
-> ToJSON BoolContent
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: BoolContent -> Value
toJSON :: BoolContent -> Value
$ctoEncoding :: BoolContent -> Encoding
toEncoding :: BoolContent -> Encoding
$ctoJSONList :: [BoolContent] -> Value
toJSONList :: [BoolContent] -> Value
$ctoEncodingList :: [BoolContent] -> Encoding
toEncodingList :: [BoolContent] -> Encoding
$comitField :: BoolContent -> Bool
omitField :: BoolContent -> Bool
ToJSON, Maybe BoolContent
Value -> Parser [BoolContent]
Value -> Parser BoolContent
(Value -> Parser BoolContent)
-> (Value -> Parser [BoolContent])
-> Maybe BoolContent
-> FromJSON BoolContent
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser BoolContent
parseJSON :: Value -> Parser BoolContent
$cparseJSONList :: Value -> Parser [BoolContent]
parseJSONList :: Value -> Parser [BoolContent]
$comittedField :: Maybe BoolContent
omittedField :: Maybe BoolContent
FromJSON, Eq BoolContent
Eq BoolContent
-> (BoolContent -> BoolContent -> Ordering)
-> (BoolContent -> BoolContent -> Bool)
-> (BoolContent -> BoolContent -> Bool)
-> (BoolContent -> BoolContent -> Bool)
-> (BoolContent -> BoolContent -> Bool)
-> (BoolContent -> BoolContent -> BoolContent)
-> (BoolContent -> BoolContent -> BoolContent)
-> Ord BoolContent
BoolContent -> BoolContent -> Bool
BoolContent -> BoolContent -> Ordering
BoolContent -> BoolContent -> BoolContent
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 :: BoolContent -> BoolContent -> Ordering
compare :: BoolContent -> BoolContent -> Ordering
$c< :: BoolContent -> BoolContent -> Bool
< :: BoolContent -> BoolContent -> Bool
$c<= :: BoolContent -> BoolContent -> Bool
<= :: BoolContent -> BoolContent -> Bool
$c> :: BoolContent -> BoolContent -> Bool
> :: BoolContent -> BoolContent -> Bool
$c>= :: BoolContent -> BoolContent -> Bool
>= :: BoolContent -> BoolContent -> Bool
$cmax :: BoolContent -> BoolContent -> BoolContent
max :: BoolContent -> BoolContent -> BoolContent
$cmin :: BoolContent -> BoolContent -> BoolContent
min :: BoolContent -> BoolContent -> BoolContent
Ord )
data FieldReadContent
= FieldReadContent
{
FieldReadContent -> Variable
fieldReadOutput :: Variable,
FieldReadContent -> Variable
fieldReadInput :: Variable,
FieldReadContent -> FieldName
fieldReadName :: Token.FieldName
}
deriving ( Int -> FieldReadContent -> ShowS
[FieldReadContent] -> ShowS
FieldReadContent -> String
(Int -> FieldReadContent -> ShowS)
-> (FieldReadContent -> String)
-> ([FieldReadContent] -> ShowS)
-> Show FieldReadContent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FieldReadContent -> ShowS
showsPrec :: Int -> FieldReadContent -> ShowS
$cshow :: FieldReadContent -> String
show :: FieldReadContent -> String
$cshowList :: [FieldReadContent] -> ShowS
showList :: [FieldReadContent] -> ShowS
Show, FieldReadContent -> FieldReadContent -> Bool
(FieldReadContent -> FieldReadContent -> Bool)
-> (FieldReadContent -> FieldReadContent -> Bool)
-> Eq FieldReadContent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FieldReadContent -> FieldReadContent -> Bool
== :: FieldReadContent -> FieldReadContent -> Bool
$c/= :: FieldReadContent -> FieldReadContent -> Bool
/= :: FieldReadContent -> FieldReadContent -> Bool
Eq, (forall x. FieldReadContent -> Rep FieldReadContent x)
-> (forall x. Rep FieldReadContent x -> FieldReadContent)
-> Generic FieldReadContent
forall x. Rep FieldReadContent x -> FieldReadContent
forall x. FieldReadContent -> Rep FieldReadContent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. FieldReadContent -> Rep FieldReadContent x
from :: forall x. FieldReadContent -> Rep FieldReadContent x
$cto :: forall x. Rep FieldReadContent x -> FieldReadContent
to :: forall x. Rep FieldReadContent x -> FieldReadContent
Generic, [FieldReadContent] -> Value
[FieldReadContent] -> Encoding
FieldReadContent -> Bool
FieldReadContent -> Value
FieldReadContent -> Encoding
(FieldReadContent -> Value)
-> (FieldReadContent -> Encoding)
-> ([FieldReadContent] -> Value)
-> ([FieldReadContent] -> Encoding)
-> (FieldReadContent -> Bool)
-> ToJSON FieldReadContent
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: FieldReadContent -> Value
toJSON :: FieldReadContent -> Value
$ctoEncoding :: FieldReadContent -> Encoding
toEncoding :: FieldReadContent -> Encoding
$ctoJSONList :: [FieldReadContent] -> Value
toJSONList :: [FieldReadContent] -> Value
$ctoEncodingList :: [FieldReadContent] -> Encoding
toEncodingList :: [FieldReadContent] -> Encoding
$comitField :: FieldReadContent -> Bool
omitField :: FieldReadContent -> Bool
ToJSON, Maybe FieldReadContent
Value -> Parser [FieldReadContent]
Value -> Parser FieldReadContent
(Value -> Parser FieldReadContent)
-> (Value -> Parser [FieldReadContent])
-> Maybe FieldReadContent
-> FromJSON FieldReadContent
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser FieldReadContent
parseJSON :: Value -> Parser FieldReadContent
$cparseJSONList :: Value -> Parser [FieldReadContent]
parseJSONList :: Value -> Parser [FieldReadContent]
$comittedField :: Maybe FieldReadContent
omittedField :: Maybe FieldReadContent
FromJSON, Eq FieldReadContent
Eq FieldReadContent
-> (FieldReadContent -> FieldReadContent -> Ordering)
-> (FieldReadContent -> FieldReadContent -> Bool)
-> (FieldReadContent -> FieldReadContent -> Bool)
-> (FieldReadContent -> FieldReadContent -> Bool)
-> (FieldReadContent -> FieldReadContent -> Bool)
-> (FieldReadContent -> FieldReadContent -> FieldReadContent)
-> (FieldReadContent -> FieldReadContent -> FieldReadContent)
-> Ord FieldReadContent
FieldReadContent -> FieldReadContent -> Bool
FieldReadContent -> FieldReadContent -> Ordering
FieldReadContent -> FieldReadContent -> FieldReadContent
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 :: FieldReadContent -> FieldReadContent -> Ordering
compare :: FieldReadContent -> FieldReadContent -> Ordering
$c< :: FieldReadContent -> FieldReadContent -> Bool
< :: FieldReadContent -> FieldReadContent -> Bool
$c<= :: FieldReadContent -> FieldReadContent -> Bool
<= :: FieldReadContent -> FieldReadContent -> Bool
$c> :: FieldReadContent -> FieldReadContent -> Bool
> :: FieldReadContent -> FieldReadContent -> Bool
$c>= :: FieldReadContent -> FieldReadContent -> Bool
>= :: FieldReadContent -> FieldReadContent -> Bool
$cmax :: FieldReadContent -> FieldReadContent -> FieldReadContent
max :: FieldReadContent -> FieldReadContent -> FieldReadContent
$cmin :: FieldReadContent -> FieldReadContent -> FieldReadContent
min :: FieldReadContent -> FieldReadContent -> FieldReadContent
Ord )
data FieldWriteContent
= FieldWriteContent
{
FieldWriteContent -> Variable
fieldWriteOutput :: Variable,
FieldWriteContent -> FieldName
fieldWriteName :: Token.FieldName,
FieldWriteContent -> Variable
fieldWriteInput :: Variable
}
deriving ( Int -> FieldWriteContent -> ShowS
[FieldWriteContent] -> ShowS
FieldWriteContent -> String
(Int -> FieldWriteContent -> ShowS)
-> (FieldWriteContent -> String)
-> ([FieldWriteContent] -> ShowS)
-> Show FieldWriteContent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FieldWriteContent -> ShowS
showsPrec :: Int -> FieldWriteContent -> ShowS
$cshow :: FieldWriteContent -> String
show :: FieldWriteContent -> String
$cshowList :: [FieldWriteContent] -> ShowS
showList :: [FieldWriteContent] -> ShowS
Show, FieldWriteContent -> FieldWriteContent -> Bool
(FieldWriteContent -> FieldWriteContent -> Bool)
-> (FieldWriteContent -> FieldWriteContent -> Bool)
-> Eq FieldWriteContent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FieldWriteContent -> FieldWriteContent -> Bool
== :: FieldWriteContent -> FieldWriteContent -> Bool
$c/= :: FieldWriteContent -> FieldWriteContent -> Bool
/= :: FieldWriteContent -> FieldWriteContent -> Bool
Eq, (forall x. FieldWriteContent -> Rep FieldWriteContent x)
-> (forall x. Rep FieldWriteContent x -> FieldWriteContent)
-> Generic FieldWriteContent
forall x. Rep FieldWriteContent x -> FieldWriteContent
forall x. FieldWriteContent -> Rep FieldWriteContent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. FieldWriteContent -> Rep FieldWriteContent x
from :: forall x. FieldWriteContent -> Rep FieldWriteContent x
$cto :: forall x. Rep FieldWriteContent x -> FieldWriteContent
to :: forall x. Rep FieldWriteContent x -> FieldWriteContent
Generic, [FieldWriteContent] -> Value
[FieldWriteContent] -> Encoding
FieldWriteContent -> Bool
FieldWriteContent -> Value
FieldWriteContent -> Encoding
(FieldWriteContent -> Value)
-> (FieldWriteContent -> Encoding)
-> ([FieldWriteContent] -> Value)
-> ([FieldWriteContent] -> Encoding)
-> (FieldWriteContent -> Bool)
-> ToJSON FieldWriteContent
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: FieldWriteContent -> Value
toJSON :: FieldWriteContent -> Value
$ctoEncoding :: FieldWriteContent -> Encoding
toEncoding :: FieldWriteContent -> Encoding
$ctoJSONList :: [FieldWriteContent] -> Value
toJSONList :: [FieldWriteContent] -> Value
$ctoEncodingList :: [FieldWriteContent] -> Encoding
toEncodingList :: [FieldWriteContent] -> Encoding
$comitField :: FieldWriteContent -> Bool
omitField :: FieldWriteContent -> Bool
ToJSON, Maybe FieldWriteContent
Value -> Parser [FieldWriteContent]
Value -> Parser FieldWriteContent
(Value -> Parser FieldWriteContent)
-> (Value -> Parser [FieldWriteContent])
-> Maybe FieldWriteContent
-> FromJSON FieldWriteContent
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser FieldWriteContent
parseJSON :: Value -> Parser FieldWriteContent
$cparseJSONList :: Value -> Parser [FieldWriteContent]
parseJSONList :: Value -> Parser [FieldWriteContent]
$comittedField :: Maybe FieldWriteContent
omittedField :: Maybe FieldWriteContent
FromJSON, Eq FieldWriteContent
Eq FieldWriteContent
-> (FieldWriteContent -> FieldWriteContent -> Ordering)
-> (FieldWriteContent -> FieldWriteContent -> Bool)
-> (FieldWriteContent -> FieldWriteContent -> Bool)
-> (FieldWriteContent -> FieldWriteContent -> Bool)
-> (FieldWriteContent -> FieldWriteContent -> Bool)
-> (FieldWriteContent -> FieldWriteContent -> FieldWriteContent)
-> (FieldWriteContent -> FieldWriteContent -> FieldWriteContent)
-> Ord FieldWriteContent
FieldWriteContent -> FieldWriteContent -> Bool
FieldWriteContent -> FieldWriteContent -> Ordering
FieldWriteContent -> FieldWriteContent -> FieldWriteContent
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 :: FieldWriteContent -> FieldWriteContent -> Ordering
compare :: FieldWriteContent -> FieldWriteContent -> Ordering
$c< :: FieldWriteContent -> FieldWriteContent -> Bool
< :: FieldWriteContent -> FieldWriteContent -> Bool
$c<= :: FieldWriteContent -> FieldWriteContent -> Bool
<= :: FieldWriteContent -> FieldWriteContent -> Bool
$c> :: FieldWriteContent -> FieldWriteContent -> Bool
> :: FieldWriteContent -> FieldWriteContent -> Bool
$c>= :: FieldWriteContent -> FieldWriteContent -> Bool
>= :: FieldWriteContent -> FieldWriteContent -> Bool
$cmax :: FieldWriteContent -> FieldWriteContent -> FieldWriteContent
max :: FieldWriteContent -> FieldWriteContent -> FieldWriteContent
$cmin :: FieldWriteContent -> FieldWriteContent -> FieldWriteContent
min :: FieldWriteContent -> FieldWriteContent -> FieldWriteContent
Ord )
data SubscriptReadContent
= SubscriptReadContent
{
SubscriptReadContent -> Variable
subscriptReadOutput :: Variable,
SubscriptReadContent -> Variable
subscriptReadInput :: Variable,
SubscriptReadContent -> Variable
subscriptReadIdx :: Variable
}
deriving ( Int -> SubscriptReadContent -> ShowS
[SubscriptReadContent] -> ShowS
SubscriptReadContent -> String
(Int -> SubscriptReadContent -> ShowS)
-> (SubscriptReadContent -> String)
-> ([SubscriptReadContent] -> ShowS)
-> Show SubscriptReadContent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SubscriptReadContent -> ShowS
showsPrec :: Int -> SubscriptReadContent -> ShowS
$cshow :: SubscriptReadContent -> String
show :: SubscriptReadContent -> String
$cshowList :: [SubscriptReadContent] -> ShowS
showList :: [SubscriptReadContent] -> ShowS
Show, SubscriptReadContent -> SubscriptReadContent -> Bool
(SubscriptReadContent -> SubscriptReadContent -> Bool)
-> (SubscriptReadContent -> SubscriptReadContent -> Bool)
-> Eq SubscriptReadContent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SubscriptReadContent -> SubscriptReadContent -> Bool
== :: SubscriptReadContent -> SubscriptReadContent -> Bool
$c/= :: SubscriptReadContent -> SubscriptReadContent -> Bool
/= :: SubscriptReadContent -> SubscriptReadContent -> Bool
Eq, (forall x. SubscriptReadContent -> Rep SubscriptReadContent x)
-> (forall x. Rep SubscriptReadContent x -> SubscriptReadContent)
-> Generic SubscriptReadContent
forall x. Rep SubscriptReadContent x -> SubscriptReadContent
forall x. SubscriptReadContent -> Rep SubscriptReadContent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SubscriptReadContent -> Rep SubscriptReadContent x
from :: forall x. SubscriptReadContent -> Rep SubscriptReadContent x
$cto :: forall x. Rep SubscriptReadContent x -> SubscriptReadContent
to :: forall x. Rep SubscriptReadContent x -> SubscriptReadContent
Generic, [SubscriptReadContent] -> Value
[SubscriptReadContent] -> Encoding
SubscriptReadContent -> Bool
SubscriptReadContent -> Value
SubscriptReadContent -> Encoding
(SubscriptReadContent -> Value)
-> (SubscriptReadContent -> Encoding)
-> ([SubscriptReadContent] -> Value)
-> ([SubscriptReadContent] -> Encoding)
-> (SubscriptReadContent -> Bool)
-> ToJSON SubscriptReadContent
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: SubscriptReadContent -> Value
toJSON :: SubscriptReadContent -> Value
$ctoEncoding :: SubscriptReadContent -> Encoding
toEncoding :: SubscriptReadContent -> Encoding
$ctoJSONList :: [SubscriptReadContent] -> Value
toJSONList :: [SubscriptReadContent] -> Value
$ctoEncodingList :: [SubscriptReadContent] -> Encoding
toEncodingList :: [SubscriptReadContent] -> Encoding
$comitField :: SubscriptReadContent -> Bool
omitField :: SubscriptReadContent -> Bool
ToJSON, Maybe SubscriptReadContent
Value -> Parser [SubscriptReadContent]
Value -> Parser SubscriptReadContent
(Value -> Parser SubscriptReadContent)
-> (Value -> Parser [SubscriptReadContent])
-> Maybe SubscriptReadContent
-> FromJSON SubscriptReadContent
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser SubscriptReadContent
parseJSON :: Value -> Parser SubscriptReadContent
$cparseJSONList :: Value -> Parser [SubscriptReadContent]
parseJSONList :: Value -> Parser [SubscriptReadContent]
$comittedField :: Maybe SubscriptReadContent
omittedField :: Maybe SubscriptReadContent
FromJSON, Eq SubscriptReadContent
Eq SubscriptReadContent
-> (SubscriptReadContent -> SubscriptReadContent -> Ordering)
-> (SubscriptReadContent -> SubscriptReadContent -> Bool)
-> (SubscriptReadContent -> SubscriptReadContent -> Bool)
-> (SubscriptReadContent -> SubscriptReadContent -> Bool)
-> (SubscriptReadContent -> SubscriptReadContent -> Bool)
-> (SubscriptReadContent
-> SubscriptReadContent -> SubscriptReadContent)
-> (SubscriptReadContent
-> SubscriptReadContent -> SubscriptReadContent)
-> Ord SubscriptReadContent
SubscriptReadContent -> SubscriptReadContent -> Bool
SubscriptReadContent -> SubscriptReadContent -> Ordering
SubscriptReadContent
-> SubscriptReadContent -> SubscriptReadContent
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 :: SubscriptReadContent -> SubscriptReadContent -> Ordering
compare :: SubscriptReadContent -> SubscriptReadContent -> Ordering
$c< :: SubscriptReadContent -> SubscriptReadContent -> Bool
< :: SubscriptReadContent -> SubscriptReadContent -> Bool
$c<= :: SubscriptReadContent -> SubscriptReadContent -> Bool
<= :: SubscriptReadContent -> SubscriptReadContent -> Bool
$c> :: SubscriptReadContent -> SubscriptReadContent -> Bool
> :: SubscriptReadContent -> SubscriptReadContent -> Bool
$c>= :: SubscriptReadContent -> SubscriptReadContent -> Bool
>= :: SubscriptReadContent -> SubscriptReadContent -> Bool
$cmax :: SubscriptReadContent
-> SubscriptReadContent -> SubscriptReadContent
max :: SubscriptReadContent
-> SubscriptReadContent -> SubscriptReadContent
$cmin :: SubscriptReadContent
-> SubscriptReadContent -> SubscriptReadContent
min :: SubscriptReadContent
-> SubscriptReadContent -> SubscriptReadContent
Ord )
data SubscriptWriteContent
= SubscriptWriteContent
{
SubscriptWriteContent -> Variable
subscriptWriteOutput :: Variable,
SubscriptWriteContent -> Variable
subscriptWriteIdx :: Variable,
SubscriptWriteContent -> Variable
subscriptWriteInput :: Variable
}
deriving ( Int -> SubscriptWriteContent -> ShowS
[SubscriptWriteContent] -> ShowS
SubscriptWriteContent -> String
(Int -> SubscriptWriteContent -> ShowS)
-> (SubscriptWriteContent -> String)
-> ([SubscriptWriteContent] -> ShowS)
-> Show SubscriptWriteContent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SubscriptWriteContent -> ShowS
showsPrec :: Int -> SubscriptWriteContent -> ShowS
$cshow :: SubscriptWriteContent -> String
show :: SubscriptWriteContent -> String
$cshowList :: [SubscriptWriteContent] -> ShowS
showList :: [SubscriptWriteContent] -> ShowS
Show, SubscriptWriteContent -> SubscriptWriteContent -> Bool
(SubscriptWriteContent -> SubscriptWriteContent -> Bool)
-> (SubscriptWriteContent -> SubscriptWriteContent -> Bool)
-> Eq SubscriptWriteContent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SubscriptWriteContent -> SubscriptWriteContent -> Bool
== :: SubscriptWriteContent -> SubscriptWriteContent -> Bool
$c/= :: SubscriptWriteContent -> SubscriptWriteContent -> Bool
/= :: SubscriptWriteContent -> SubscriptWriteContent -> Bool
Eq, (forall x. SubscriptWriteContent -> Rep SubscriptWriteContent x)
-> (forall x. Rep SubscriptWriteContent x -> SubscriptWriteContent)
-> Generic SubscriptWriteContent
forall x. Rep SubscriptWriteContent x -> SubscriptWriteContent
forall x. SubscriptWriteContent -> Rep SubscriptWriteContent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SubscriptWriteContent -> Rep SubscriptWriteContent x
from :: forall x. SubscriptWriteContent -> Rep SubscriptWriteContent x
$cto :: forall x. Rep SubscriptWriteContent x -> SubscriptWriteContent
to :: forall x. Rep SubscriptWriteContent x -> SubscriptWriteContent
Generic, [SubscriptWriteContent] -> Value
[SubscriptWriteContent] -> Encoding
SubscriptWriteContent -> Bool
SubscriptWriteContent -> Value
SubscriptWriteContent -> Encoding
(SubscriptWriteContent -> Value)
-> (SubscriptWriteContent -> Encoding)
-> ([SubscriptWriteContent] -> Value)
-> ([SubscriptWriteContent] -> Encoding)
-> (SubscriptWriteContent -> Bool)
-> ToJSON SubscriptWriteContent
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: SubscriptWriteContent -> Value
toJSON :: SubscriptWriteContent -> Value
$ctoEncoding :: SubscriptWriteContent -> Encoding
toEncoding :: SubscriptWriteContent -> Encoding
$ctoJSONList :: [SubscriptWriteContent] -> Value
toJSONList :: [SubscriptWriteContent] -> Value
$ctoEncodingList :: [SubscriptWriteContent] -> Encoding
toEncodingList :: [SubscriptWriteContent] -> Encoding
$comitField :: SubscriptWriteContent -> Bool
omitField :: SubscriptWriteContent -> Bool
ToJSON, Maybe SubscriptWriteContent
Value -> Parser [SubscriptWriteContent]
Value -> Parser SubscriptWriteContent
(Value -> Parser SubscriptWriteContent)
-> (Value -> Parser [SubscriptWriteContent])
-> Maybe SubscriptWriteContent
-> FromJSON SubscriptWriteContent
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser SubscriptWriteContent
parseJSON :: Value -> Parser SubscriptWriteContent
$cparseJSONList :: Value -> Parser [SubscriptWriteContent]
parseJSONList :: Value -> Parser [SubscriptWriteContent]
$comittedField :: Maybe SubscriptWriteContent
omittedField :: Maybe SubscriptWriteContent
FromJSON, Eq SubscriptWriteContent
Eq SubscriptWriteContent
-> (SubscriptWriteContent -> SubscriptWriteContent -> Ordering)
-> (SubscriptWriteContent -> SubscriptWriteContent -> Bool)
-> (SubscriptWriteContent -> SubscriptWriteContent -> Bool)
-> (SubscriptWriteContent -> SubscriptWriteContent -> Bool)
-> (SubscriptWriteContent -> SubscriptWriteContent -> Bool)
-> (SubscriptWriteContent
-> SubscriptWriteContent -> SubscriptWriteContent)
-> (SubscriptWriteContent
-> SubscriptWriteContent -> SubscriptWriteContent)
-> Ord SubscriptWriteContent
SubscriptWriteContent -> SubscriptWriteContent -> Bool
SubscriptWriteContent -> SubscriptWriteContent -> Ordering
SubscriptWriteContent
-> SubscriptWriteContent -> SubscriptWriteContent
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 :: SubscriptWriteContent -> SubscriptWriteContent -> Ordering
compare :: SubscriptWriteContent -> SubscriptWriteContent -> Ordering
$c< :: SubscriptWriteContent -> SubscriptWriteContent -> Bool
< :: SubscriptWriteContent -> SubscriptWriteContent -> Bool
$c<= :: SubscriptWriteContent -> SubscriptWriteContent -> Bool
<= :: SubscriptWriteContent -> SubscriptWriteContent -> Bool
$c> :: SubscriptWriteContent -> SubscriptWriteContent -> Bool
> :: SubscriptWriteContent -> SubscriptWriteContent -> Bool
$c>= :: SubscriptWriteContent -> SubscriptWriteContent -> Bool
>= :: SubscriptWriteContent -> SubscriptWriteContent -> Bool
$cmax :: SubscriptWriteContent
-> SubscriptWriteContent -> SubscriptWriteContent
max :: SubscriptWriteContent
-> SubscriptWriteContent -> SubscriptWriteContent
$cmin :: SubscriptWriteContent
-> SubscriptWriteContent -> SubscriptWriteContent
min :: SubscriptWriteContent
-> SubscriptWriteContent -> SubscriptWriteContent
Ord )
data ParamDeclContent
= ParamDeclContent
{
ParamDeclContent -> ParamVariable
paramVariable :: ParamVariable
}
deriving ( Int -> ParamDeclContent -> ShowS
[ParamDeclContent] -> ShowS
ParamDeclContent -> String
(Int -> ParamDeclContent -> ShowS)
-> (ParamDeclContent -> String)
-> ([ParamDeclContent] -> ShowS)
-> Show ParamDeclContent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ParamDeclContent -> ShowS
showsPrec :: Int -> ParamDeclContent -> ShowS
$cshow :: ParamDeclContent -> String
show :: ParamDeclContent -> String
$cshowList :: [ParamDeclContent] -> ShowS
showList :: [ParamDeclContent] -> ShowS
Show, ParamDeclContent -> ParamDeclContent -> Bool
(ParamDeclContent -> ParamDeclContent -> Bool)
-> (ParamDeclContent -> ParamDeclContent -> Bool)
-> Eq ParamDeclContent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ParamDeclContent -> ParamDeclContent -> Bool
== :: ParamDeclContent -> ParamDeclContent -> Bool
$c/= :: ParamDeclContent -> ParamDeclContent -> Bool
/= :: ParamDeclContent -> ParamDeclContent -> Bool
Eq, (forall x. ParamDeclContent -> Rep ParamDeclContent x)
-> (forall x. Rep ParamDeclContent x -> ParamDeclContent)
-> Generic ParamDeclContent
forall x. Rep ParamDeclContent x -> ParamDeclContent
forall x. ParamDeclContent -> Rep ParamDeclContent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ParamDeclContent -> Rep ParamDeclContent x
from :: forall x. ParamDeclContent -> Rep ParamDeclContent x
$cto :: forall x. Rep ParamDeclContent x -> ParamDeclContent
to :: forall x. Rep ParamDeclContent x -> ParamDeclContent
Generic, [ParamDeclContent] -> Value
[ParamDeclContent] -> Encoding
ParamDeclContent -> Bool
ParamDeclContent -> Value
ParamDeclContent -> Encoding
(ParamDeclContent -> Value)
-> (ParamDeclContent -> Encoding)
-> ([ParamDeclContent] -> Value)
-> ([ParamDeclContent] -> Encoding)
-> (ParamDeclContent -> Bool)
-> ToJSON ParamDeclContent
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: ParamDeclContent -> Value
toJSON :: ParamDeclContent -> Value
$ctoEncoding :: ParamDeclContent -> Encoding
toEncoding :: ParamDeclContent -> Encoding
$ctoJSONList :: [ParamDeclContent] -> Value
toJSONList :: [ParamDeclContent] -> Value
$ctoEncodingList :: [ParamDeclContent] -> Encoding
toEncodingList :: [ParamDeclContent] -> Encoding
$comitField :: ParamDeclContent -> Bool
omitField :: ParamDeclContent -> Bool
ToJSON, Maybe ParamDeclContent
Value -> Parser [ParamDeclContent]
Value -> Parser ParamDeclContent
(Value -> Parser ParamDeclContent)
-> (Value -> Parser [ParamDeclContent])
-> Maybe ParamDeclContent
-> FromJSON ParamDeclContent
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser ParamDeclContent
parseJSON :: Value -> Parser ParamDeclContent
$cparseJSONList :: Value -> Parser [ParamDeclContent]
parseJSONList :: Value -> Parser [ParamDeclContent]
$comittedField :: Maybe ParamDeclContent
omittedField :: Maybe ParamDeclContent
FromJSON, Eq ParamDeclContent
Eq ParamDeclContent
-> (ParamDeclContent -> ParamDeclContent -> Ordering)
-> (ParamDeclContent -> ParamDeclContent -> Bool)
-> (ParamDeclContent -> ParamDeclContent -> Bool)
-> (ParamDeclContent -> ParamDeclContent -> Bool)
-> (ParamDeclContent -> ParamDeclContent -> Bool)
-> (ParamDeclContent -> ParamDeclContent -> ParamDeclContent)
-> (ParamDeclContent -> ParamDeclContent -> ParamDeclContent)
-> Ord ParamDeclContent
ParamDeclContent -> ParamDeclContent -> Bool
ParamDeclContent -> ParamDeclContent -> Ordering
ParamDeclContent -> ParamDeclContent -> ParamDeclContent
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 :: ParamDeclContent -> ParamDeclContent -> Ordering
compare :: ParamDeclContent -> ParamDeclContent -> Ordering
$c< :: ParamDeclContent -> ParamDeclContent -> Bool
< :: ParamDeclContent -> ParamDeclContent -> Bool
$c<= :: ParamDeclContent -> ParamDeclContent -> Bool
<= :: ParamDeclContent -> ParamDeclContent -> Bool
$c> :: ParamDeclContent -> ParamDeclContent -> Bool
> :: ParamDeclContent -> ParamDeclContent -> Bool
$c>= :: ParamDeclContent -> ParamDeclContent -> Bool
>= :: ParamDeclContent -> ParamDeclContent -> Bool
$cmax :: ParamDeclContent -> ParamDeclContent -> ParamDeclContent
max :: ParamDeclContent -> ParamDeclContent -> ParamDeclContent
$cmin :: ParamDeclContent -> ParamDeclContent -> ParamDeclContent
min :: ParamDeclContent -> ParamDeclContent -> ParamDeclContent
Ord )
output :: InstructionContent -> Maybe Variable
output :: InstructionContent -> Maybe Variable
output (Unop UnopContent
c) = Variable -> Maybe Variable
forall a. a -> Maybe a
Just (Variable -> Maybe Variable) -> Variable -> Maybe Variable
forall a b. (a -> b) -> a -> b
$ UnopContent -> Variable
unopOutput UnopContent
c
output (Call CallContent
c) = Variable -> Maybe Variable
forall a. a -> Maybe a
Just (Variable -> Maybe Variable) -> Variable -> Maybe Variable
forall a b. (a -> b) -> a -> b
$ CallContent -> Variable
callOutput CallContent
c
output (Binop BinopContent
c) = Variable -> Maybe Variable
forall a. a -> Maybe a
Just (Variable -> Maybe Variable) -> Variable -> Maybe Variable
forall a b. (a -> b) -> a -> b
$ BinopContent -> Variable
binopOutput BinopContent
c
output (Assign AssignContent
c) = Variable -> Maybe Variable
forall a. a -> Maybe a
Just (Variable -> Maybe Variable) -> Variable -> Maybe Variable
forall a b. (a -> b) -> a -> b
$ AssignContent -> Variable
assignOutput AssignContent
c
output (FieldRead FieldReadContent
c) = Variable -> Maybe Variable
forall a. a -> Maybe a
Just (Variable -> Maybe Variable) -> Variable -> Maybe Variable
forall a b. (a -> b) -> a -> b
$ FieldReadContent -> Variable
fieldReadOutput FieldReadContent
c
output (SubscriptRead SubscriptReadContent
c) = Variable -> Maybe Variable
forall a. a -> Maybe a
Just (Variable -> Maybe Variable) -> Variable -> Maybe Variable
forall a b. (a -> b) -> a -> b
$ SubscriptReadContent -> Variable
subscriptReadOutput SubscriptReadContent
c
output InstructionContent
_ = Maybe Variable
forall a. Maybe a
Nothing
inputs :: InstructionContent -> Set Variable
inputs :: InstructionContent -> Set Variable
inputs (Call CallContent
c) = [Variable] -> Set Variable
forall a. Ord a => [a] -> Set a
Data.Set.fromList (CallContent -> [Variable]
args CallContent
c)
inputs InstructionContent
_ = Set Variable
forall a. Set a
Data.Set.empty
variables :: InstructionContent -> Set Variable
variables :: InstructionContent -> Set Variable
variables InstructionContent
instruction = case InstructionContent -> Maybe Variable
output InstructionContent
instruction of
Maybe Variable
Nothing -> InstructionContent -> Set Variable
inputs InstructionContent
instruction
Just Variable
oneOutput -> (Variable -> Set Variable
forall a. a -> Set a
Data.Set.singleton Variable
oneOutput) Set Variable -> Set Variable -> Set Variable
forall a. Ord a => Set a -> Set a -> Set a
`Data.Set.union` (InstructionContent -> Set Variable
inputs InstructionContent
instruction)