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 KiOccName = OccName Kind
- type TyName = Name Type
- type TyOccName = OccName Type
- type TyVar = Var Type
- tyView :: Type -> TypeView
- coreView :: HashMap TyConOccName TyCon -> Type -> Maybe Type
- typeKind :: HashMap TyConOccName TyCon -> Type -> Kind
- mkTyConTy :: TyConName -> Type
- mkFunTy :: Type -> Type -> Type
- mkTyConApp :: TyConName -> [Type] -> Type
- splitFunTy :: HashMap TyConOccName TyCon -> Type -> Maybe (Type, Type)
- splitFunTys :: HashMap TyConOccName TyCon -> Type -> ([Type], Type)
- splitFunForallTy :: Type -> ([Either TyVar Type], Type)
- splitCoreFunForallTy :: HashMap TyConOccName TyCon -> Type -> ([Either TyVar Type], Type)
- splitTyConAppM :: Type -> Maybe (TyConName, [Type])
- isPolyFunTy :: Type -> Bool
- isPolyFunCoreTy :: HashMap TyConOccName TyCon -> Type -> Bool
- isPolyTy :: Type -> Bool
- isFunTy :: HashMap TyConOccName TyCon -> Type -> Bool
- applyFunTy :: HashMap TyConOccName TyCon -> Type -> Type -> Type
- applyTy :: Fresh m => HashMap TyConOccName TyCon -> Type -> KindOrType -> m Type
- findFunSubst :: HashMap TyConOccName TyCon -> [([Type], Type)] -> [Type] -> Maybe Type
- reduceTypeFamily :: HashMap TyConOccName TyCon -> Type -> Maybe Type
- undefinedTy :: Type
- isIntegerTy :: Type -> Bool
- normalizeType :: HashMap TyConOccName TyCon -> Type -> Type
Documentation
Types in CoreHW: function and polymorphic types
VarTy !Kind !TyName | Type variable |
ConstTy !ConstTy | Type constant |
ForAllTy !(Bind TyVar Type) | Polymorphic Type |
AppTy !Type !Type | Type Application |
LitTy !LitTy | Type literal |
Instances
An easier view on types
Type Constants
Instances
Show ConstTy Source # | |
Generic ConstTy Source # | |
NFData ConstTy Source # | |
Defined in Clash.Core.Type | |
Hashable ConstTy Source # | |
Defined in Clash.Core.Type | |
Alpha ConstTy Source # | |
Defined in Clash.Core.Type aeq' :: AlphaCtx -> ConstTy -> ConstTy -> Bool fvAny' :: (Contravariant f, Applicative f) => AlphaCtx -> (AnyName -> f AnyName) -> ConstTy -> f ConstTy close :: AlphaCtx -> NamePatFind -> ConstTy -> ConstTy open :: AlphaCtx -> NthPatFind -> ConstTy -> ConstTy isPat :: ConstTy -> DisjointSet AnyName nthPatFind :: ConstTy -> NthPatFind namePatFind :: ConstTy -> NamePatFind swaps' :: AlphaCtx -> Perm AnyName -> ConstTy -> ConstTy lfreshen' :: LFresh m => AlphaCtx -> ConstTy -> (ConstTy -> Perm AnyName -> m b) -> m b freshen' :: Fresh m => AlphaCtx -> ConstTy -> m (ConstTy, Perm AnyName) | |
Subst a ConstTy Source # | |
type Rep ConstTy Source # | |
Defined in Clash.Core.Type |
Literal Types
Instances
Show LitTy Source # | |
Generic LitTy Source # | |
NFData LitTy Source # | |
Defined in Clash.Core.Type | |
Hashable LitTy Source # | |
Defined in Clash.Core.Type | |
Alpha LitTy Source # | |
Defined in Clash.Core.Type aeq' :: AlphaCtx -> LitTy -> LitTy -> Bool fvAny' :: (Contravariant f, Applicative f) => AlphaCtx -> (AnyName -> f AnyName) -> LitTy -> f LitTy close :: AlphaCtx -> NamePatFind -> LitTy -> LitTy open :: AlphaCtx -> NthPatFind -> LitTy -> LitTy isPat :: LitTy -> DisjointSet AnyName nthPatFind :: LitTy -> NthPatFind namePatFind :: LitTy -> NamePatFind swaps' :: AlphaCtx -> Perm AnyName -> LitTy -> LitTy lfreshen' :: LFresh m => AlphaCtx -> LitTy -> (LitTy -> Perm AnyName -> m b) -> m b freshen' :: Fresh m => AlphaCtx -> LitTy -> m (LitTy, Perm AnyName) | |
Pretty LitTy Source # | |
Subst a LitTy Source # | |
type Rep LitTy Source # | |
Defined in Clash.Core.Type type Rep LitTy = D1 (MetaData "LitTy" "Clash.Core.Type" "clash-lib-0.99.2-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
coreView :: HashMap TyConOccName TyCon -> 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".
mkTyConApp :: TyConName -> [Type] -> Type Source #
Make a TyCon Application out of a TyCon and a list of argument types
splitFunTy :: HashMap TyConOccName TyCon -> Type -> Maybe (Type, Type) Source #
Split a function type in an argument and result type
splitFunTys :: HashMap TyConOccName TyCon -> Type -> ([Type], Type) Source #
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 :: HashMap TyConOccName TyCon -> 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 :: HashMap TyConOccName TyCon -> Type -> Bool Source #
Is a type a polymorphic or function type under coreView
?
applyFunTy :: HashMap TyConOccName TyCon -> Type -> Type -> Type Source #
Apply a function type to an argument type and get the result type
applyTy :: Fresh m => HashMap TyConOccName TyCon -> Type -> KindOrType -> m Type Source #
Substitute the type variable of a type (ForAllTy
) with another type
findFunSubst :: HashMap TyConOccName TyCon -> [([Type], Type)] -> [Type] -> Maybe Type Source #
reduceTypeFamily :: HashMap TyConOccName TyCon -> Type -> Maybe Type Source #
undefinedTy :: Type Source #
The type of GHC.Err.undefined :: forall a . a
isIntegerTy :: Type -> Bool Source #
normalizeType :: HashMap TyConOccName TyCon -> Type -> Type Source #