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

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

Clash.Core.DataCon

Description

Data Constructors in CoreHW

Synopsis

Documentation

data DataCon Source #

Data Constructor

Constructors

MkData 

Fields

  • dcName :: !DcName

    Name of the DataCon

  • dcTag :: !ConTag

    Syntactical position in the type definition

  • dcType :: !Type

    Type of the 'DataCon

  • dcUnivTyVars :: [TyName]

    Universally quantified type-variables, these type variables are also part of the result type of the DataCon

  • dcExtTyVars :: [TyName]

    Existentially quantified type-variables, these type variables are not part of the result of the DataCon, but only of the arguments.

  • dcArgTys :: [Type]

    Argument types

Instances
Eq DataCon Source # 
Instance details

Methods

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

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

Ord DataCon Source # 
Instance details
Show DataCon Source # 
Instance details
Generic DataCon Source # 
Instance details

Associated Types

type Rep DataCon :: * -> * #

Methods

from :: DataCon -> Rep DataCon x #

to :: Rep DataCon x -> DataCon #

NFData DataCon Source # 
Instance details

Methods

rnf :: DataCon -> () #

Hashable DataCon Source # 
Instance details

Methods

hashWithSalt :: Int -> DataCon -> Int

hash :: DataCon -> Int

Alpha DataCon Source # 
Instance details

Methods

aeq' :: AlphaCtx -> DataCon -> DataCon -> Bool

fvAny' :: (Contravariant f, Applicative f) => AlphaCtx -> (AnyName -> f AnyName) -> DataCon -> f DataCon

close :: AlphaCtx -> NamePatFind -> DataCon -> DataCon

open :: AlphaCtx -> NthPatFind -> DataCon -> DataCon

isPat :: DataCon -> DisjointSet AnyName

isTerm :: DataCon -> All

isEmbed :: DataCon -> Bool

nthPatFind :: DataCon -> NthPatFind

namePatFind :: DataCon -> NamePatFind

swaps' :: AlphaCtx -> Perm AnyName -> DataCon -> DataCon

lfreshen' :: LFresh m => AlphaCtx -> DataCon -> (DataCon -> Perm AnyName -> m b) -> m b

freshen' :: Fresh m => AlphaCtx -> DataCon -> m (DataCon, Perm AnyName)

acompare' :: AlphaCtx -> DataCon -> DataCon -> Ordering

Pretty DataCon Source # 
Instance details

Methods

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

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

Subst a DataCon Source # 
Instance details

Methods

isvar :: DataCon -> Maybe (SubstName DataCon a)

isCoerceVar :: DataCon -> Maybe (SubstCoerce DataCon a)

subst :: Name a -> a -> DataCon -> DataCon

substs :: [(Name a, a)] -> DataCon -> DataCon

type Rep DataCon Source # 
Instance details

type DcName = Name DataCon Source #

DataCon reference

type ConTag = Int Source #

Syntactical position of the DataCon in the type definition

dataConInstArgTys :: DataCon -> [Type] -> Maybe [Type] Source #

Given a DataCon and a list of types, the type variables of the DataCon type are substituted for the list of types. The argument types are returned.

The list of types should be equal to the number of type variables, otherwise Nothing is returned.