| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Stg.Language
Contents
Description
The STG language syntax tree, modeled after the description in the 1992 paper (link).
A Program is typically created using functionality provided by the
Stg.Parser module, as opposed to manually combining the data types given
in this module.
For plenty of comparisons of STG language source and generated parse trees, have a look at the Stg.Parser.QuasiQuoter module.
- newtype Program = Program Binds
- newtype Binds = Binds (Map Var LambdaForm)
- data LambdaForm = LambdaForm ![Var] !UpdateFlag ![Var] !Expr
- prettyLambda :: ([Var] -> Doc) -> LambdaForm -> Doc
- data UpdateFlag
- data Rec
- data Expr
- data Alts = Alts !NonDefaultAlts !DefaultAlt
- data NonDefaultAlts
- data AlgebraicAlt = AlgebraicAlt !Constr ![Var] !Expr
- data PrimitiveAlt = PrimitiveAlt !Literal !Expr
- data DefaultAlt
- = DefaultNotBound !Expr
- | DefaultBound !Var !Expr
- newtype Literal = Literal Integer
- data PrimOp
- newtype Var = Var Text
- data Atom
- newtype Constr = Constr Text
- class Pretty a where
- pretty :: a -> Doc
- prettyList :: [a] -> Doc
- classify :: LambdaForm -> LambdaType
- data LambdaType
Documentation
An STG program consists of bindings.
Bindings are collections of lambda forms, indexed over variables.
They exist at the top level, or as part of a let(rec) binding.
Constructors
| Binds (Map Var LambdaForm) |
Instances
| Eq Binds Source | |
| Ord Binds Source | |
| Show Binds Source | |
| Generic Binds Source | |
| Pretty Binds Source | |
| Monoid Binds Source | Right-biased union of binds. This makes it easier to overwrite modify
definitions from other programs. For example, if you have one program that
has a certain definition of program' = program <> [stg| map = ... |] to make it use your own version. |
| NFData Binds Source | |
| Lift Binds Source | |
| type Rep Binds Source |
data LambdaForm Source
A lambda form unifies free and bound variables associated with a function body. The lambda body must not be of primitive type, as this would imply the value is both boxed and unboxed.
>>>[stg| \(x) y z -> expr x z |]LambdaForm [Var "x"] NoUpdate [Var "y",Var "z"] (AppF (Var "expr") [AtomVar (Var "x"),AtomVar (Var "z")])
Constructors
| LambdaForm ![Var] !UpdateFlag ![Var] !Expr |
Arguments
| :: ([Var] -> Doc) | Free variable list printer |
| -> LambdaForm | |
| -> Doc |
Prettyprint a LambdaForm, given prettyprinters for the free variable
list.
Introduced so Closure can hijack it to display
the free value list differently.
data UpdateFlag Source
The update flag distinguishes updateable from non-updateable lambda forms.
The former will be overwritten in-place when it is evaluated, allowing the calculation of a thunk to be shared among multiple uses of the same value.
Distinguishes let from letrec.
Constructors
| NonRecursive | |
| Recursive |
An expression in the STG language.
List of possible alternatives in a Case expression.
The list of alts has to be homogeneous. This is not ensured by the type system, and should be handled by the parser instead.
Constructors
| Alts !NonDefaultAlts !DefaultAlt |
data NonDefaultAlts Source
The part of a Case alternative that's not the default.
Constructors
| NoNonDefaultAlts | Used in 'case' statements that consist only of a default alternative. These can be useful to force or unpack values. |
| AlgebraicAlts !(NonEmpty AlgebraicAlt) | Algebraic alternative, like |
| PrimitiveAlts !(NonEmpty PrimitiveAlt) | Primitive alternative, like |
data DefaultAlt Source
If no viable alternative is found in a pattern match, use a DefaultAlt
as fallback.
Constructors
| DefaultNotBound !Expr | |
| DefaultBound !Var !Expr |
Literals are the basis of primitive operations.
Primitive operations.
Variable.
Smallest unit of data. Atoms unify variables and literals, and are what functions take as arguments.
Constructors of algebraic data types.
class Pretty a where
The member prettyList is only used to define the instance Pretty
a => Pretty [a]. In normal circumstances only the pretty function
is used.
Minimal complete definition
Instances
| Pretty Bool | |
| Pretty Char | |
| Pretty Double | |
| Pretty Float | |
| Pretty Int | |
| Pretty Integer | |
| Pretty () | |
| Pretty Doc | |
| Pretty Rendering | |
| Pretty Delta | |
| Pretty Constr | |
| Pretty Atom | |
| Pretty Var | |
| Pretty PrimOp | |
| Pretty Literal | |
| Pretty DefaultAlt | |
| Pretty PrimitiveAlt | |
| Pretty AlgebraicAlt | |
| Pretty Alts | |
| Pretty Expr | |
| Pretty Rec | |
| Pretty LambdaType | |
| Pretty LambdaForm | |
| Pretty Binds | |
| Pretty Program | |
| Pretty HeapObject | |
| Pretty Heap | |
| Pretty Closure | |
| Pretty InfoDetail | |
| Pretty StateError | |
| Pretty NotInScope | |
| Pretty StateTransition | |
| Pretty InfoShort | |
| Pretty Info | |
| Pretty Locals | |
| Pretty Globals | |
| Pretty Code | |
| Pretty Value | |
| Pretty MemAddr | |
| Pretty StackFrame | |
| Pretty StgState | |
| Pretty a => Pretty [a] | |
| Pretty a => Pretty (Maybe a) | |
| Show a => Pretty (Result a) | |
| Pretty a => Pretty (Stack a) | |
| (Pretty a, Pretty b) => Pretty (a, b) | |
| (Pretty k, Pretty v) => Pretty (Mapping k v) | |
| (Pretty a, Pretty b, Pretty c) => Pretty (a, b, c) |
Meta information
classify :: LambdaForm -> LambdaType Source
Classify the type of a lambda form based on its shape.
data LambdaType Source
Possible classification of lambda forms.
Constructors
| LambdaCon | Data constructor ( |
| LambdaFun | Function (lambda with non-empty argument list) |
| LambdaThunk | Thunk (everything else) |
Instances