| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Cryptol.TypeCheck.TCon
Documentation
infixPrimTy :: TCon -> Maybe (Ident, Fixity) Source #
This is used for pretty prinitng. XXX: it would be nice to just rely in the info from the Prelude.
Kinds, classify types.
Instances
| Generic Kind Source # | |
| Show Kind Source # | |
| PP Kind Source # | |
| NFData Kind Source # | |
Defined in Cryptol.TypeCheck.TCon | |
| Eq Kind Source # | |
| Ord Kind Source # | |
| type Rep Kind Source # | |
Defined in Cryptol.TypeCheck.TCon type Rep Kind = D1 ('MetaData "Kind" "Cryptol.TypeCheck.TCon" "cryptol-3.3.0-7OIQa8lMv7L2xoAlM9JEI6" 'False) ((C1 ('MetaCons "KType" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KNum" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "KProp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons ":->" ('InfixI 'RightAssociative 5) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Kind) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Kind)))) | |
Type constants.
Instances
| Generic TCon Source # | |
| Show TCon Source # | |
| FreeVars TCon Source # | |
| HasKind TCon Source # | |
| PP TCon Source # | |
| NFData TCon Source # | |
Defined in Cryptol.TypeCheck.TCon | |
| Eq TCon Source # | |
| Ord TCon Source # | |
| type Rep TCon Source # | |
Defined in Cryptol.TypeCheck.TCon type Rep TCon = D1 ('MetaData "TCon" "Cryptol.TypeCheck.TCon" "cryptol-3.3.0-7OIQa8lMv7L2xoAlM9JEI6" 'False) ((C1 ('MetaCons "TC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TC)) :+: C1 ('MetaCons "PC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PC))) :+: (C1 ('MetaCons "TF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TFun)) :+: C1 ('MetaCons "TError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Kind)))) | |
Predicate symbols.
If you add additional user-visible constructors, please update primTys.
Constructors
| PEqual | _ == _ |
| PNeq | _ /= _ |
| PGeq | _ >= _ |
| PFin | fin _ |
| PPrime | prime _ |
| PHas Selector |
|
| PZero | Zero _ |
| PLogic | Logic _ |
| PRing | Ring _ |
| PIntegral | Integral _ |
| PField | Field _ |
| PRound | Round _ |
| PEq | Eq _ |
| PCmp | Cmp _ |
| PSignedCmp | SignedCmp _ |
| PLiteral | Literal _ _ |
| PLiteralLessThan | LiteralLessThan _ _ |
| PFLiteral | FLiteral _ _ _ |
| PValidFloat |
|
| PAnd | This is useful when simplifying things in place |
| PTrue | Ditto |
Instances
1-1 constants.
If you add additional user-visible constructors, please update primTys.
Constructors
| TCNum Integer | Numbers |
| TCInf | Inf |
| TCBit | Bit |
| TCInteger | Integer |
| TCFloat | Float |
| TCIntMod | Z _ |
| TCRational | Rational |
| TCArray | Array _ _ |
| TCSeq | [_] _ |
| TCFun | _ -> _ |
| TCTuple Int | (_, _, _) |
Instances
Built-in type functions.
If you add additional user-visible constructors,
please update primTys in Cryptol.Prims.Types.
Constructors
| TCAdd | : Num -> Num -> Num |
| TCSub | : Num -> Num -> Num |
| TCMul | : Num -> Num -> Num |
| TCDiv | : Num -> Num -> Num |
| TCMod | : Num -> Num -> Num |
| TCExp | : Num -> Num -> Num |
| TCWidth | : Num -> Num |
| TCMin | : Num -> Num -> Num |
| TCMax | : Num -> Num -> Num |
| TCCeilDiv | : Num -> Num -> Num |
| TCCeilMod | : Num -> Num -> Num |
| TCLenFromThenTo |
|