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

Copyright(C) 2012-2016 University of Twente
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Clash.Core.TyCon

Description

Type Constructors in CoreHW

Synopsis

Documentation

data TyCon Source #

Type Constructor

Constructors

AlgTyCon

Algorithmic DataCons

Fields

FunTyCon

Function TyCons (e.g. type families)

Fields

PrimTyCon

Primitive TyCons

Fields

SuperKindTyCon

To close the loop on the type hierarchy

Fields

Instances
Eq TyCon Source # 
Instance details

Defined in Clash.Core.TyCon

Methods

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

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

Show TyCon Source # 
Instance details

Defined in Clash.Core.TyCon

Methods

showsPrec :: Int -> TyCon -> ShowS #

show :: TyCon -> String #

showList :: [TyCon] -> ShowS #

Generic TyCon Source # 
Instance details

Defined in Clash.Core.TyCon

Associated Types

type Rep TyCon :: Type -> Type #

Methods

from :: TyCon -> Rep TyCon x #

to :: Rep TyCon x -> TyCon #

Binary TyCon Source # 
Instance details

Defined in Clash.Core.TyCon

Methods

put :: TyCon -> Put #

get :: Get TyCon #

putList :: [TyCon] -> Put #

NFData TyCon Source # 
Instance details

Defined in Clash.Core.TyCon

Methods

rnf :: TyCon -> () #

Uniquable TyCon Source # 
Instance details

Defined in Clash.Core.TyCon

PrettyPrec TyCon Source # 
Instance details

Defined in Clash.Core.Pretty

type Rep TyCon Source # 
Instance details

Defined in Clash.Core.TyCon

type Rep TyCon = D1 (MetaData "TyCon" "Clash.Core.TyCon" "clash-lib-1.2.0-inplace" False) ((C1 (MetaCons "AlgTyCon" PrefixI True) ((S1 (MetaSel (Just "tyConUniq") SourceUnpack SourceStrict DecidedStrict) (Rec0 Unique) :*: (S1 (MetaSel (Just "tyConName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TyConName) :*: S1 (MetaSel (Just "tyConKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Kind))) :*: (S1 (MetaSel (Just "tyConArity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: (S1 (MetaSel (Just "algTcRhs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 AlgTyConRhs) :*: S1 (MetaSel (Just "isClassTc") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool)))) :+: C1 (MetaCons "FunTyCon" PrefixI True) ((S1 (MetaSel (Just "tyConUniq") SourceUnpack SourceStrict DecidedStrict) (Rec0 Unique) :*: S1 (MetaSel (Just "tyConName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TyConName)) :*: (S1 (MetaSel (Just "tyConKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Kind) :*: (S1 (MetaSel (Just "tyConArity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "tyConSubst") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [([Type], Type)]))))) :+: (C1 (MetaCons "PrimTyCon" PrefixI True) ((S1 (MetaSel (Just "tyConUniq") SourceUnpack SourceStrict DecidedStrict) (Rec0 Unique) :*: S1 (MetaSel (Just "tyConName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TyConName)) :*: (S1 (MetaSel (Just "tyConKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Kind) :*: S1 (MetaSel (Just "tyConArity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int))) :+: C1 (MetaCons "SuperKindTyCon" PrefixI True) (S1 (MetaSel (Just "tyConUniq") SourceUnpack SourceStrict DecidedStrict) (Rec0 Unique) :*: S1 (MetaSel (Just "tyConName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TyConName))))

type TyConName = Name TyCon Source #

TyCon reference

data AlgTyConRhs Source #

The RHS of an Algebraic Datatype

Constructors

DataTyCon 

Fields

NewTyCon 

Fields

  • dataCon :: !DataCon

    The newtype DataCon

  • ntEtadRhs :: ([TyVar], Type)

    The argument type of the newtype DataCon in eta-reduced form, which is just the representation of the TyCon. The TyName's are the type-variables from the corresponding TyCon.

Instances
Show AlgTyConRhs Source # 
Instance details

Defined in Clash.Core.TyCon

Generic AlgTyConRhs Source # 
Instance details

Defined in Clash.Core.TyCon

Associated Types

type Rep AlgTyConRhs :: Type -> Type #

Binary AlgTyConRhs Source # 
Instance details

Defined in Clash.Core.TyCon

NFData AlgTyConRhs Source # 
Instance details

Defined in Clash.Core.TyCon

Methods

rnf :: AlgTyConRhs -> () #

type Rep AlgTyConRhs Source # 
Instance details

Defined in Clash.Core.TyCon

type Rep AlgTyConRhs = D1 (MetaData "AlgTyConRhs" "Clash.Core.TyCon" "clash-lib-1.2.0-inplace" False) (C1 (MetaCons "DataTyCon" PrefixI True) (S1 (MetaSel (Just "dataCons") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [DataCon])) :+: C1 (MetaCons "NewTyCon" PrefixI True) (S1 (MetaSel (Just "dataCon") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 DataCon) :*: S1 (MetaSel (Just "ntEtadRhs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ([TyVar], Type))))

mkKindTyCon :: TyConName -> Kind -> TyCon Source #

Create a Kind out of a TyConName

isTupleTyConLike :: TyConName -> Bool Source #

Does the TyCon look like a tuple TyCon

tyConDataCons :: TyCon -> [DataCon] Source #

Get the DataCons belonging to a TyCon