Copyright | (C) 2012-2016 University of Twente 2017 Google Inc. |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | Christiaan Baaij <christiaan.baaij@gmail.com> |
Safe Haskell | None |
Language | Haskell2010 |
Term representation in the CoreHW language: System F + LetRec + Case
Documentation
Term representation in the CoreHW language: System F + LetRec + Case
Var !Type !TmName | Variable reference |
Data !DataCon | Datatype constructor |
Literal !Literal | Literal |
Prim !Text !Type | Primitive |
Lam !(Bind Id Term) | Term-abstraction |
TyLam !(Bind TyVar Term) | Type-abstraction |
App !Term !Term | Application |
TyApp !Term !Type | Type-application |
Letrec !(Bind (Rec [LetBinding]) Term) | Recursive let-binding |
Case !Term !Type [Alt] | Case-expression: subject, type of alternatives, list of alternatives |
Cast !Term !Type !Type | Cast a term from one type to another |
Instances
type LetBinding = (Id, Embed Term) Source #
Binding in a LetRec construct
Patterns in the LHS of a case-decomposition
DataPat !(Embed DataCon) !(Rebind [TyVar] [Id]) | Datatype pattern, '[TyVar]' bind existentially-quantified type-variables of a DataCon |
LitPat !(Embed Literal) | Literal pattern |
DefaultPat | Default pattern |
Instances
Eq Pat Source # | |
Show Pat Source # | |
Generic Pat Source # | |
NFData Pat Source # | |
Hashable Pat Source # | |
Alpha Pat Source # | |
aeq' :: AlphaCtx -> Pat -> Pat -> Bool fvAny' :: (Contravariant f, Applicative f) => AlphaCtx -> (AnyName -> f AnyName) -> Pat -> f Pat close :: AlphaCtx -> NamePatFind -> Pat -> Pat open :: AlphaCtx -> NthPatFind -> Pat -> Pat isPat :: Pat -> DisjointSet AnyName nthPatFind :: Pat -> NthPatFind namePatFind :: Pat -> NamePatFind swaps' :: AlphaCtx -> Perm AnyName -> Pat -> Pat lfreshen' :: LFresh m => AlphaCtx -> Pat -> (Pat -> Perm AnyName -> m b) -> m b freshen' :: Fresh m => AlphaCtx -> Pat -> m (Pat, Perm AnyName) | |
Pretty Pat Source # | |
Subst Term Pat Source # | |
Subst Type Pat Source # | |
type Rep Pat Source # | |
type Rep Pat = D1 (MetaData "Pat" "Clash.Core.Term" "clash-lib-0.99.1-inplace" False) (C1 (MetaCons "DataPat" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Embed DataCon)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Rebind [TyVar] [Id]))) :+: (C1 (MetaCons "LitPat" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Embed Literal))) :+: C1 (MetaCons "DefaultPat" PrefixI False) (U1 :: * -> *))) |