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
Synopsis
- data Term
- type TmName = Name Term
- type LetBinding = (Id, Term)
- data Pat
- type Alt = (Pat, Term)
- data TickInfo
- data NameMod
- data PrimInfo = PrimInfo {
- primType :: !Type
- primWorkInfo :: !WorkInfo
- data WorkInfo
- data CoreContext
- type Context = [CoreContext]
- isLambdaBodyCtx :: CoreContext -> Bool
- isTickCtx :: CoreContext -> Bool
- collectArgs :: Term -> (Term, [Either Term Type])
- collectArgsTicks :: Term -> (Term, [Either Term Type], [TickInfo])
- collectTicks :: Term -> (Term, [TickInfo])
- primArg :: Term -> Maybe (Text, Int, Int)
- partitionTicks :: [TickInfo] -> ([TickInfo], [TickInfo])
Documentation
Term representation in the CoreHW language: System F + LetRec + Case
Var !Id | Variable reference |
Data !DataCon | Datatype constructor |
Literal !Literal | Literal |
Prim !Text !PrimInfo | Primitive |
Lam !Id Term | Term-abstraction |
TyLam !TyVar Term | Type-abstraction |
App !Term !Term | Application |
TyApp !Term !Type | Type-application |
Letrec [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 |
Tick !TickInfo !Term | Annotated term |
Instances
type LetBinding = (Id, Term) Source #
Binding in a LetRec construct
Patterns in the LHS of a case-decomposition
DataPat !DataCon [TyVar] [Id] | Datatype pattern, '[TyVar]' bind existentially-quantified type-variables of a DataCon |
LitPat !Literal | Literal pattern |
DefaultPat | Default pattern |
Instances
Eq Pat Source # | |
Ord Pat Source # | |
Show Pat Source # | |
Generic Pat Source # | |
Hashable Pat Source # | |
Defined in Clash.Core.Term | |
Binary Pat Source # | |
NFData Pat Source # | |
Defined in Clash.Core.Term | |
PrettyPrec Pat Source # | |
type Rep Pat Source # | |
Defined in Clash.Core.Term type Rep Pat = D1 ('MetaData "Pat" "Clash.Core.Term" "clash-lib-0.9999-inplace" 'False) (C1 ('MetaCons "DataPat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DataCon) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TyVar]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Id]))) :+: (C1 ('MetaCons "LitPat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Literal)) :+: C1 ('MetaCons "DefaultPat" 'PrefixI 'False) (U1 :: Type -> Type))) |
SrcSpan !SrcSpan | Source tick, will get added by GHC by running clash with `-g` |
NameMod !NameMod !Type | Modifier for naming module instantiations and registers, are added by
the user by using the functions |
Instances
Eq TickInfo Source # | |
Show TickInfo Source # | |
Generic TickInfo Source # | |
Hashable TickInfo Source # | |
Defined in Clash.Core.Term | |
Binary TickInfo Source # | |
NFData TickInfo Source # | |
Defined in Clash.Core.Term | |
PrettyPrec TickInfo Source # | |
type Rep TickInfo Source # | |
Defined in Clash.Core.Term type Rep TickInfo = D1 ('MetaData "TickInfo" "Clash.Core.Term" "clash-lib-0.9999-inplace" 'False) (C1 ('MetaCons "SrcSpan" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SrcSpan)) :+: C1 ('MetaCons "NameMod" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NameMod) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Type))) |
Tag to indicate which instance/register name modifier was used
PrefixName | Clash.Magic.prefixName |
SuffixName | Clash.Magic.suffixName |
SetName | Clash.Magic.setName |
PrimInfo | |
|
Instances
Show PrimInfo Source # | |
Generic PrimInfo Source # | |
Hashable PrimInfo Source # | |
Defined in Clash.Core.Term | |
Binary PrimInfo Source # | |
NFData PrimInfo Source # | |
Defined in Clash.Core.Term | |
type Rep PrimInfo Source # | |
Defined in Clash.Core.Term type Rep PrimInfo = D1 ('MetaData "PrimInfo" "Clash.Core.Term" "clash-lib-0.9999-inplace" 'False) (C1 ('MetaCons "PrimInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "primType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Type) :*: S1 ('MetaSel ('Just "primWorkInfo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 WorkInfo))) |
WorkConstant | Ignores its arguments, and outputs a constant |
WorkNever | Never adds any work |
WorkVariable | Does work when the arguments are variable |
WorkAlways | Performs work regardless of whether the variables are constant or variable; these are things like clock or reset generators |
Instances
Show WorkInfo Source # | |
Generic WorkInfo Source # | |
Hashable WorkInfo Source # | |
Defined in Clash.Core.Term | |
Binary WorkInfo Source # | |
NFData WorkInfo Source # | |
Defined in Clash.Core.Term | |
type Rep WorkInfo Source # | |
Defined in Clash.Core.Term type Rep WorkInfo = D1 ('MetaData "WorkInfo" "Clash.Core.Term" "clash-lib-0.9999-inplace" 'False) ((C1 ('MetaCons "WorkConstant" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WorkNever" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "WorkVariable" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WorkAlways" 'PrefixI 'False) (U1 :: Type -> Type))) |
data CoreContext Source #
Context in which a term appears
AppFun | Function position of an application |
AppArg (Maybe (Text, Int, Int)) | Argument position of an application. If this is an argument applied to a primitive, a tuple is defined containing (name of the primitive, #type args, #term args) |
TyAppC | Function position of a type application |
LetBinding Id [Id] | RHS of a Let-binder with the sibling LHS' |
LetBody [Id] | Body of a Let-binding with the bound LHS' |
LamBody Id | Body of a lambda-term with the abstracted variable |
TyLamBody TyVar | Body of a TyLambda-term with the abstracted type-variable |
CaseAlt Pat | RHS of a case-alternative with the bound pattern on the LHS |
CaseScrut | Subject of a case-decomposition |
CastBody | Body of a Cast |
TickC TickInfo | Body of a Tick |
Instances
type Context = [CoreContext] Source #
A list of CoreContext
describes the complete navigation path from the
top-level to a specific sub-expression.
isLambdaBodyCtx :: CoreContext -> Bool Source #
Is the Context a Lambda/Term-abstraction context?
isTickCtx :: CoreContext -> Bool Source #
Is the Context a Tick context?
collectArgs :: Term -> (Term, [Either Term Type]) Source #
Split a (Type)Application in the applied term and it arguments