| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Bitcode
Synopsis
- data Instruction = Instruction {}
- 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
- mkNopInstruction :: Location -> Instruction
- data TmpVariable = TmpVariable {}
- data SrcVariable = SrcVariable {}
- data ArgContent = ArgContent {}
- data ParamVariable = ParamVariable {}
- data Variable
- variableFqn :: Variable -> Fqn
- data Variables = Variables {
- actualVariables :: Set Variable
- data SrcVariables = SrcVariables {
- actualSrcVariables :: Set SrcVariable
- createEmptyCollectionOfGlobalVariables :: SrcVariables
- data TmpVariables = TmpVariables {
- actualTmpVariables :: Set TmpVariable
- locationVariable :: Variable -> Location
- data CallContent = CallContent {
- callOutput :: Variable
- callee :: Variable
- args :: [Variable]
- callLocation :: Location
- callInputs :: CallContent -> [TmpVariable]
- data BinopContent = BinopContent {}
- data UnopContent = UnopContent {}
- data AssumeContent = AssumeContent {
- assumeVariable :: Variable
- assumedValue :: Bool
- mkAssumeInstruction :: Variable -> Bool -> Instruction
- data ReturnContent = ReturnContent {
- returnValue :: Maybe Variable
- data AssignContent = AssignContent {}
- data IntContent = IntContent {}
- data StrContent = StrContent {}
- data BoolContent = BoolContent {}
- data FieldReadContent = FieldReadContent {}
- data FieldWriteContent = FieldWriteContent {}
- data SubscriptReadContent = SubscriptReadContent {}
- data SubscriptWriteContent = SubscriptWriteContent {}
- data ParamDeclContent = ParamDeclContent {}
- output :: InstructionContent -> Maybe Variable
- inputs :: InstructionContent -> Set TmpVariable
- inputs' :: InstructionContent -> Set Variable
- variables :: InstructionContent -> Set Variable
Documentation
data Instruction Source #
Constructors
| Instruction | |
Fields | |
Instances
| FromJSON Instruction Source # | |
Defined in Bitcode Methods parseJSON :: Value -> Parser Instruction # parseJSONList :: Value -> Parser [Instruction] # omittedField :: Maybe Instruction # | |
| ToJSON Instruction Source # | |
Defined in Bitcode Methods toJSON :: Instruction -> Value # toEncoding :: Instruction -> Encoding # toJSONList :: [Instruction] -> Value # toEncodingList :: [Instruction] -> Encoding # omitField :: Instruction -> Bool # | |
| Generic Instruction Source # | |
Defined in Bitcode Associated Types type Rep Instruction :: Type -> Type | |
| Show Instruction Source # | |
Defined in Bitcode Methods showsPrec :: Int -> Instruction -> ShowS show :: Instruction -> String showList :: [Instruction] -> ShowS | |
| Eq Instruction Source # | |
Defined in Bitcode | |
| Ord Instruction Source # | |
Defined in Bitcode Methods compare :: Instruction -> Instruction -> Ordering (<) :: Instruction -> Instruction -> Bool (<=) :: Instruction -> Instruction -> Bool (>) :: Instruction -> Instruction -> Bool (>=) :: Instruction -> Instruction -> Bool max :: Instruction -> Instruction -> Instruction min :: Instruction -> Instruction -> Instruction | |
| type Rep Instruction Source # | |
Defined in Bitcode type Rep Instruction = D1 ('MetaData "Instruction" "Bitcode" "dhscanner-bitcode-0.1.0.1-inplace" 'False) (C1 ('MetaCons "Instruction" 'PrefixI 'True) (S1 ('MetaSel ('Just "location") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Location) :*: S1 ('MetaSel ('Just "instructionContent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InstructionContent))) | |
data InstructionContent Source #
A minimal instruction set to translate any programming language to an intermediate langauge ready for static analysis
Constructors
Instances
| FromJSON InstructionContent Source # | |
Defined in Bitcode Methods parseJSON :: Value -> Parser InstructionContent # parseJSONList :: Value -> Parser [InstructionContent] # omittedField :: Maybe InstructionContent # | |
| ToJSON InstructionContent Source # | |
Defined in Bitcode Methods toJSON :: InstructionContent -> Value # toEncoding :: InstructionContent -> Encoding # toJSONList :: [InstructionContent] -> Value # toEncodingList :: [InstructionContent] -> Encoding # omitField :: InstructionContent -> Bool # | |
| Generic InstructionContent Source # | |
Defined in Bitcode Associated Types type Rep InstructionContent :: Type -> Type Methods from :: InstructionContent -> Rep InstructionContent x to :: Rep InstructionContent x -> InstructionContent | |
| Show InstructionContent Source # | |
Defined in Bitcode Methods showsPrec :: Int -> InstructionContent -> ShowS show :: InstructionContent -> String showList :: [InstructionContent] -> ShowS | |
| Eq InstructionContent Source # | |
Defined in Bitcode Methods (==) :: InstructionContent -> InstructionContent -> Bool (/=) :: InstructionContent -> InstructionContent -> Bool | |
| Ord InstructionContent Source # | |
Defined in Bitcode Methods compare :: InstructionContent -> InstructionContent -> Ordering (<) :: InstructionContent -> InstructionContent -> Bool (<=) :: InstructionContent -> InstructionContent -> Bool (>) :: InstructionContent -> InstructionContent -> Bool (>=) :: InstructionContent -> InstructionContent -> Bool max :: InstructionContent -> InstructionContent -> InstructionContent min :: InstructionContent -> InstructionContent -> InstructionContent | |
| type Rep InstructionContent Source # | |
Defined in Bitcode type Rep InstructionContent = D1 ('MetaData "InstructionContent" "Bitcode" "dhscanner-bitcode-0.1.0.1-inplace" 'False) (((C1 ('MetaCons "Nop" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Call" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CallContent)) :+: C1 ('MetaCons "Unop" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnopContent)))) :+: ((C1 ('MetaCons "Binop" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BinopContent)) :+: C1 ('MetaCons "Assume" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AssumeContent))) :+: (C1 ('MetaCons "Return" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ReturnContent)) :+: C1 ('MetaCons "Assign" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AssignContent))))) :+: (((C1 ('MetaCons "LoadImmStr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 StrContent)) :+: C1 ('MetaCons "LoadImmInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IntContent))) :+: (C1 ('MetaCons "LoadImmBool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BoolContent)) :+: C1 ('MetaCons "ParamDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ParamDeclContent)))) :+: ((C1 ('MetaCons "FieldRead" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FieldReadContent)) :+: C1 ('MetaCons "FieldWrite" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FieldWriteContent))) :+: (C1 ('MetaCons "SubscriptRead" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SubscriptReadContent)) :+: C1 ('MetaCons "SubscriptWrite" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SubscriptWriteContent)))))) | |
data TmpVariable Source #
Constructors
| TmpVariable | |
Fields | |
Instances
| FromJSON TmpVariable Source # | |
Defined in Bitcode Methods parseJSON :: Value -> Parser TmpVariable # parseJSONList :: Value -> Parser [TmpVariable] # omittedField :: Maybe TmpVariable # | |
| ToJSON TmpVariable Source # | |
Defined in Bitcode Methods toJSON :: TmpVariable -> Value # toEncoding :: TmpVariable -> Encoding # toJSONList :: [TmpVariable] -> Value # toEncodingList :: [TmpVariable] -> Encoding # omitField :: TmpVariable -> Bool # | |
| Generic TmpVariable Source # | |
Defined in Bitcode Associated Types type Rep TmpVariable :: Type -> Type | |
| Show TmpVariable Source # | |
Defined in Bitcode Methods showsPrec :: Int -> TmpVariable -> ShowS show :: TmpVariable -> String showList :: [TmpVariable] -> ShowS | |
| Eq TmpVariable Source # | |
Defined in Bitcode | |
| Ord TmpVariable Source # | |
Defined in Bitcode Methods compare :: TmpVariable -> TmpVariable -> Ordering (<) :: TmpVariable -> TmpVariable -> Bool (<=) :: TmpVariable -> TmpVariable -> Bool (>) :: TmpVariable -> TmpVariable -> Bool (>=) :: TmpVariable -> TmpVariable -> Bool max :: TmpVariable -> TmpVariable -> TmpVariable min :: TmpVariable -> TmpVariable -> TmpVariable | |
| type Rep TmpVariable Source # | |
Defined in Bitcode type Rep TmpVariable = D1 ('MetaData "TmpVariable" "Bitcode" "dhscanner-bitcode-0.1.0.1-inplace" 'False) (C1 ('MetaCons "TmpVariable" 'PrefixI 'True) (S1 ('MetaSel ('Just "tmpVariableFqn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Fqn) :*: S1 ('MetaSel ('Just "tmpVariableLocation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Location))) | |
data SrcVariable Source #
Constructors
| SrcVariable | |
Fields | |
Instances
| FromJSON SrcVariable Source # | |
Defined in Bitcode Methods parseJSON :: Value -> Parser SrcVariable # parseJSONList :: Value -> Parser [SrcVariable] # omittedField :: Maybe SrcVariable # | |
| ToJSON SrcVariable Source # | |
Defined in Bitcode Methods toJSON :: SrcVariable -> Value # toEncoding :: SrcVariable -> Encoding # toJSONList :: [SrcVariable] -> Value # toEncodingList :: [SrcVariable] -> Encoding # omitField :: SrcVariable -> Bool # | |
| Generic SrcVariable Source # | |
Defined in Bitcode Associated Types type Rep SrcVariable :: Type -> Type | |
| Show SrcVariable Source # | |
Defined in Bitcode Methods showsPrec :: Int -> SrcVariable -> ShowS show :: SrcVariable -> String showList :: [SrcVariable] -> ShowS | |
| Eq SrcVariable Source # | |
Defined in Bitcode | |
| Ord SrcVariable Source # | |
Defined in Bitcode Methods compare :: SrcVariable -> SrcVariable -> Ordering (<) :: SrcVariable -> SrcVariable -> Bool (<=) :: SrcVariable -> SrcVariable -> Bool (>) :: SrcVariable -> SrcVariable -> Bool (>=) :: SrcVariable -> SrcVariable -> Bool max :: SrcVariable -> SrcVariable -> SrcVariable min :: SrcVariable -> SrcVariable -> SrcVariable | |
| type Rep SrcVariable Source # | |
Defined in Bitcode type Rep SrcVariable = D1 ('MetaData "SrcVariable" "Bitcode" "dhscanner-bitcode-0.1.0.1-inplace" 'False) (C1 ('MetaCons "SrcVariable" 'PrefixI 'True) (S1 ('MetaSel ('Just "srcVariableFqn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Fqn) :*: S1 ('MetaSel ('Just "srcVariableToken") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VarName))) | |
data ArgContent Source #
Constructors
| ArgContent | |
Fields | |
Instances
| FromJSON ArgContent Source # | |
Defined in Bitcode Methods parseJSON :: Value -> Parser ArgContent # parseJSONList :: Value -> Parser [ArgContent] # omittedField :: Maybe ArgContent # | |
| ToJSON ArgContent Source # | |
Defined in Bitcode Methods toJSON :: ArgContent -> Value # toEncoding :: ArgContent -> Encoding # toJSONList :: [ArgContent] -> Value # toEncodingList :: [ArgContent] -> Encoding # omitField :: ArgContent -> Bool # | |
| Generic ArgContent Source # | |
Defined in Bitcode Associated Types type Rep ArgContent :: Type -> Type | |
| Show ArgContent Source # | |
Defined in Bitcode Methods showsPrec :: Int -> ArgContent -> ShowS show :: ArgContent -> String showList :: [ArgContent] -> ShowS | |
| Eq ArgContent Source # | |
Defined in Bitcode | |
| Ord ArgContent Source # | |
Defined in Bitcode Methods compare :: ArgContent -> ArgContent -> Ordering (<) :: ArgContent -> ArgContent -> Bool (<=) :: ArgContent -> ArgContent -> Bool (>) :: ArgContent -> ArgContent -> Bool (>=) :: ArgContent -> ArgContent -> Bool max :: ArgContent -> ArgContent -> ArgContent min :: ArgContent -> ArgContent -> ArgContent | |
| type Rep ArgContent Source # | |
Defined in Bitcode type Rep ArgContent = D1 ('MetaData "ArgContent" "Bitcode" "dhscanner-bitcode-0.1.0.1-inplace" 'False) (C1 ('MetaCons "ArgContent" 'PrefixI 'True) (S1 ('MetaSel ('Just "argVariableFqn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Fqn) :*: (S1 ('MetaSel ('Just "argVariableSerialIdx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word) :*: S1 ('MetaSel ('Just "argVariableMyAwesomeCallContext") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Location)))) | |
data ParamVariable Source #
Constructors
| ParamVariable | |
Fields
| |
Instances
| FromJSON ParamVariable Source # | |
Defined in Bitcode Methods parseJSON :: Value -> Parser ParamVariable # parseJSONList :: Value -> Parser [ParamVariable] # omittedField :: Maybe ParamVariable # | |
| ToJSON ParamVariable Source # | |
Defined in Bitcode Methods toJSON :: ParamVariable -> Value # toEncoding :: ParamVariable -> Encoding # toJSONList :: [ParamVariable] -> Value # toEncodingList :: [ParamVariable] -> Encoding # omitField :: ParamVariable -> Bool # | |
| Generic ParamVariable Source # | |
Defined in Bitcode Associated Types type Rep ParamVariable :: Type -> Type | |
| Show ParamVariable Source # | |
Defined in Bitcode Methods showsPrec :: Int -> ParamVariable -> ShowS show :: ParamVariable -> String showList :: [ParamVariable] -> ShowS | |
| Eq ParamVariable Source # | |
Defined in Bitcode | |
| Ord ParamVariable Source # | |
Defined in Bitcode Methods compare :: ParamVariable -> ParamVariable -> Ordering (<) :: ParamVariable -> ParamVariable -> Bool (<=) :: ParamVariable -> ParamVariable -> Bool (>) :: ParamVariable -> ParamVariable -> Bool (>=) :: ParamVariable -> ParamVariable -> Bool max :: ParamVariable -> ParamVariable -> ParamVariable min :: ParamVariable -> ParamVariable -> ParamVariable | |
| type Rep ParamVariable Source # | |
Defined in Bitcode type Rep ParamVariable = D1 ('MetaData "ParamVariable" "Bitcode" "dhscanner-bitcode-0.1.0.1-inplace" 'False) (C1 ('MetaCons "ParamVariable" 'PrefixI 'True) (S1 ('MetaSel ('Just "paramVariableFqn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Fqn) :*: (S1 ('MetaSel ('Just "paramVariableSerialIdx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word) :*: S1 ('MetaSel ('Just "paramVariableToken") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ParamName)))) | |
Constructors
| TmpVariableCtor TmpVariable | |
| SrcVariableCtor SrcVariable | |
| ParamVariableCtor ParamVariable | |
| Arg ArgContent |
Instances
| FromJSON Variable Source # | |
| ToJSON Variable Source # | |
| Generic Variable Source # | |
| Show Variable Source # | |
| Eq Variable Source # | |
| Ord Variable Source # | |
| type Rep Variable Source # | |
Defined in Bitcode type Rep Variable = D1 ('MetaData "Variable" "Bitcode" "dhscanner-bitcode-0.1.0.1-inplace" 'False) ((C1 ('MetaCons "TmpVariableCtor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TmpVariable)) :+: C1 ('MetaCons "SrcVariableCtor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcVariable))) :+: (C1 ('MetaCons "ParamVariableCtor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ParamVariable)) :+: C1 ('MetaCons "Arg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ArgContent)))) | |
variableFqn :: Variable -> Fqn Source #
Can not be serialized to JSON
Constructors
| Variables | |
Fields
| |
data SrcVariables Source #
Constructors
| SrcVariables | |
Fields
| |
Instances
| Show SrcVariables Source # | |
Defined in Bitcode Methods showsPrec :: Int -> SrcVariables -> ShowS show :: SrcVariables -> String showList :: [SrcVariables] -> ShowS | |
| Eq SrcVariables Source # | |
Defined in Bitcode | |
| Ord SrcVariables Source # | |
Defined in Bitcode Methods compare :: SrcVariables -> SrcVariables -> Ordering (<) :: SrcVariables -> SrcVariables -> Bool (<=) :: SrcVariables -> SrcVariables -> Bool (>) :: SrcVariables -> SrcVariables -> Bool (>=) :: SrcVariables -> SrcVariables -> Bool max :: SrcVariables -> SrcVariables -> SrcVariables min :: SrcVariables -> SrcVariables -> SrcVariables | |
createEmptyCollectionOfGlobalVariables :: SrcVariables Source #
Creating an empty collection of global variables
data TmpVariables Source #
Can not be serialized to JSON
Constructors
| TmpVariables | |
Fields
| |
Instances
| Show TmpVariables Source # | |
Defined in Bitcode Methods showsPrec :: Int -> TmpVariables -> ShowS show :: TmpVariables -> String showList :: [TmpVariables] -> ShowS | |
| Eq TmpVariables Source # | |
Defined in Bitcode | |
| Ord TmpVariables Source # | |
Defined in Bitcode Methods compare :: TmpVariables -> TmpVariables -> Ordering (<) :: TmpVariables -> TmpVariables -> Bool (<=) :: TmpVariables -> TmpVariables -> Bool (>) :: TmpVariables -> TmpVariables -> Bool (>=) :: TmpVariables -> TmpVariables -> Bool max :: TmpVariables -> TmpVariables -> TmpVariables min :: TmpVariables -> TmpVariables -> TmpVariables | |
locationVariable :: Variable -> Location Source #
data CallContent Source #
Constructors
| CallContent | |
Fields
| |
Instances
| FromJSON CallContent Source # | |
Defined in Bitcode Methods parseJSON :: Value -> Parser CallContent # parseJSONList :: Value -> Parser [CallContent] # omittedField :: Maybe CallContent # | |
| ToJSON CallContent Source # | |
Defined in Bitcode Methods toJSON :: CallContent -> Value # toEncoding :: CallContent -> Encoding # toJSONList :: [CallContent] -> Value # toEncodingList :: [CallContent] -> Encoding # omitField :: CallContent -> Bool # | |
| Generic CallContent Source # | |
Defined in Bitcode Associated Types type Rep CallContent :: Type -> Type | |
| Show CallContent Source # | |
Defined in Bitcode Methods showsPrec :: Int -> CallContent -> ShowS show :: CallContent -> String showList :: [CallContent] -> ShowS | |
| Eq CallContent Source # | |
Defined in Bitcode | |
| Ord CallContent Source # | |
Defined in Bitcode Methods compare :: CallContent -> CallContent -> Ordering (<) :: CallContent -> CallContent -> Bool (<=) :: CallContent -> CallContent -> Bool (>) :: CallContent -> CallContent -> Bool (>=) :: CallContent -> CallContent -> Bool max :: CallContent -> CallContent -> CallContent min :: CallContent -> CallContent -> CallContent | |
| type Rep CallContent Source # | |
Defined in Bitcode type Rep CallContent = D1 ('MetaData "CallContent" "Bitcode" "dhscanner-bitcode-0.1.0.1-inplace" 'False) (C1 ('MetaCons "CallContent" 'PrefixI 'True) ((S1 ('MetaSel ('Just "callOutput") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Variable) :*: S1 ('MetaSel ('Just "callee") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Variable)) :*: (S1 ('MetaSel ('Just "args") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Variable]) :*: S1 ('MetaSel ('Just "callLocation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Location)))) | |
callInputs :: CallContent -> [TmpVariable] Source #
data BinopContent Source #
Constructors
| BinopContent | |
Instances
| FromJSON BinopContent Source # | |
Defined in Bitcode Methods parseJSON :: Value -> Parser BinopContent # parseJSONList :: Value -> Parser [BinopContent] # omittedField :: Maybe BinopContent # | |
| ToJSON BinopContent Source # | |
Defined in Bitcode Methods toJSON :: BinopContent -> Value # toEncoding :: BinopContent -> Encoding # toJSONList :: [BinopContent] -> Value # toEncodingList :: [BinopContent] -> Encoding # omitField :: BinopContent -> Bool # | |
| Generic BinopContent Source # | |
Defined in Bitcode Associated Types type Rep BinopContent :: Type -> Type | |
| Show BinopContent Source # | |
Defined in Bitcode Methods showsPrec :: Int -> BinopContent -> ShowS show :: BinopContent -> String showList :: [BinopContent] -> ShowS | |
| Eq BinopContent Source # | |
Defined in Bitcode | |
| Ord BinopContent Source # | |
Defined in Bitcode Methods compare :: BinopContent -> BinopContent -> Ordering (<) :: BinopContent -> BinopContent -> Bool (<=) :: BinopContent -> BinopContent -> Bool (>) :: BinopContent -> BinopContent -> Bool (>=) :: BinopContent -> BinopContent -> Bool max :: BinopContent -> BinopContent -> BinopContent min :: BinopContent -> BinopContent -> BinopContent | |
| type Rep BinopContent Source # | |
Defined in Bitcode type Rep BinopContent = D1 ('MetaData "BinopContent" "Bitcode" "dhscanner-bitcode-0.1.0.1-inplace" 'False) (C1 ('MetaCons "BinopContent" 'PrefixI 'True) (S1 ('MetaSel ('Just "binopOutput") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Variable) :*: (S1 ('MetaSel ('Just "binopLhs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Variable) :*: S1 ('MetaSel ('Just "binopRhs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Variable)))) | |
data UnopContent Source #
Constructors
| UnopContent | |
Fields
| |
Instances
| FromJSON UnopContent Source # | |
Defined in Bitcode Methods parseJSON :: Value -> Parser UnopContent # parseJSONList :: Value -> Parser [UnopContent] # omittedField :: Maybe UnopContent # | |
| ToJSON UnopContent Source # | |
Defined in Bitcode Methods toJSON :: UnopContent -> Value # toEncoding :: UnopContent -> Encoding # toJSONList :: [UnopContent] -> Value # toEncodingList :: [UnopContent] -> Encoding # omitField :: UnopContent -> Bool # | |
| Generic UnopContent Source # | |
Defined in Bitcode Associated Types type Rep UnopContent :: Type -> Type | |
| Show UnopContent Source # | |
Defined in Bitcode Methods showsPrec :: Int -> UnopContent -> ShowS show :: UnopContent -> String showList :: [UnopContent] -> ShowS | |
| Eq UnopContent Source # | |
Defined in Bitcode | |
| Ord UnopContent Source # | |
Defined in Bitcode Methods compare :: UnopContent -> UnopContent -> Ordering (<) :: UnopContent -> UnopContent -> Bool (<=) :: UnopContent -> UnopContent -> Bool (>) :: UnopContent -> UnopContent -> Bool (>=) :: UnopContent -> UnopContent -> Bool max :: UnopContent -> UnopContent -> UnopContent min :: UnopContent -> UnopContent -> UnopContent | |
| type Rep UnopContent Source # | |
Defined in Bitcode type Rep UnopContent = D1 ('MetaData "UnopContent" "Bitcode" "dhscanner-bitcode-0.1.0.1-inplace" 'False) (C1 ('MetaCons "UnopContent" 'PrefixI 'True) (S1 ('MetaSel ('Just "unopOutput") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Variable) :*: S1 ('MetaSel ('Just "unopLhs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Variable))) | |
data AssumeContent Source #
Constructors
| AssumeContent | |
Fields
| |
Instances
| FromJSON AssumeContent Source # | |
Defined in Bitcode Methods parseJSON :: Value -> Parser AssumeContent # parseJSONList :: Value -> Parser [AssumeContent] # omittedField :: Maybe AssumeContent # | |
| ToJSON AssumeContent Source # | |
Defined in Bitcode Methods toJSON :: AssumeContent -> Value # toEncoding :: AssumeContent -> Encoding # toJSONList :: [AssumeContent] -> Value # toEncodingList :: [AssumeContent] -> Encoding # omitField :: AssumeContent -> Bool # | |
| Generic AssumeContent Source # | |
Defined in Bitcode Associated Types type Rep AssumeContent :: Type -> Type | |
| Show AssumeContent Source # | |
Defined in Bitcode Methods showsPrec :: Int -> AssumeContent -> ShowS show :: AssumeContent -> String showList :: [AssumeContent] -> ShowS | |
| Eq AssumeContent Source # | |
Defined in Bitcode | |
| Ord AssumeContent Source # | |
Defined in Bitcode Methods compare :: AssumeContent -> AssumeContent -> Ordering (<) :: AssumeContent -> AssumeContent -> Bool (<=) :: AssumeContent -> AssumeContent -> Bool (>) :: AssumeContent -> AssumeContent -> Bool (>=) :: AssumeContent -> AssumeContent -> Bool max :: AssumeContent -> AssumeContent -> AssumeContent min :: AssumeContent -> AssumeContent -> AssumeContent | |
| type Rep AssumeContent Source # | |
Defined in Bitcode type Rep AssumeContent = D1 ('MetaData "AssumeContent" "Bitcode" "dhscanner-bitcode-0.1.0.1-inplace" 'False) (C1 ('MetaCons "AssumeContent" 'PrefixI 'True) (S1 ('MetaSel ('Just "assumeVariable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Variable) :*: S1 ('MetaSel ('Just "assumedValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) | |
mkAssumeInstruction :: Variable -> Bool -> Instruction Source #
data ReturnContent Source #
Constructors
| ReturnContent | |
Fields
| |
Instances
data AssignContent Source #
Constructors
| AssignContent | |
Fields | |
Instances
| FromJSON AssignContent Source # | |
Defined in Bitcode Methods parseJSON :: Value -> Parser AssignContent # parseJSONList :: Value -> Parser [AssignContent] # omittedField :: Maybe AssignContent # | |
| ToJSON AssignContent Source # | |
Defined in Bitcode Methods toJSON :: AssignContent -> Value # toEncoding :: AssignContent -> Encoding # toJSONList :: [AssignContent] -> Value # toEncodingList :: [AssignContent] -> Encoding # omitField :: AssignContent -> Bool # | |
| Generic AssignContent Source # | |
Defined in Bitcode Associated Types type Rep AssignContent :: Type -> Type | |
| Show AssignContent Source # | |
Defined in Bitcode Methods showsPrec :: Int -> AssignContent -> ShowS show :: AssignContent -> String showList :: [AssignContent] -> ShowS | |
| Eq AssignContent Source # | |
Defined in Bitcode | |
| Ord AssignContent Source # | |
Defined in Bitcode Methods compare :: AssignContent -> AssignContent -> Ordering (<) :: AssignContent -> AssignContent -> Bool (<=) :: AssignContent -> AssignContent -> Bool (>) :: AssignContent -> AssignContent -> Bool (>=) :: AssignContent -> AssignContent -> Bool max :: AssignContent -> AssignContent -> AssignContent min :: AssignContent -> AssignContent -> AssignContent | |
| type Rep AssignContent Source # | |
Defined in Bitcode type Rep AssignContent = D1 ('MetaData "AssignContent" "Bitcode" "dhscanner-bitcode-0.1.0.1-inplace" 'False) (C1 ('MetaCons "AssignContent" 'PrefixI 'True) (S1 ('MetaSel ('Just "assignOutput") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Variable) :*: S1 ('MetaSel ('Just "assignInput") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Variable))) | |
data IntContent Source #
Constructors
| IntContent | |
Fields | |
Instances
| FromJSON IntContent Source # | |
Defined in Bitcode Methods parseJSON :: Value -> Parser IntContent # parseJSONList :: Value -> Parser [IntContent] # omittedField :: Maybe IntContent # | |
| ToJSON IntContent Source # | |
Defined in Bitcode Methods toJSON :: IntContent -> Value # toEncoding :: IntContent -> Encoding # toJSONList :: [IntContent] -> Value # toEncodingList :: [IntContent] -> Encoding # omitField :: IntContent -> Bool # | |
| Generic IntContent Source # | |
Defined in Bitcode Associated Types type Rep IntContent :: Type -> Type | |
| Show IntContent Source # | |
Defined in Bitcode Methods showsPrec :: Int -> IntContent -> ShowS show :: IntContent -> String showList :: [IntContent] -> ShowS | |
| Eq IntContent Source # | |
Defined in Bitcode | |
| Ord IntContent Source # | |
Defined in Bitcode Methods compare :: IntContent -> IntContent -> Ordering (<) :: IntContent -> IntContent -> Bool (<=) :: IntContent -> IntContent -> Bool (>) :: IntContent -> IntContent -> Bool (>=) :: IntContent -> IntContent -> Bool max :: IntContent -> IntContent -> IntContent min :: IntContent -> IntContent -> IntContent | |
| type Rep IntContent Source # | |
Defined in Bitcode type Rep IntContent = D1 ('MetaData "IntContent" "Bitcode" "dhscanner-bitcode-0.1.0.1-inplace" 'False) (C1 ('MetaCons "IntContent" 'PrefixI 'True) (S1 ('MetaSel ('Just "loadImmIntOutput") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TmpVariable) :*: S1 ('MetaSel ('Just "loadImmIntValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ConstInt))) | |
data StrContent Source #
Constructors
| StrContent | |
Fields | |
Instances
| FromJSON StrContent Source # | |
Defined in Bitcode Methods parseJSON :: Value -> Parser StrContent # parseJSONList :: Value -> Parser [StrContent] # omittedField :: Maybe StrContent # | |
| ToJSON StrContent Source # | |
Defined in Bitcode Methods toJSON :: StrContent -> Value # toEncoding :: StrContent -> Encoding # toJSONList :: [StrContent] -> Value # toEncodingList :: [StrContent] -> Encoding # omitField :: StrContent -> Bool # | |
| Generic StrContent Source # | |
Defined in Bitcode Associated Types type Rep StrContent :: Type -> Type | |
| Show StrContent Source # | |
Defined in Bitcode Methods showsPrec :: Int -> StrContent -> ShowS show :: StrContent -> String showList :: [StrContent] -> ShowS | |
| Eq StrContent Source # | |
Defined in Bitcode | |
| Ord StrContent Source # | |
Defined in Bitcode Methods compare :: StrContent -> StrContent -> Ordering (<) :: StrContent -> StrContent -> Bool (<=) :: StrContent -> StrContent -> Bool (>) :: StrContent -> StrContent -> Bool (>=) :: StrContent -> StrContent -> Bool max :: StrContent -> StrContent -> StrContent min :: StrContent -> StrContent -> StrContent | |
| type Rep StrContent Source # | |
Defined in Bitcode type Rep StrContent = D1 ('MetaData "StrContent" "Bitcode" "dhscanner-bitcode-0.1.0.1-inplace" 'False) (C1 ('MetaCons "StrContent" 'PrefixI 'True) (S1 ('MetaSel ('Just "loadImmStrOutput") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TmpVariable) :*: S1 ('MetaSel ('Just "loadImmStrValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ConstStr))) | |
data BoolContent Source #
Constructors
| BoolContent | |
Fields | |
Instances
| FromJSON BoolContent Source # | |
Defined in Bitcode Methods parseJSON :: Value -> Parser BoolContent # parseJSONList :: Value -> Parser [BoolContent] # omittedField :: Maybe BoolContent # | |
| ToJSON BoolContent Source # | |
Defined in Bitcode Methods toJSON :: BoolContent -> Value # toEncoding :: BoolContent -> Encoding # toJSONList :: [BoolContent] -> Value # toEncodingList :: [BoolContent] -> Encoding # omitField :: BoolContent -> Bool # | |
| Generic BoolContent Source # | |
Defined in Bitcode Associated Types type Rep BoolContent :: Type -> Type | |
| Show BoolContent Source # | |
Defined in Bitcode Methods showsPrec :: Int -> BoolContent -> ShowS show :: BoolContent -> String showList :: [BoolContent] -> ShowS | |
| Eq BoolContent Source # | |
Defined in Bitcode | |
| Ord BoolContent Source # | |
Defined in Bitcode Methods compare :: BoolContent -> BoolContent -> Ordering (<) :: BoolContent -> BoolContent -> Bool (<=) :: BoolContent -> BoolContent -> Bool (>) :: BoolContent -> BoolContent -> Bool (>=) :: BoolContent -> BoolContent -> Bool max :: BoolContent -> BoolContent -> BoolContent min :: BoolContent -> BoolContent -> BoolContent | |
| type Rep BoolContent Source # | |
Defined in Bitcode type Rep BoolContent = D1 ('MetaData "BoolContent" "Bitcode" "dhscanner-bitcode-0.1.0.1-inplace" 'False) (C1 ('MetaCons "BoolContent" 'PrefixI 'True) (S1 ('MetaSel ('Just "loadImmBoolOutput") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TmpVariable) :*: S1 ('MetaSel ('Just "loadImmBoolValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ConstBool))) | |
data FieldReadContent Source #
Constructors
| FieldReadContent | |
Fields | |
Instances
data FieldWriteContent Source #
Constructors
| FieldWriteContent | |
Fields | |
Instances
data SubscriptReadContent Source #
Constructors
| SubscriptReadContent | |
Fields | |
Instances
data SubscriptWriteContent Source #
Constructors
| SubscriptWriteContent | |
Fields | |
Instances
data ParamDeclContent Source #
Constructors
| ParamDeclContent | |
Fields | |
Instances
output :: InstructionContent -> Maybe Variable Source #
inputs :: InstructionContent -> Set TmpVariable Source #
inputs' :: InstructionContent -> Set Variable Source #
variables :: InstructionContent -> Set Variable Source #