dhscanner-bitcode-1.0.10: Intermediate language for static code analysis
Safe HaskellSafe-Inferred
LanguageHaskell2010

Bitcode

Description

  • The intermediate language (IL) / intermediate representation (IR) / bitcode are all synonyms for:

    • a data structure able to represent code originating from multiple programming languages.
    • minimal instruction set, similar in spirit to RISC architectures
    • unlike actual assembly, it has an infinite number of temporaries ( instead of registers )
  • Its main purpose is to serve as the:

    • second step for static code analysis
    • part of the dhscanner framework for static analysis performing security checks 🔒 and PII leaks detection 🪪
  • As part of the dhscanner framework:

    • targets mostly languages used for cloud native applications ☁️
    • Python, Ruby 💎, Php, Javascript, Typescript, Java ☕️, C# and Golang.
  • Typical flow:

    • Abstract syntax trees (ASTs) are scanned

      • Callable entities are identified
      • each Callable is associated with its control flow graph (Cfg)
      • control flow graphs are directed, connecting bitcode instructions
  • Non Haskell parogrammers note:

    • Each Callable object is immutable ( like everything else in Haskell ... )
Synopsis

Documentation

data Instruction Source #

  • All instructions have an associated location
  • That is also true for instrumented instructions (like Nop and Assume)

Instances

Instances details
FromJSON Instruction Source # 
Instance details

Defined in Bitcode

ToJSON Instruction Source # 
Instance details

Defined in Bitcode

Generic Instruction Source # 
Instance details

Defined in Bitcode

Associated Types

type Rep Instruction :: Type -> Type

Methods

from :: Instruction -> Rep Instruction x

to :: Rep Instruction x -> Instruction

Show Instruction Source # 
Instance details

Defined in Bitcode

Methods

showsPrec :: Int -> Instruction -> ShowS

show :: Instruction -> String

showList :: [Instruction] -> ShowS

Eq Instruction Source # 
Instance details

Defined in Bitcode

Methods

(==) :: Instruction -> Instruction -> Bool

(/=) :: Instruction -> Instruction -> Bool

Ord Instruction Source # 
Instance details

Defined in Bitcode

type Rep Instruction Source # 
Instance details

Defined in Bitcode

type Rep Instruction = D1 ('MetaData "Instruction" "Bitcode" "dhscanner-bitcode-1.0.10-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 for translating common programming languages

Instances

Instances details
FromJSON InstructionContent Source # 
Instance details

Defined in Bitcode

ToJSON InstructionContent Source # 
Instance details

Defined in Bitcode

Generic InstructionContent Source # 
Instance details

Defined in Bitcode

Associated Types

type Rep InstructionContent :: Type -> Type

Show InstructionContent Source # 
Instance details

Defined in Bitcode

Methods

showsPrec :: Int -> InstructionContent -> ShowS

show :: InstructionContent -> String

showList :: [InstructionContent] -> ShowS

Eq InstructionContent Source # 
Instance details

Defined in Bitcode

Ord InstructionContent Source # 
Instance details

Defined in Bitcode

type Rep InstructionContent Source # 
Instance details

Defined in Bitcode

type Rep InstructionContent = D1 ('MetaData "InstructionContent" "Bitcode" "dhscanner-bitcode-1.0.10-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 "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 "UnresolvedRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnresolvedRefContent))) :+: (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 Value Source #

Instances

Instances details
FromJSON Value Source # 
Instance details

Defined in Bitcode

ToJSON Value Source # 
Instance details

Defined in Bitcode

Generic Value Source # 
Instance details

Defined in Bitcode

Associated Types

type Rep Value :: Type -> Type

Methods

from :: Value -> Rep Value x

to :: Rep Value x -> Value

Show Value Source # 
Instance details

Defined in Bitcode

Methods

showsPrec :: Int -> Value -> ShowS

show :: Value -> String

showList :: [Value] -> ShowS

Eq Value Source # 
Instance details

Defined in Bitcode

Methods

(==) :: Value -> Value -> Bool

(/=) :: Value -> Value -> Bool

Ord Value Source # 
Instance details

Defined in Bitcode

Methods

compare :: Value -> Value -> Ordering

(<) :: Value -> Value -> Bool

(<=) :: Value -> Value -> Bool

(>) :: Value -> Value -> Bool

(>=) :: Value -> Value -> Bool

max :: Value -> Value -> Value

min :: Value -> Value -> Value

type Rep Value Source # 
Instance details

Defined in Bitcode

type Rep Value = D1 ('MetaData "Value" "Bitcode" "dhscanner-bitcode-1.0.10-inplace" 'False) (C1 ('MetaCons "VariableCtor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Variable)) :+: (C1 ('MetaCons "ConstValueCtor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ConstValue)) :+: C1 ('MetaCons "KeywordArgCtor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KeywordArgVariable))))

