clash-lib-0.2.1: CAES Language for Synchronous Hardware - As a Library

Safe HaskellNone
LanguageHaskell2010

CLaSH.Core.Type

Description

Types in CoreHW

Synopsis

Documentation

data Type Source

Types in CoreHW: function and polymorphic types

Constructors

VarTy Kind TyName

Type variable

ConstTy ConstTy

Type constant

ForAllTy (Bind TyVar Type)

Polymorphic Type

AppTy Type Type

Type Application

LitTy LitTy

Type literal

data TypeView Source

An easier view on types

Constructors

FunTy Type Type

Function type

TyConApp TyConName [Type]

Applied TyCon

OtherType Type

Neither of the above

Instances

data ConstTy Source

Type Constants

Constructors

TyCon TyConName

TyCon type

Arrow

Function type

data LitTy Source

Literal Types

Constructors

NumTy Int 
SymTy String 

Instances

Show LitTy 
NFData LitTy 
Rep LitTy 
Alpha LitTy 
Pretty LitTy 
(Sat (ctx0 Int), Sat (ctx0 String)) => Rep1 ctx LitTy 
Subst Term LitTy 
Subst Type LitTy 

type Kind = Type Source

The level above types

type KindOrType = Type Source

Either a Kind or a Type

type KiName = Name Kind Source

Reference to a Kind

type TyName = Name Type Source

Reference to a Type

type TyVar = Var Type Source

Type variable

tyView :: Type -> TypeView Source

An easier view on types

coreView :: HashMap TyConName TyCon -> Type -> TypeView Source

A view on types in which Signal types and newtypes are transparent

transparentTy :: Type -> Type Source

A transformation that renders Signal types transparent

typeKind :: HashMap TyConName TyCon -> Type -> Kind Source

Determine the kind of a type

mkTyConTy :: TyConName -> Type Source

Make a Type out of a TyCon

mkFunTy :: Type -> Type -> Type Source

Make a function type of an argument and result type

mkTyConApp :: TyConName -> [Type] -> Type Source

Make a TyCon Application out of a TyCon and a list of argument types

splitFunTy :: HashMap TyConName TyCon -> 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

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 TyConName TyCon -> Type -> Bool Source

Is a type a polymorphic or function type under coreView?

isPolyTy :: Type -> Bool Source

Is a type polymorphic?

isFunTy :: HashMap TyConName TyCon -> Type -> Bool Source

Is a type a function type?

applyFunTy :: HashMap TyConName TyCon -> Type -> Type -> Type Source

Apply a function type to an argument type and get the result type

applyTy :: Fresh m => Type -> KindOrType -> m Type Source

Substitute the type variable of a type (ForAllTy) with another type