| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Lang.Crucible.Syntax.Atoms
Description
Atoms used by the Crucible CFG concrete syntax.
Synopsis
- data Atomic
- atom :: Parser Atomic
- newtype AtomName = AtomName Text
- newtype LabelName = LabelName Text
- newtype RegName = RegName Text
- newtype FunName = FunName Text
- newtype GlobalName = GlobalName Text
- data Keyword- = Defun
- | DefBlock
- | DefGlobal
- | Declare
- | Extern
- | Registers
- | Start
- | SetGlobal
- | SetRef
- | DropRef_
- | Plus
- | Minus
- | Times
- | Div
- | Negate
- | Abs
- | Just_
- | Nothing_
- | FromJust
- | Inj
- | Proj
- | AnyT
- | UnitT
- | BoolT
- | NatT
- | IntegerT
- | RealT
- | ComplexRealT
- | CharT
- | StringT
- | BitvectorT
- | VectorT
- | SequenceT
- | FPT
- | FunT
- | MaybeT
- | VariantT
- | StructT
- | RefT
- | Half_
- | Float_
- | Double_
- | Quad_
- | X86_80_
- | DoubleDouble_
- | Unicode_
- | Char8_
- | Char16_
- | The
- | Equalp
- | Integerp
- | If
- | Not_
- | And_
- | Or_
- | Xor_
- | Mod
- | Lt
- | Le
- | Show
- | StringConcat_
- | StringEmpty_
- | StringLength_
- | ToAny
- | FromAny
- | VectorLit_
- | VectorReplicate_
- | VectorIsEmpty_
- | VectorSize_
- | VectorGetEntry_
- | VectorSetEntry_
- | VectorCons_
- | MkStruct_
- | GetField_
- | SetField_
- | SequenceNil_
- | SequenceCons_
- | SequenceAppend_
- | SequenceIsNil_
- | SequenceLength_
- | SequenceHead_
- | SequenceTail_
- | SequenceUncons_
- | Deref
- | Ref
- | EmptyRef
- | Jump_
- | Return_
- | Branch_
- | MaybeBranch_
- | TailCall_
- | Error_
- | Output_
- | Case
- | Print_
- | PrintLn_
- | Let
- | Fresh
- | Assert_
- | Assume_
- | SetRegister
- | Funcall
- | Breakpoint_
- | BV
- | BVConcat_
- | BVSelect_
- | BVTrunc_
- | BVZext_
- | BVSext_
- | BVNonzero_
- | BoolToBV_
- | BVCarry_
- | BVSCarry_
- | BVSBorrow_
- | BVNot_
- | BVAnd_
- | BVOr_
- | BVXor_
- | BVShl_
- | BVLshr_
- | BVAshr_
- | Sle
- | Slt
- | Sdiv
- | Smod
- | ZeroExt
- | SignExt
- | RNE_
- | RNA_
- | RTP_
- | RTN_
- | RTZ_
- | FPToUBV_
- | FPToSBV_
- | UBVToFP_
- | SBVToFP_
- | BinaryToFP_
- | FPToBinary_
- | FPToReal_
- | RealToFP_
 
The atom datatype
The atoms of the language
Constructors
| Kw !Keyword | Keywords are all the built-in operators and expression formers | 
| Lbl !LabelName | Labels, but not the trailing colon | 
| At !AtomName | Atom names (which look like Scheme symbols) | 
| Rg !RegName | Registers, whose names have a leading single $ | 
| Gl !GlobalName | Global variables, whose names have a leading double $$ | 
| Fn !FunName | Function names, minus the leading @ | 
| Int !Integer | Literal integers | 
| Rat !Rational | Literal rational numbers | 
| Bool !Bool | Literal Booleans | 
| StrLit !Text | Literal strings | 
Individual atoms
The name of an atom (non-keyword identifier)
The name of a label (identifier followed by colon)
Instances
| Show LabelName Source # | |
| Eq LabelName Source # | |
| Ord LabelName Source # | |
| Pretty LabelName Source # | |
| Defined in Lang.Crucible.Syntax.Atoms | |
The name of a register (dollar sign followed by identifier)
The name of a function (at-sign followed by identifier)
newtype GlobalName Source #
The name of a global variable (two dollar signs followed by identifier)
Constructors
| GlobalName Text | 
Instances
| Show GlobalName Source # | |
| Defined in Lang.Crucible.Syntax.Atoms Methods showsPrec :: Int -> GlobalName -> ShowS # show :: GlobalName -> String # showList :: [GlobalName] -> ShowS # | |
| Eq GlobalName Source # | |
| Defined in Lang.Crucible.Syntax.Atoms | |
| Ord GlobalName Source # | |
| Defined in Lang.Crucible.Syntax.Atoms Methods compare :: GlobalName -> GlobalName -> Ordering # (<) :: GlobalName -> GlobalName -> Bool # (<=) :: GlobalName -> GlobalName -> Bool # (>) :: GlobalName -> GlobalName -> Bool # (>=) :: GlobalName -> GlobalName -> Bool # max :: GlobalName -> GlobalName -> GlobalName # min :: GlobalName -> GlobalName -> GlobalName # | |
| Pretty GlobalName Source # | |
| Defined in Lang.Crucible.Syntax.Atoms | |
Individual language keywords (reserved identifiers)
Constructors