data Variable Source #

Instances

Instances details
FromJSON Variable Source # 
Instance details

Defined in Bitcode

ToJSON Variable Source # 
Instance details

Defined in Bitcode

Generic Variable Source # 
Instance details

Defined in Bitcode

Associated Types

type Rep Variable :: Type -> Type

Methods

from :: Variable -> Rep Variable x

to :: Rep Variable x -> Variable

Show Variable Source # 
Instance details

Defined in Bitcode

Methods

showsPrec :: Int -> Variable -> ShowS

show :: Variable -> String

showList :: [Variable] -> ShowS

Eq Variable Source # 
Instance details

Defined in Bitcode

Methods

(==) :: Variable -> Variable -> Bool

(/=) :: Variable -> Variable -> Bool

Ord Variable Source # 
Instance details

Defined in Bitcode

Methods

compare :: Variable -> Variable -> Ordering

(<) :: Variable -> Variable -> Bool

(<=) :: Variable -> Variable -> Bool

(>) :: Variable -> Variable -> Bool

(>=) :: Variable -> Variable -> Bool

max :: Variable -> Variable -> Variable

min :: Variable -> Variable -> Variable

type Rep Variable Source # 
Instance details

Defined in Bitcode

type Rep Variable = D1 ('MetaData "Variable" "Bitcode" "dhscanner-bitcode-1.0.10-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))))

data TmpVariable Source #

Instances

Instances details
FromJSON TmpVariable Source # 
Instance details

Defined in Bitcode

ToJSON TmpVariable Source # 
Instance details

Defined in Bitcode

Generic TmpVariable Source # 
Instance details

Defined in Bitcode

Associated Types

type Rep TmpVariable :: Type -> Type

Methods

from :: TmpVariable -> Rep TmpVariable x

to :: Rep TmpVariable x -> TmpVariable

Show TmpVariable Source # 
Instance details

Defined in Bitcode

Methods

showsPrec :: Int -> TmpVariable -> ShowS

show :: TmpVariable -> String

showList :: [TmpVariable] -> ShowS

Eq TmpVariable Source # 
Instance details

Defined in Bitcode

Methods

(==) :: TmpVariable -> TmpVariable -> Bool

(/=) :: TmpVariable -> TmpVariable -> Bool

Ord TmpVariable Source # 
Instance details

Defined in Bitcode

type Rep TmpVariable Source # 
Instance details

Defined in Bitcode

type Rep TmpVariable = D1 ('MetaData "TmpVariable" "Bitcode" "dhscanner-bitcode-1.0.10-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 #

Instances

Instances details
FromJSON SrcVariable Source # 
Instance details

Defined in Bitcode

ToJSON SrcVariable Source # 
Instance details

Defined in Bitcode

Generic SrcVariable Source # 
Instance details

Defined in Bitcode

Associated Types

type Rep SrcVariable :: Type -> Type

Methods

from :: SrcVariable -> Rep SrcVariable x

to :: Rep SrcVariable x -> SrcVariable

Show SrcVariable Source # 
Instance details

Defined in Bitcode

Methods

showsPrec :: Int -> SrcVariable -> ShowS

show :: SrcVariable -> String

showList :: [SrcVariable] -> ShowS

Eq SrcVariable Source # 
Instance details

Defined in Bitcode

Methods

(==) :: SrcVariable -> SrcVariable -> Bool

(/=) :: SrcVariable -> SrcVariable -> Bool

Ord SrcVariable Source # 
Instance details

Defined in Bitcode

type Rep SrcVariable Source # 
Instance details

Defined in Bitcode

type Rep SrcVariable = D1 ('MetaData "SrcVariable" "Bitcode" "dhscanner-bitcode-1.0.10-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 ParamVariable Source #

Instances

Instances details
FromJSON ParamVariable Source # 
Instance details

Defined in Bitcode

ToJSON ParamVariable Source # 
Instance details

Defined in Bitcode

Generic ParamVariable Source # 
Instance details

Defined in Bitcode

Associated Types

type Rep ParamVariable :: Type -> Type

Show ParamVariable Source # 
Instance details

Defined in Bitcode

Methods

showsPrec :: Int -> ParamVariable -> ShowS

show :: ParamVariable -> String

showList :: [ParamVariable] -> ShowS

Eq ParamVariable Source # 
Instance details

Defined in Bitcode

Ord ParamVariable Source # 
Instance details

Defined in Bitcode

type Rep ParamVariable Source # 
Instance details

Defined in Bitcode

type Rep ParamVariable = D1 ('MetaData "ParamVariable" "Bitcode" "dhscanner-bitcode-1.0.10-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))))

data KeywordArgVariable Source #

Constructors

KeywordArgVariable 

Fields

Instances

Instances details
FromJSON KeywordArgVariable Source # 
Instance details

Defined in Bitcode

ToJSON KeywordArgVariable Source # 
Instance details

Defined in Bitcode

Generic KeywordArgVariable Source # 
Instance details

Defined in Bitcode

Associated Types

type Rep KeywordArgVariable :: Type -> Type

Show KeywordArgVariable Source # 
Instance details

Defined in Bitcode

Methods

showsPrec :: Int -> KeywordArgVariable -> ShowS

show :: KeywordArgVariable -> String

showList :: [KeywordArgVariable] -> ShowS

Eq KeywordArgVariable Source # 
Instance details

Defined in Bitcode

Ord KeywordArgVariable Source # 
Instance details

Defined in Bitcode

type Rep KeywordArgVariable Source # 
Instance details

Defined in Bitcode

type Rep KeywordArgVariable = D1 ('MetaData "KeywordArgVariable" "Bitcode" "dhscanner-bitcode-1.0.10-inplace" 'False) (C1 ('MetaCons "KeywordArgVariable" 'PrefixI 'True) (S1 ('MetaSel ('Just "keywordArgName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "keywordArgValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Value)))

data CallContent Source #

Instances

Instances details
FromJSON CallContent Source # 
Instance details

Defined in Bitcode

ToJSON CallContent Source # 
Instance details

Defined in Bitcode

Generic CallContent Source # 
Instance details

Defined in Bitcode

Associated Types

type Rep CallContent :: Type -> Type

Methods

from :: CallContent -> Rep CallContent x

to :: Rep CallContent x -> CallContent

Show CallContent Source # 
Instance details

Defined in Bitcode

Methods

showsPrec :: Int -> CallContent -> ShowS

show :: CallContent -> String

showList :: [CallContent] -> ShowS

Eq CallContent Source # 
Instance details

Defined in Bitcode

Methods

(==) :: CallContent -> CallContent -> Bool

(/=) :: CallContent -> CallContent -> Bool

Ord CallContent Source # 
Instance details

Defined in Bitcode

type Rep CallContent Source # 
Instance details

Defined in Bitcode

type Rep CallContent = D1 ('MetaData "CallContent" "Bitcode" "dhscanner-bitcode-1.0.10-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 [Value]) :*: S1 ('MetaSel ('Just "callLocation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Location))))

data UnresolvedRefContent Source #

Instances

Instances details
FromJSON UnresolvedRefContent Source # 
Instance details

Defined in Bitcode

ToJSON UnresolvedRefContent Source # 
Instance details

Defined in Bitcode

Generic UnresolvedRefContent Source # 
Instance details

Defined in Bitcode

Associated Types

type Rep UnresolvedRefContent :: Type -> Type

Show UnresolvedRefContent Source # 
Instance details

Defined in Bitcode

Methods

showsPrec :: Int -> UnresolvedRefContent -> ShowS

show :: UnresolvedRefContent -> String

showList :: [UnresolvedRefContent] -> ShowS

Eq UnresolvedRefContent Source # 
Instance details

Defined in Bitcode

Ord UnresolvedRefContent Source # 
Instance details

Defined in Bitcode

type Rep UnresolvedRefContent Source # 
Instance details

Defined in Bitcode

type Rep UnresolvedRefContent = D1 ('MetaData "UnresolvedRefContent" "Bitcode" "dhscanner-bitcode-1.0.10-inplace" 'False) (C1 ('MetaCons "UnresolvedRefContent" 'PrefixI 'True) (S1 ('MetaSel ('Just "unresolvedRefOutput") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Variable) :*: (S1 ('MetaSel ('Just "unresolvedRef") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Variable) :*: S1 ('MetaSel ('Just "unresolvedRefLocation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Location))))

data BinopContent Source #

Constructors

BinopContent 

Instances

Instances details
FromJSON BinopContent Source # 
Instance details

Defined in Bitcode

ToJSON BinopContent Source # 
Instance details

Defined in Bitcode

Generic BinopContent Source # 
Instance details

Defined in Bitcode

Associated Types

type Rep BinopContent :: Type -> Type

Show BinopContent Source # 
Instance details

Defined in Bitcode

Methods

showsPrec :: Int -> BinopContent -> ShowS

show :: BinopContent -> String

showList :: [BinopContent] -> ShowS

Eq BinopContent Source # 
Instance details

Defined in Bitcode

Methods

(==) :: BinopContent -> BinopContent -> Bool

(/=) :: BinopContent -> BinopContent -> Bool

Ord BinopContent Source # 
Instance details

Defined in Bitcode

type Rep BinopContent Source # 
Instance details

Defined in Bitcode

type Rep BinopContent = D1 ('MetaData "BinopContent" "Bitcode" "dhscanner-bitcode-1.0.10-inplace" 'False) (C1 ('MetaCons "BinopContent" 'PrefixI 'True) (S1 ('MetaSel ('Just "binopOutput") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Variable) :*: (S1 ('MetaSel ('Just "binopLhs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Value) :*: S1 ('MetaSel ('Just "binopRhs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Value))))

data UnopContent Source #

Constructors

UnopContent 

Instances

Instances details
FromJSON UnopContent Source # 
Instance details

Defined in Bitcode

ToJSON UnopContent Source # 
Instance details

Defined in Bitcode

Generic UnopContent Source # 
Instance details

Defined in Bitcode

Associated Types

type Rep UnopContent :: Type -> Type

Methods

from :: UnopContent -> Rep UnopContent x

to :: Rep UnopContent x -> UnopContent

Show UnopContent Source # 
Instance details

Defined in Bitcode

Methods

showsPrec :: Int -> UnopContent -> ShowS

show :: UnopContent -> String

showList :: [UnopContent] -> ShowS

Eq UnopContent Source # 
Instance details

Defined in Bitcode

Methods

(==) :: UnopContent -> UnopContent -> Bool

(/=) :: UnopContent -> UnopContent -> Bool

Ord UnopContent Source # 
Instance details

Defined in Bitcode

type Rep UnopContent Source # 
Instance details

Defined in Bitcode

type Rep UnopContent = D1 ('MetaData "UnopContent" "Bitcode" "dhscanner-bitcode-1.0.10-inplace" 'False) (C1 ('MetaCons "UnopContent" 'PrefixI 'True) (S1 ('MetaSel ('Just "unopOutput") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Variable) :*: S1 ('MetaSel ('Just "unopLhs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Value)))

data AssumeContent Source #

Constructors

AssumeContent 

Fields

Instances

Instances details
FromJSON AssumeContent Source # 
Instance details

Defined in Bitcode

ToJSON AssumeContent Source # 
Instance details

Defined in Bitcode

Generic AssumeContent Source # 
Instance details

Defined in Bitcode

Associated Types

type Rep AssumeContent :: Type -> Type

Show AssumeContent Source # 
Instance details

Defined in Bitcode

Methods

showsPrec :: Int -> AssumeContent -> ShowS

show :: AssumeContent -> String

showList :: [AssumeContent] -> ShowS

Eq AssumeContent Source # 
Instance details

Defined in Bitcode

Ord AssumeContent Source # 
Instance details

Defined in Bitcode

type Rep AssumeContent Source # 
Instance details

Defined in Bitcode

type Rep AssumeContent = D1 ('MetaData "AssumeContent" "Bitcode" "dhscanner-bitcode-1.0.10-inplace" 'False) (C1 ('MetaCons "AssumeContent" 'PrefixI 'True) (S1 ('MetaSel ('Just "assumeValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Value) :*: S1 ('MetaSel ('Just "assumeTruthy") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))

data ReturnContent Source #

Constructors

ReturnContent 

Fields

Instances

Instances details
FromJSON ReturnContent Source # 
Instance details

Defined in Bitcode

ToJSON ReturnContent Source # 
Instance details

Defined in Bitcode

Generic ReturnContent Source # 
Instance details

Defined in Bitcode

Associated Types

type Rep ReturnContent :: Type -> Type

Show ReturnContent Source # 
Instance details

Defined in Bitcode

Methods

showsPrec :: Int -> ReturnContent -> ShowS

show :: ReturnContent -> String

showList :: [ReturnContent] -> ShowS

Eq ReturnContent Source # 
Instance details

Defined in Bitcode

Ord ReturnContent Source # 
Instance details

Defined in Bitcode

type Rep ReturnContent Source # 
Instance details

Defined in Bitcode

type Rep ReturnContent = D1 ('MetaData "ReturnContent" "Bitcode" "dhscanner-bitcode-1.0.10-inplace" 'False) (C1 ('MetaCons "ReturnContent" 'PrefixI 'True) (S1 ('MetaSel ('Just "returnValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Value))))

data AssignContent Source #

Instances

Instances details
FromJSON AssignContent Source # 
Instance details

Defined in Bitcode

ToJSON AssignContent Source # 
Instance details

Defined in Bitcode

Generic AssignContent Source # 
Instance details

Defined in Bitcode

Associated Types

type Rep AssignContent :: Type -> Type

Show AssignContent Source # 
Instance details

Defined in Bitcode

Methods

showsPrec :: Int -> AssignContent -> ShowS

show :: AssignContent -> String

showList :: [AssignContent] -> ShowS

Eq AssignContent Source # 
Instance details

Defined in Bitcode

Ord AssignContent Source # 
Instance details

Defined in Bitcode

type Rep AssignContent Source # 
Instance details

Defined in Bitcode

type Rep AssignContent = D1 ('MetaData "AssignContent" "Bitcode" "dhscanner-bitcode-1.0.10-inplace" 'False) (C1 ('MetaCons "AssignContent" 'PrefixI 'True) (S1 ('MetaSel ('Just "assignOutput") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Variable) :*: S1 ('MetaSel ('Just "assignInput") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Value)))

data ConstValue Source #

Instances

Instances details
FromJSON ConstValue Source # 
Instance details

Defined in Bitcode

ToJSON ConstValue Source # 
Instance details

Defined in Bitcode

Generic ConstValue Source # 
Instance details

Defined in Bitcode

Associated Types

type Rep ConstValue :: Type -> Type

Methods

from :: ConstValue -> Rep ConstValue x

to :: Rep ConstValue x -> ConstValue

Show ConstValue Source # 
Instance details

Defined in Bitcode

Methods

showsPrec :: Int -> ConstValue -> ShowS

show :: ConstValue -> String

showList :: [ConstValue] -> ShowS

Eq ConstValue Source # 
Instance details

Defined in Bitcode

Methods

(==) :: ConstValue -> ConstValue -> Bool

(/=) :: ConstValue -> ConstValue -> Bool

Ord ConstValue Source # 
Instance details

Defined in Bitcode

type Rep ConstValue Source # 
Instance details

Defined in Bitcode

type Rep ConstValue = D1 ('MetaData "ConstValue" "Bitcode" "dhscanner-bitcode-1.0.10-inplace" 'False) ((C1 ('MetaCons "ConstIntValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ConstInt)) :+: C1 ('MetaCons "ConstStrValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ConstStr))) :+: (C1 ('MetaCons "ConstBoolValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ConstBool)) :+: C1 ('MetaCons "ConstNullValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ConstNull))))

data FieldReadContent Source #

Instances

Instances details
FromJSON FieldReadContent Source # 
Instance details

Defined in Bitcode

ToJSON FieldReadContent Source # 
Instance details

Defined in Bitcode

Generic FieldReadContent Source # 
Instance details

Defined in Bitcode

Associated Types

type Rep FieldReadContent :: Type -> Type

Show FieldReadContent Source # 
Instance details

Defined in Bitcode

Methods

showsPrec :: Int -> FieldReadContent -> ShowS

show :: FieldReadContent -> String

showList :: [FieldReadContent] -> ShowS

Eq FieldReadContent Source # 
Instance details

Defined in Bitcode

Ord FieldReadContent Source # 
Instance details

Defined in Bitcode

type Rep FieldReadContent Source # 
Instance details

Defined in Bitcode

type Rep FieldReadContent = D1 ('MetaData "FieldReadContent" "Bitcode" "dhscanner-bitcode-1.0.10-inplace" 'False) (C1 ('MetaCons "FieldReadContent" 'PrefixI 'True) (S1 ('MetaSel ('Just "fieldReadOutput") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Variable) :*: (S1 ('MetaSel ('Just "fieldReadInput") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Variable) :*: S1 ('MetaSel ('Just "fieldReadName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FieldName))))

data FieldWriteContent Source #

Instances

Instances details
FromJSON FieldWriteContent Source # 
Instance details

Defined in Bitcode

ToJSON FieldWriteContent Source # 
Instance details

Defined in Bitcode

Generic FieldWriteContent Source # 
Instance details

Defined in Bitcode

Associated Types

type Rep FieldWriteContent :: Type -> Type

Show FieldWriteContent Source # 
Instance details

Defined in Bitcode

Methods

showsPrec :: Int -> FieldWriteContent -> ShowS

show :: FieldWriteContent -> String

showList :: [FieldWriteContent] -> ShowS

Eq FieldWriteContent Source # 
Instance details

Defined in Bitcode

Ord FieldWriteContent Source # 
Instance details

Defined in Bitcode

type Rep FieldWriteContent Source # 
Instance details

Defined in Bitcode

type Rep FieldWriteContent = D1 ('MetaData "FieldWriteContent" "Bitcode" "dhscanner-bitcode-1.0.10-inplace" 'False) (C1 ('MetaCons "FieldWriteContent" 'PrefixI 'True) (S1 ('MetaSel ('Just "fieldWriteOutput") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Variable) :*: (S1 ('MetaSel ('Just "fieldWriteName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FieldName) :*: S1 ('MetaSel ('Just "fieldWriteInput") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Value))))

data SubscriptReadContent Source #

Instances

Instances details
FromJSON SubscriptReadContent Source # 
Instance details

Defined in Bitcode

ToJSON SubscriptReadContent Source # 
Instance details

Defined in Bitcode

Generic SubscriptReadContent Source # 
Instance details

Defined in Bitcode

Associated Types

type Rep SubscriptReadContent :: Type -> Type

Show SubscriptReadContent Source # 
Instance details

Defined in Bitcode

Methods

showsPrec :: Int -> SubscriptReadContent -> ShowS

show :: SubscriptReadContent -> String

showList :: [SubscriptReadContent] -> ShowS

Eq SubscriptReadContent Source # 
Instance details

Defined in Bitcode

Ord SubscriptReadContent Source # 
Instance details

Defined in Bitcode

type Rep SubscriptReadContent Source # 
Instance details

Defined in Bitcode

type Rep SubscriptReadContent = D1 ('MetaData "SubscriptReadContent" "Bitcode" "dhscanner-bitcode-1.0.10-inplace" 'False) (C1 ('MetaCons "SubscriptReadContent" 'PrefixI 'True) (S1 ('MetaSel ('Just "subscriptReadOutput") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Variable) :*: (S1 ('MetaSel ('Just "subscriptReadInput") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Variable) :*: S1 ('MetaSel ('Just "subscriptReadIdx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Value))))

data SubscriptWriteContent Source #

Instances

Instances details
FromJSON SubscriptWriteContent Source # 
Instance details

Defined in Bitcode

ToJSON SubscriptWriteContent Source # 
Instance details

Defined in Bitcode

Generic SubscriptWriteContent Source # 
Instance details

Defined in Bitcode

Associated Types

type Rep SubscriptWriteContent :: Type -> Type

Show SubscriptWriteContent Source # 
Instance details

Defined in Bitcode

Methods

showsPrec :: Int -> SubscriptWriteContent -> ShowS

show :: SubscriptWriteContent -> String

showList :: [SubscriptWriteContent] -> ShowS

Eq SubscriptWriteContent Source # 
Instance details

Defined in Bitcode

Ord SubscriptWriteContent Source # 
Instance details

Defined in Bitcode

type Rep SubscriptWriteContent Source # 
Instance details

Defined in Bitcode

type Rep SubscriptWriteContent = D1 ('MetaData "SubscriptWriteContent" "Bitcode" "dhscanner-bitcode-1.0.10-inplace" 'False) (C1 ('MetaCons "SubscriptWriteContent" 'PrefixI 'True) (S1 ('MetaSel ('Just "subscriptWriteOutput") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Variable) :*: (S1 ('MetaSel ('Just "subscriptWriteIdx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Value) :*: S1 ('MetaSel ('Just "subscriptWriteInput") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Value))))

data ParamDeclContent Source #

Instances

Instances details
FromJSON ParamDeclContent Source # 
Instance details

Defined in Bitcode

ToJSON ParamDeclContent Source # 
Instance details

Defined in Bitcode

Generic ParamDeclContent Source # 
Instance details

Defined in Bitcode

Associated Types

type Rep ParamDeclContent :: Type -> Type

Show ParamDeclContent Source # 
Instance details

Defined in Bitcode

Methods

showsPrec :: Int -> ParamDeclContent -> ShowS

show :: ParamDeclContent -> String

showList :: [ParamDeclContent] -> ShowS

Eq ParamDeclContent Source # 
Instance details

Defined in Bitcode

Ord ParamDeclContent Source # 
Instance details

Defined in Bitcode

type Rep ParamDeclContent Source # 
Instance details

Defined in Bitcode

type Rep ParamDeclContent = D1 ('MetaData "ParamDeclContent" "Bitcode" "dhscanner-bitcode-1.0.10-inplace" 'False) (C1 ('MetaCons "ParamDeclContent" 'PrefixI 'True) (S1 ('MetaSel ('Just "paramVariable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ParamVariable)))