| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Cryptol.Prims.Syntax
Synopsis
- data PrimTy = PrimTy {
- primTyCon :: !TCon
- primTyIdent :: !Ident
- primTyDoc :: !String
- primTyFixity :: !(Maybe Fixity)
- primTyList :: [PrimTy]
- primTyIx :: Ord a => (PrimTy -> Maybe a) -> a -> Maybe PrimTy
- primTyFromPName :: PName -> Maybe PrimTy
- primTyFromTC :: TCon -> Maybe PrimTy
- primTyFromTF :: TFun -> Maybe PrimTy
- primTyFromPC :: PC -> Maybe PrimTy
- data Kind
- class HasKind t where
- data TCon
- data PC
- data TC
- data UserTC = UserTC Name Kind
- data TCErrorMessage = TCErrorMessage {
- tcErrorMessage :: !String
- data TFun
Documentation
Information about a user visible built-in type.
Constructors
| PrimTy | |
Fields
| |
primTyList :: [PrimTy] Source #
This list should contain all user-visible built-in types.
primTyIx :: Ord a => (PrimTy -> Maybe a) -> a -> Maybe PrimTy Source #
Construct an index for quick lookup of primtys.
Kinds, classify types.
Instances
| Eq Kind Source # | |
| Ord Kind Source # | |
| Show Kind Source # | |
| Generic Kind Source # | |
| NFData Kind Source # | |
Defined in Cryptol.Prims.Syntax | |
| PP Kind Source # | |
| type Rep Kind Source # | |
Defined in Cryptol.Prims.Syntax type Rep Kind = D1 (MetaData "Kind" "Cryptol.Prims.Syntax" "cryptol-2.6.0-24w5HMDd2znGLrodkM4xJM" False) ((C1 (MetaCons "KType" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "KNum" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "KProp" PrefixI False) (U1 :: * -> *) :+: 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)))) | |
class HasKind t where Source #
Minimal complete definition
Type constants.
Instances
Predicate symbols.
If you add additional user-visible constructors, please update primTys.
Constructors
| PEqual | _ == _ |
| PNeq | _ /= _ |
| PGeq | _ >= _ |
| PFin | fin _ |
| PHas Selector |
|
| PZero | Zero _ |
| PLogic | Logic _ |
| PArith | Arith _ |
| PCmp | Cmp _ |
| PSignedCmp | SignedCmp _ |
| PLiteral | Literal _ _ |
| 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 |
| TCIntMod | Z _ |
| TCSeq | [_] _ |
| TCFun | _ -> _ |
| TCTuple Int | (_, _, _) |
| TCNewtype UserTC | user-defined, |
Instances
Instances
| Eq UserTC Source # | |
| Ord UserTC Source # | |
| Show UserTC Source # | |
| Generic UserTC Source # | |
| NFData UserTC Source # | |
Defined in Cryptol.Prims.Syntax | |
| PP UserTC Source # | |
| HasKind UserTC Source # | |
| type Rep UserTC Source # | |
Defined in Cryptol.Prims.Syntax type Rep UserTC = D1 (MetaData "UserTC" "Cryptol.Prims.Syntax" "cryptol-2.6.0-24w5HMDd2znGLrodkM4xJM" False) (C1 (MetaCons "UserTC" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Kind))) | |
data TCErrorMessage Source #
Constructors
| TCErrorMessage | |
Fields
| |
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 |
| TCLenFromThen |
|
| TCLenFromThenTo |
|