clash-lib-1.4.3: Clash: a functional hardware description language - As a library
Copyright(C) 2012-2016 University of Twente
2016 Myrtle Software Ltd
2017 Google Inc.
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Clash.Core.Type

Description

Types in CoreHW

Synopsis

Documentation

data Type Source #

Types in CoreHW: function and polymorphic types

Constructors

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

Instances details
Eq Type Source # 
Instance details

Defined in Clash.Core.Subst

Methods

(==) :: Type -> Type -> Bool #

(/=) :: Type -> Type -> Bool #

Ord Type Source # 
Instance details

Defined in Clash.Core.Subst

Methods

compare :: Type -> Type -> Ordering #

(<) :: Type -> Type -> Bool #

(<=) :: Type -> Type -> Bool #

(>) :: Type -> Type -> Bool #

(>=) :: Type -> Type -> Bool #

max :: Type -> Type -> Type #

min :: Type -> Type -> Type #

Show Type Source # 
Instance details

Defined in Clash.Core.Type

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

Generic Type Source # 
Instance details

Defined in Clash.Core.Type

Associated Types

type Rep Type :: Type -> Type #

Methods

from :: Type -> Rep Type x #

to :: Rep Type x -> Type #

Hashable Type Source # 
Instance details

Defined in Clash.Core.Type

Methods

hashWithSalt :: Int -> Type -> Int #

hash :: Type -> Int #

Binary Type Source # 
Instance details

Defined in Clash.Core.Type

Methods

put :: Type -> Put #

get :: Get Type #

putList :: [Type] -> Put #

NFData Type Source # 
Instance details

Defined in Clash.Core.Type

Methods

rnf :: Type -> () #

ClashPretty Type Source # 
Instance details

Defined in Clash.Core.Pretty

Methods

clashPretty :: Type -> Doc () Source #

PrettyPrec Type Source # 
Instance details

Defined in Clash.Core.Pretty

type Rep Type Source # 
Instance details

Defined in Clash.Core.Type

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

Instances details
Show TypeView Source # 
Instance details

Defined in Clash.Core.Type

data ConstTy Source #

Type Constants

Constructors

TyCon !TyConName

TyCon type

Arrow

Function type

Instances

Instances details
Eq ConstTy Source # 
Instance details

Defined in Clash.Core.Type

Methods

(==) :: ConstTy -> ConstTy -> Bool #

(/=) :: ConstTy -> ConstTy -> Bool #

Ord ConstTy Source # 
Instance details

Defined in Clash.Core.Type

Show ConstTy Source # 
Instance details

Defined in Clash.Core.Type

Generic ConstTy Source # 
Instance details

Defined in Clash.Core.Type

Associated Types

type Rep ConstTy :: Type -> Type #

Methods

from :: ConstTy -> Rep ConstTy x #

to :: Rep ConstTy x -> ConstTy #

Hashable ConstTy Source # 
Instance details

Defined in Clash.Core.Type

Methods

hashWithSalt :: Int -> ConstTy -> Int #

hash :: ConstTy -> Int #

Binary ConstTy Source # 
Instance details

Defined in Clash.Core.Type

Methods

put :: ConstTy -> Put #

get :: Get ConstTy #

putList :: [ConstTy] -> Put #

NFData ConstTy Source # 
Instance details

Defined in Clash.Core.Type

Methods

rnf :: ConstTy -> () #

type Rep ConstTy Source # 
Instance details

Defined in Clash.Core.Type

type Rep ConstTy = D1 ('MetaData "ConstTy" "Clash.Core.Type" "clash-lib-1.4.3-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))

data LitTy Source #

Literal Types

Constructors

NumTy !Integer 
SymTy !String 

Instances

Instances details
Eq LitTy Source # 
Instance details

Defined in Clash.Core.Type

Methods

(==) :: LitTy -> LitTy -> Bool #

(/=) :: LitTy -> LitTy -> Bool #

Ord LitTy Source # 
Instance details

Defined in Clash.Core.Type

Methods

compare :: LitTy -> LitTy -> Ordering #

(<) :: LitTy -> LitTy -> Bool #

(<=) :: LitTy -> LitTy -> Bool #

(>) :: LitTy -> LitTy -> Bool #

(>=) :: LitTy -> LitTy -> Bool #

max :: LitTy -> LitTy -> LitTy #

min :: LitTy -> LitTy -> LitTy #

Show LitTy Source # 
Instance details

Defined in Clash.Core.Type

Methods

showsPrec :: Int -> LitTy -> ShowS #

show :: LitTy -> String #

showList :: [LitTy] -> ShowS #

Generic LitTy Source # 
Instance details

Defined in Clash.Core.Type

Associated Types

type Rep LitTy :: Type -> Type #

Methods

from :: LitTy -> Rep LitTy x #

to :: Rep LitTy x -> LitTy #

Hashable LitTy Source # 
Instance details

Defined in Clash.Core.Type

Methods

hashWithSalt :: Int -> LitTy -> Int #

hash :: LitTy -> Int #

Binary LitTy Source # 
Instance details

Defined in Clash.Core.Type

Methods

put :: LitTy -> Put #

get :: Get LitTy #

putList :: [LitTy] -> Put #

NFData LitTy Source # 
Instance details

Defined in Clash.Core.Type

Methods

rnf :: LitTy -> () #

Pretty LitTy Source # 
Instance details

Defined in Clash.Core.Pretty

Methods

pretty :: LitTy -> Doc ann #

prettyList :: [LitTy] -> Doc ann #

PrettyPrec LitTy Source # 
Instance details

Defined in Clash.Core.Pretty

type Rep LitTy Source # 
Instance details

Defined in Clash.Core.Type

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

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".

typeKind :: TyConMap -> 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

mkPolyFunTy Source #

Arguments

:: Type

Result type

-> [Either TyVar Type]

List of quantifiers and function argument types

-> Type 

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?

isPolyTy :: Type -> Bool Source #

Is a type polymorphic?

isFunTy :: TyConMap -> Type -> Bool Source #

Is a type a function type?

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

normalizeType :: TyConMap -> Type -> Type Source #

Normalize a type, looking through Signals and newtypes

For example: Signal a (Vec (6-1) (Unsigned (3+1))) normalizes to Vec 5 (Unsigned 4)

typeAttrs :: Type -> [Attr'] Source #

Extract attributes from type. Will return an empty list if this is an AnnType with an empty list AND if this is not an AnnType at all.