sequent-core-0.2.0.1: Alternative Core language for GHC plugins

Maintainermaurerl@cs.uoregon.edu
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Language.SequentCore.Syntax

Contents

Description

The AST for Sequent Core, with basic operations.

Synopsis

AST Types

data Value b Source

An atomic value. These include literals, lambdas, and variables, as well as types and coercions (see GHC's Expr for the reasoning).

Constructors

Lit Literal

A primitive literal value.

Var Id

A term variable. Must not be a nullary constructor; use Cons for this.

Lam b (Command b)

A function. The body is a computation, that is, a Command.

Cons DataCon [Command b]

A value formed by a saturated constructor application.

Type Type

A type. Used to pass a type as an argument to a type-level lambda.

Coercion Coercion

A coercion. Used to pass evidence for the cast operation to a lambda.

Instances

data Frame b Source

A stack frame. A continuation is simply a list of these. Each represents the outer part of a Haskell expression, with a "hole" where a value can be placed. Computation in the sequent calculus is expressed as the interaction of a value with a continuation.

Constructors

App (Command b)

Apply the value to an argument, which may be a computation.

Case b Type [Alt b]

Perform case analysis on the value.

Cast Coercion

Cast the value using the given proof.

Tick (Tickish Id)

Annotate the enclosed frame. Used by the profiler.

Instances

type Cont b = [Frame b] Source

A continuation, expressed as a list of Frames. In terms of the sequent calculus, here nil stands for a free covariable; since Haskell does not allow for control effects, we only allow for one covariable.

data Command b Source

A general computation. A command brings together a list of bindings, some value, and a continuation saying what to do with that value. The value and continuation comprise a cut in the sequent calculus.

Invariant: If cmdValue is a variable representing a constructor, then cmdCont must not begin with as many App frames as the constructor's arity. In other words, the command must not represent a saturated application of a constructor. Such an application should be represented by a Cons value instead. When in doubt, use mkCommand to enforce this invariant.

Constructors

Command 

Fields

cmdLet :: [Bind b]

Bindings surrounding the computation.

cmdValue :: Value b

The value provided to the continuation.

cmdCont :: Cont b

What to do with the value.

Instances

data Bind b Source

A binding. Similar to the Bind datatype from GHC. Can be either a single non-recursive binding or a mutually recursive block.

Constructors

NonRec b (Command b)

A single non-recursive binding.

Rec [(b, Command b)]

A block of mutually recursive bindings.

Instances

data Alt b Source

A case alternative. Given by the head constructor (or literal), a list of bound variables (empty for a literal), and the body as a Command.

Constructors

Alt AltCon [b] (Command b) 

Instances

data AltCon :: *

A case alternative constructor (i.e. pattern match)

Constructors

DataAlt DataCon 
LitAlt Literal

A literal: case e of { 1 -> ... } Invariant: always an *unlifted* literal See Note [Literal alternatives]

DEFAULT

Trivial alternative: case e of { _ -> ... }

type SeqCoreValue = Value Var Source

Usual instance of Value, with Vars for binders

type SeqCoreFrame = Frame Var Source

Usual instance of Frame, with Vars for binders

type SeqCoreCont = Cont Var Source

Usual instance of Cont, with Vars for binders

type SeqCoreCommand = Command Var Source

Usual instance of Command, with Vars for binders

type SeqCoreBind = Bind Var Source

Usual instance of Bind, with Vars for binders

type SeqCoreAlt = Alt Var Source

Usual instance of Alt, with Vars for binders

Constructors

mkCommand :: [Bind b] -> Value b -> Cont b -> Command b Source

Constructs a command, given let bindings, a value, and a continuation.

This smart constructor enforces the invariant that a saturated constructor invocation is represented as a Cons value rather than using App frames.

valueCommand :: Value b -> Command b Source

Constructs a command that simply returns a value.

varCommand :: Id -> Command b Source

Constructs a command that simply returns a variable.

lambdas :: [b] -> Command b -> Command b Source

Constructs a number of lambdas surrounding a function body.

addLets :: [Bind b] -> Command b -> Command b Source

Adds the given bindings outside those in the given command.

extendCont :: Command b -> Cont b -> Command b Source

Adds the given continuation frames to the end of those in the given command.

Deconstructors

collectLambdas :: Command b -> ([b], Command b) Source

Divide a command into a sequence of lambdas and a body. If c is not a lambda, then collectLambdas c == ([], c).

collectArgs :: Cont b -> ([Command b], Cont b) Source

Divide a continuation into a sequence of arguments and an outer continuation. If k is not an application continuation, then collectArgs k == ([], k).

isLambda :: Command b -> Bool Source

True if the given command is a simple lambda, with no let bindings and no continuation.

isTypeArg :: Command b -> Bool Source

True if the given command simply returns a type as a value. This may only be true of a command appearing as an argument (that is, inside an App frame) or as the body of a let.

isCoArg :: Command b -> Bool Source

True if the given command simply returns a coercion as a value. This may only be true of a command appearing as an argument (that is, inside an App frame) or as the body of a let.

isErasedArg :: Command b -> Bool Source

True if the given command simply returns a value that is either a type or a coercion. This may only be true of a command appearing as an argument (that is, inside an App frame) or as the body of a let.

isRuntimeArg :: Command b -> Bool Source

True if the given command appears at runtime. Types and coercions are erased.

isTypeValue :: Value b -> Bool Source

True if the given value is a type. See Type.

isCoValue :: Value b -> Bool Source

True if the given value is a coercion. See Coercion.

isErasedValue :: Value b -> Bool Source

True if the given value is a type or coercion.

isRuntimeValue :: Value b -> Bool Source

True if the given value appears at runtime.

isTrivial :: HasId b => Command b -> Bool Source

True if the given command represents no actual run-time computation or allocation. For this to hold, it must have no let bindings, and its value and its continuation must both be trivial. Equivalent to exprIsTrivial in GHC.

isTrivialValue :: HasId b => Value b -> Bool Source

True if the given value represents no actual run-time computation. Some literals are not trivial, and a lambda whose argument is not erased or whose body is non-trivial is also non-trivial.

isTrivialCont :: Cont b -> Bool Source

True if the given continuation represents no actual run-time computation. This holds if all of its frames are trivial (perhaps because it is the empty continuation).

isTrivialFrame :: Frame b -> Bool Source

True if the given continuation represents no actual run-time computation. This is true of casts and of applications of erased arguments (types and coercions). Ticks are not considered trivial, since this would cause them to be inlined.

commandAsSaturatedCall :: Command b -> Maybe (Value b, [Command b], Cont b) Source

If a command represents a saturated call to some function, splits it into the function, the arguments, and the remaining continuation after the arguments.

asSaturatedCall :: Value b -> Cont b -> Maybe ([Command b], Cont b) Source

If the given value is a function, and the given continuation would provide enough arguments to saturate it, returns the arguments and the remainder of the continuation.

asValueCommand :: Command b -> Maybe (Value b) Source

If a command does nothing but provide a value, returns that value.

Calculations

valueArity :: Value b -> Int Source

Compute (a conservative estimate of) the arity of a value. If the value is a variable, this may be a lower bound.

commandType :: SeqCoreCommand -> Type Source

Compute the type of a command.

Alpha-equivalence

(=~=) :: AlphaEq a => a -> a -> Bool infix 4 Source

True if the two given terms are the same, up to renaming of bound variables.

class AlphaEq a where Source

The class of types that can be compared up to alpha-equivalence.

Minimal complete definition

aeqIn

Methods

aeq :: a -> a -> Bool infix 4 Source

True if the two given terms are the same, up to renaming of bound variables.

aeqIn :: AlphaEnv -> a -> a -> Bool Source

True if the two given terms are the same, up to renaming of bound variables and the specified equivalences between free variables.

Instances

AlphaEq Coercion 
AlphaEq Type 
AlphaEq a => AlphaEq [a] 
HasId b => AlphaEq (Alt b) 
HasId b => AlphaEq (Bind b) 
HasId b => AlphaEq (Command b) 
HasId b => AlphaEq (Frame b) 
HasId b => AlphaEq (Value b) 

type AlphaEnv = RnEnv2 Source

The type of the environment of an alpha-equivalence comparison. Only needed by user code if two terms need to be compared under some assumed correspondences between free variables. See GHC's VarEnv module for operations.

class HasId a where Source

A class of types that contain an identifier. Useful so that we can compare, say, elements of Command b for any b that wraps an identifier with additional information.

Methods

identifier :: a -> Id Source

The identifier contained by the type a.

Instances