Copyright | (C) 2012-2016 University of Twente 2016 Myrtle Software Ltd 2017 Google Inc. |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | Christiaan Baaij <christiaan.baaij@gmail.com> |
Safe Haskell | None |
Language | Haskell2010 |
Types in CoreHW
Synopsis
- data Type
- data TypeView
- data ConstTy
- data LitTy
- type Kind = Type
- type KindOrType = Type
- type KiName = Name Kind
- type TyName = Name Type
- type TyVar = Var Type
- tyView :: Type -> TypeView
- coreView :: TyConMap -> Type -> Type
- coreView1 :: TyConMap -> Type -> Maybe Type
- typeKind :: TyConMap -> Type -> Kind
- mkTyConTy :: TyConName -> Type
- mkFunTy :: Type -> Type -> Type
- mkPolyFunTy :: Type -> [Either TyVar Type] -> Type
- mkTyConApp :: TyConName -> [Type] -> Type
- splitFunTy :: TyConMap -> Type -> Maybe (Type, Type)
- splitFunTys :: TyConMap -> Type -> ([Type], Type)
- splitFunForallTy :: Type -> ([Either TyVar Type], Type)
- splitCoreFunForallTy :: TyConMap -> Type -> ([Either TyVar Type], Type)
- splitTyConAppM :: Type -> Maybe (TyConName, [Type])
- isPolyFunTy :: Type -> Bool
- isPolyFunCoreTy :: TyConMap -> Type -> Bool
- isPolyTy :: Type -> Bool
- isTypeFamilyApplication :: TyConMap -> Type -> Bool
- isFunTy :: TyConMap -> Type -> Bool
- isClassTy :: TyConMap -> Type -> Bool
- applyFunTy :: TyConMap -> Type -> Type -> Type
- findFunSubst :: TyConMap -> [([Type], Type)] -> [Type] -> Maybe Type
- reduceTypeFamily :: TyConMap -> Type -> Maybe Type
- undefinedTy :: Type
- isIntegerTy :: Type -> Bool
- normalizeType :: TyConMap -> Type -> Type
- varAttrs :: Var a -> [Attr']
- typeAttrs :: Type -> [Attr']
Documentation
Types in CoreHW: function and polymorphic types
VarTy !TyVar | Type variable |
ConstTy !ConstTy | Type constant |
ForAllTy !TyVar !Type | Polymorphic Type |
AppTy !Type !Type | Type Application |
LitTy !LitTy | Type literal |
AnnType [Attr'] !Type | Annotated type, see Clash.Annotations.SynthesisAttributes |
Instances
An easier view on types
Type Constants
Instances
Eq ConstTy Source # | |
Ord ConstTy Source # | |
Show ConstTy Source # | |
Generic ConstTy Source # | |
Hashable ConstTy Source # | |
Defined in Clash.Core.Type | |
Binary ConstTy Source # | |
NFData ConstTy Source # | |
Defined in Clash.Core.Type | |
type Rep ConstTy Source # | |
Defined in Clash.Core.Type type Rep ConstTy = D1 ('MetaData "ConstTy" "Clash.Core.Type" "clash-lib-1.3.0-inplace" 'False) (C1 ('MetaCons "TyCon" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TyConName)) :+: C1 ('MetaCons "Arrow" 'PrefixI 'False) (U1 :: Type -> Type)) |
Literal Types
Instances
Eq LitTy Source # | |
Ord LitTy Source # | |
Show LitTy Source # | |
Generic LitTy Source # | |
Hashable LitTy Source # | |
Defined in Clash.Core.Type | |
Binary LitTy Source # | |
NFData LitTy Source # | |
Defined in Clash.Core.Type | |
Pretty LitTy Source # | |
Defined in Clash.Core.Pretty | |
PrettyPrec LitTy Source # | |
type Rep LitTy Source # | |
Defined in Clash.Core.Type type Rep LitTy = D1 ('MetaData "LitTy" "Clash.Core.Type" "clash-lib-1.3.0-inplace" 'False) (C1 ('MetaCons "NumTy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Integer)) :+: C1 ('MetaCons "SymTy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String))) |
type KindOrType = Type Source #
Either a Kind or a Type
tyView :: Type -> TypeView Source #
An easier view on types
Note [Arrow arguments]
Clash' Arrow type can either have 2 or 4 arguments, depending on who created it. By default it has two arguments: the argument type of a function, and the result type of a function.
So when do we have 4 arguments? When in Haskell/GHC land the arrow was unsaturated. This can happen in instance heads, or in the eta-reduced representation of newtypes. So what are those additional 2 arguments compared to the "normal" function type? They're the kinds of argument and result type.
coreView :: TyConMap -> Type -> Type Source #
A view on types in which newtypes are transparent, the Signal type is transparent, and type functions are evaluated to WHNF (when possible).
Strips away ALL layers. If no layers are found it returns the given type.
coreView1 :: TyConMap -> Type -> Maybe Type Source #
A view on types in which newtypes are transparent, the Signal type is transparent, and type functions are evaluated to WHNF (when possible).
Only strips away one "layer".
Make a polymorphic function type out of a result type and a list of quantifiers and function argument types
mkTyConApp :: TyConName -> [Type] -> Type Source #
Make a TyCon Application out of a TyCon and a list of argument types
splitFunTy :: TyConMap -> Type -> Maybe (Type, Type) Source #
Split a function type in an argument and result type
splitFunForallTy :: Type -> ([Either TyVar Type], Type) Source #
Split a poly-function type in a: list of type-binders and argument types, and the result type
splitCoreFunForallTy :: TyConMap -> Type -> ([Either TyVar Type], Type) Source #
Split a poly-function type in a: list of type-binders and argument types,
and the result type. Looks through Signal
and type functions.
splitTyConAppM :: Type -> Maybe (TyConName, [Type]) Source #
Split a TyCon Application in a TyCon and its arguments
isPolyFunTy :: Type -> Bool Source #
Is a type a polymorphic or function type?
isPolyFunCoreTy :: TyConMap -> Type -> Bool Source #
Is a type a polymorphic or function type under coreView1
?
applyFunTy :: TyConMap -> Type -> Type -> Type Source #
Apply a function type to an argument type and get the result type
undefinedTy :: Type Source #
The type forall a . a
isIntegerTy :: Type -> Bool Source #