clash-lib-0.7: 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 # 

Methods

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

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

Ord TyCon Source # 

Methods

compare :: TyCon -> TyCon -> Ordering #

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

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

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

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

max :: TyCon -> TyCon -> TyCon #

min :: TyCon -> TyCon -> TyCon #

Show TyCon Source # 

Methods

showsPrec :: Int -> TyCon -> ShowS #

show :: TyCon -> String #

showList :: [TyCon] -> ShowS #

Generic TyCon Source # 

Associated Types

type Rep TyCon :: * -> * #

Methods

from :: TyCon -> Rep TyCon x #

to :: Rep TyCon x -> TyCon #

NFData TyCon Source # 

Methods

rnf :: TyCon -> () #

Alpha TyCon Source # 
Pretty TyCon Source # 

Methods

ppr :: LFresh m => TyCon -> m Doc Source #

pprPrec :: LFresh m => Rational -> TyCon -> m Doc Source #

type Rep TyCon Source # 
type Rep TyCon = D1 (MetaData "TyCon" "CLaSH.Core.TyCon" "clash-lib-0.7-83ZNOjNIImPHkX9dasXVwo" False) ((:+:) ((:+:) (C1 (MetaCons "AlgTyCon" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "tyConName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TyConName)) (S1 (MetaSel (Just Symbol "tyConKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Kind))) ((:*:) (S1 (MetaSel (Just Symbol "tyConArity") NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Int)) (S1 (MetaSel (Just Symbol "algTcRhs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 AlgTyConRhs))))) (C1 (MetaCons "FunTyCon" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "tyConName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TyConName)) (S1 (MetaSel (Just Symbol "tyConKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Kind))) ((:*:) (S1 (MetaSel (Just Symbol "tyConArity") NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Int)) (S1 (MetaSel (Just Symbol "tyConSubst") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [([Type], Type)])))))) ((:+:) (C1 (MetaCons "PrimTyCon" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "tyConName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TyConName)) ((:*:) (S1 (MetaSel (Just Symbol "tyConKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Kind)) (S1 (MetaSel (Just Symbol "tyConArity") NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Int))))) (C1 (MetaCons "SuperKindTyCon" PrefixI True) (S1 (MetaSel (Just Symbol "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 :: ([TyName], 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 # 
Generic AlgTyConRhs Source # 

Associated Types

type Rep AlgTyConRhs :: * -> * #

NFData AlgTyConRhs Source # 

Methods

rnf :: AlgTyConRhs -> () #

Alpha AlgTyConRhs Source # 
type Rep AlgTyConRhs Source # 
type Rep AlgTyConRhs = D1 (MetaData "AlgTyConRhs" "CLaSH.Core.TyCon" "clash-lib-0.7-83ZNOjNIImPHkX9dasXVwo" False) ((:+:) (C1 (MetaCons "DataTyCon" PrefixI True) (S1 (MetaSel (Just Symbol "dataCons") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [DataCon]))) (C1 (MetaCons "NewTyCon" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "dataCon") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 DataCon)) (S1 (MetaSel (Just Symbol "ntEtadRhs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ([TyName], 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