Copyright | (C) 2021 QBayLogic B.V. |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | QBayLogic B.V. <devops@qbaylogic.com> |
Safe Haskell | None |
Language | Haskell2010 |
Utility class to extract type information from data which has a type.
Synopsis
- class HasType a where
- coreTypeOf :: a -> Type
- coreKindOf :: HasType a => a -> Kind
- class InferType a where
- inferCoreTypeOf :: TyConMap -> a -> Type
- inferCoreKindOf :: InferType a => TyConMap -> a -> Kind
- applyTypeToArgs :: Term -> TyConMap -> Type -> [Either Term Type] -> Type
- piResultTy :: HasCallStack => TyConMap -> Type -> Type -> Type
- piResultTys :: HasCallStack => TyConMap -> Type -> [Type] -> Type
Documentation
class HasType a where Source #
coreTypeOf :: a -> Type Source #
Instances
HasType Literal Source # | |
Defined in Clash.Core.HasType coreTypeOf :: Literal -> Type Source # | |
HasType TyCon Source # | |
Defined in Clash.Core.HasType coreTypeOf :: TyCon -> Type Source # | |
HasType Type Source # | |
Defined in Clash.Core.HasType coreTypeOf :: Type -> Type Source # | |
HasType DataCon Source # | |
Defined in Clash.Core.HasType coreTypeOf :: DataCon -> Type Source # | |
HasType PrimInfo Source # | |
Defined in Clash.Core.HasType coreTypeOf :: PrimInfo -> Type Source # | |
HasType (Var a) Source # | |
Defined in Clash.Core.HasType coreTypeOf :: Var a -> Type Source # |
coreKindOf :: HasType a => a -> Kind Source #
class InferType a where Source #
inferCoreTypeOf :: TyConMap -> a -> Type Source #
Instances
InferType Type Source # | |
Defined in Clash.Core.HasType | |
InferType Term Source # | |
Defined in Clash.Core.HasType | |
InferType Value Source # | |
Defined in Clash.Core.Evaluator.Types |
Get the result type of a polymorphic function given a list of arguments
piResultTy :: HasCallStack => TyConMap -> Type -> Type -> Type Source #
Like piResultTys
, but only applies a single type. If multiple types are
being applied use piResultTys
, as it is more efficient to only substitute
once with many types.
piResultTys :: HasCallStack => TyConMap -> Type -> [Type] -> Type Source #
(piResultTys f_ty [ty1, ..., tyn])
gives the type of (f ty1 .. tyn)
where f :: f_ty
piResultTys
is interesting because:
f_ty
may have more foralls than there are args- Less obviously, it may have fewer foralls
Fore case 2. think of:
piResultTys (forall a . a) [forall b.b, Int]
This really can happen, such as situations involving undefined
s type:
undefined :: forall a. a
undefined (forall b. b -> b) Int
This term should have the type (Int -> Int)
, but notice that there are
more type args than foralls in undefined
s type.
For efficiency reasons, when there are no foralls, we simply drop arrows from a function type/kind.