Safe Haskell | None |
---|---|
Language | Haskell2010 |
IR.IR
Description
Sslang's intermediate representation and its associated helpers.
Synopsis
- data Program t = Program {}
- data SymInfo t = SymInfo {}
- data TypeDef = TypeDef {
- variants :: [(DConId, TypeVariant)]
- targs :: [TVarId]
- data TypeVariant
- = VariantNamed [(VarId, Type)]
- | VariantUnnamed [Type]
- data Binder t = Binder {
- _binderId :: Maybe VarId
- _binderType :: t
- data Literal
- data PrimOp
- data Primitive
- data Expr t
- data Alt t
- newtype VarId = VarId Identifier
- newtype TConId = TConId Identifier
- newtype DConId = DConId Identifier
- newtype ExceptType = ExceptDefault Literal
- data Type
- data Annotation
- data Annotations
- variantFields :: TypeVariant -> Int
- foldLambda :: [Binder Type] -> Expr Type -> Expr Type
- unfoldLambda :: Expr t -> ([Binder t], Expr t)
- extract :: Carrier c => c a -> a
- inject :: Carrier c => a -> c a -> c a
- injectMore :: (Semigroup a, Carrier c) => a -> c a -> c a
- foldApp :: Expr t -> [(Expr t, t)] -> Expr t
- unfoldApp :: Expr t -> (Expr t, [(Expr t, t)])
- isValue :: Expr t -> Bool
- altBinders :: Alt t -> [Binder t]
- pattern BindVar :: VarId -> t -> Binder t
- pattern BindAnon :: t -> Binder t
- binderToVar :: Binder a -> Maybe VarId
- class Carrier c
- uninitializedSymTable :: Map VarId (SymInfo t)
- type SymTable t = Map VarId (SymInfo t)
Documentation
Top-level compilation unit, parameterized by the type system.
Constructors
Program | |
Instances
Functor Program Source # | |
Foldable Program Source # | |
Defined in IR.IR Methods fold :: Monoid m => Program m -> m # foldMap :: Monoid m => (a -> m) -> Program a -> m # foldMap' :: Monoid m => (a -> m) -> Program a -> m # foldr :: (a -> b -> b) -> b -> Program a -> b # foldr' :: (a -> b -> b) -> b -> Program a -> b # foldl :: (b -> a -> b) -> b -> Program a -> b # foldl' :: (b -> a -> b) -> b -> Program a -> b # foldr1 :: (a -> a -> a) -> Program a -> a # foldl1 :: (a -> a -> a) -> Program a -> a # elem :: Eq a => a -> Program a -> Bool # maximum :: Ord a => Program a -> a # minimum :: Ord a => Program a -> a # | |
Traversable Program Source # | |
Eq t => Eq (Program t) Source # | |
Data t => Data (Program t) Source # | |
Defined in IR.IR Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Program t -> c (Program t) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Program t) # toConstr :: Program t -> Constr # dataTypeOf :: Program t -> DataType # dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (Program t)) # dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (Program t)) # gmapT :: (forall b. Data b => b -> b) -> Program t -> Program t # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Program t -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Program t -> r # gmapQ :: (forall d. Data d => d -> u) -> Program t -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Program t -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Program t -> m (Program t) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Program t -> m (Program t) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Program t -> m (Program t) # | |
Show t => Show (Program t) Source # | |
Pretty (Program Type) | Pretty Typeclass: pretty print the IR Adds * indentation and line breaks * some parens (not minimal parens, but fewer than around every node) Omits * let _ = * type annotations Reverts * curried funcs of one arg back to multiple arg funcs |
Information stored in global symbol table.
Constructors
SymInfo | |
Instances
Functor SymInfo Source # | |
Foldable SymInfo Source # | |
Defined in IR.IR Methods fold :: Monoid m => SymInfo m -> m # foldMap :: Monoid m => (a -> m) -> SymInfo a -> m # foldMap' :: Monoid m => (a -> m) -> SymInfo a -> m # foldr :: (a -> b -> b) -> b -> SymInfo a -> b # foldr' :: (a -> b -> b) -> b -> SymInfo a -> b # foldl :: (b -> a -> b) -> b -> SymInfo a -> b # foldl' :: (b -> a -> b) -> b -> SymInfo a -> b # foldr1 :: (a -> a -> a) -> SymInfo a -> a # foldl1 :: (a -> a -> a) -> SymInfo a -> a # elem :: Eq a => a -> SymInfo a -> Bool # maximum :: Ord a => SymInfo a -> a # minimum :: Ord a => SymInfo a -> a # | |
Traversable SymInfo Source # | |
Eq t => Eq (SymInfo t) Source # | |
Data t => Data (SymInfo t) Source # | |
Defined in IR.IR Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SymInfo t -> c (SymInfo t) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SymInfo t) # toConstr :: SymInfo t -> Constr # dataTypeOf :: SymInfo t -> DataType # dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (SymInfo t)) # dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (SymInfo t)) # gmapT :: (forall b. Data b => b -> b) -> SymInfo t -> SymInfo t # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SymInfo t -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SymInfo t -> r # gmapQ :: (forall d. Data d => d -> u) -> SymInfo t -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SymInfo t -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SymInfo t -> m (SymInfo t) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SymInfo t -> m (SymInfo t) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SymInfo t -> m (SymInfo t) # | |
Show t => Show (SymInfo t) Source # | |
The type definition associated with a type constructor.
A definition for `data MyList a = Cons a (MyList a) | Nil` looks like:
TypeDef { targs = [a]
, [ (Cons, VariantUnnamed [TVar a, TCon (MyList [TVar a])])
, (Nil, VariantUnnamed [])
]
}
(Data constructors for identifiers are omitted for brevity.)
Note that for a flat type system, where all type constructors are nullary, targs
will just be set to [].
Instances
Eq TypeDef Source # | |
Data TypeDef Source # | |
Defined in IR.IR Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TypeDef -> c TypeDef # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TypeDef # toConstr :: TypeDef -> Constr # dataTypeOf :: TypeDef -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TypeDef) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TypeDef) # gmapT :: (forall b. Data b => b -> b) -> TypeDef -> TypeDef # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TypeDef -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TypeDef -> r # gmapQ :: (forall d. Data d => d -> u) -> TypeDef -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TypeDef -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TypeDef -> m TypeDef # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeDef -> m TypeDef # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeDef -> m TypeDef # | |
Show TypeDef Source # | |
data TypeVariant Source #
Arguments to a data constructor, whose fields may or may not be named
Constructors
VariantNamed [(VarId, Type)] | A record with named fields |
VariantUnnamed [Type] | An algebraic type with unnamed fields |
Instances
Eq TypeVariant Source # | |
Defined in IR.IR | |
Data TypeVariant Source # | |
Defined in IR.IR Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TypeVariant -> c TypeVariant # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TypeVariant # toConstr :: TypeVariant -> Constr # dataTypeOf :: TypeVariant -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TypeVariant) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TypeVariant) # gmapT :: (forall b. Data b => b -> b) -> TypeVariant -> TypeVariant # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TypeVariant -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TypeVariant -> r # gmapQ :: (forall d. Data d => d -> u) -> TypeVariant -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TypeVariant -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TypeVariant -> m TypeVariant # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeVariant -> m TypeVariant # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeVariant -> m TypeVariant # | |
Show TypeVariant Source # | |
Defined in IR.IR Methods showsPrec :: Int -> TypeVariant -> ShowS # show :: TypeVariant -> String # showList :: [TypeVariant] -> ShowS # |
A name to be bound; Nothing
represents a wildcard, e.g., let _ = ...
.
Constructors
Binder | |
Fields
|
Instances
Functor Binder Source # | |
Foldable Binder Source # | |
Defined in IR.IR Methods fold :: Monoid m => Binder m -> m # foldMap :: Monoid m => (a -> m) -> Binder a -> m # foldMap' :: Monoid m => (a -> m) -> Binder a -> m # foldr :: (a -> b -> b) -> b -> Binder a -> b # foldr' :: (a -> b -> b) -> b -> Binder a -> b # foldl :: (b -> a -> b) -> b -> Binder a -> b # foldl' :: (b -> a -> b) -> b -> Binder a -> b # foldr1 :: (a -> a -> a) -> Binder a -> a # foldl1 :: (a -> a -> a) -> Binder a -> a # elem :: Eq a => a -> Binder a -> Bool # maximum :: Ord a => Binder a -> a # minimum :: Ord a => Binder a -> a # | |
Traversable Binder Source # | |
Carrier Binder Source # | |
Eq t => Eq (Binder t) Source # | |
Data t => Data (Binder t) Source # | |
Defined in IR.IR Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Binder t -> c (Binder t) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Binder t) # toConstr :: Binder t -> Constr # dataTypeOf :: Binder t -> DataType # dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (Binder t)) # dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (Binder t)) # gmapT :: (forall b. Data b => b -> b) -> Binder t -> Binder t # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Binder t -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Binder t -> r # gmapQ :: (forall d. Data d => d -> u) -> Binder t -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Binder t -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Binder t -> m (Binder t) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Binder t -> m (Binder t) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Binder t -> m (Binder t) # | |
Show t => Show (Binder t) Source # | |
Literal values supported by the language.
Note that these don't carry any connotation of type: 1
just means 1
,
Constructors
LitIntegral Integer | |
LitEvent |
Instances
Eq Literal Source # | |
Data Literal Source # | |
Defined in IR.IR Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Literal -> c Literal # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Literal # toConstr :: Literal -> Constr # dataTypeOf :: Literal -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Literal) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Literal) # gmapT :: (forall b. Data b => b -> b) -> Literal -> Literal # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Literal -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Literal -> r # gmapQ :: (forall d. Data d => d -> u) -> Literal -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Literal -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Literal -> m Literal # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Literal -> m Literal # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Literal -> m Literal # | |
Show Literal Source # | |
Pretty Literal | |
Primitive operations.
These should be the kinds of functions one may expect to be available as operators in C, or as instructions in an assembly language.
For simplicity and consistency, they should be:
- Pure (i.e., side-effectful iff operands are side-effectful, i.e., no
=
) - Strict in all operands (i.e., no
&&
or||
)
We can instead implement short-circuit control flow using match statements.
Constructors
PrimNeg | negation, i.e., -x |
PrimNot | logical not, i.e., !x |
PrimBitNot | bitwise not, i.e., ~x |
PrimAdd | addition, i.e., x + y |
PrimSub | subtraction, i.e., x - y |
PrimMul | multiplication, i.e., x * y |
PrimDiv | division, i.e., x / y |
PrimMod | modulus, i.e., x % y |
PrimBitAnd | bitwise-and, i.e., x & y |
PrimBitOr | bitwise-or, i.e., x | y |
PrimEq | equality, i.e., x == y |
PrimNeq | equality, i.e., x != y |
PrimGt | greater than, i.e., x > y |
PrimGe | greater than or equal to, i.e., x >= y |
PrimLt | less than, i.e., x < y |
PrimLe | less than or equal to, i.e., x <= y |
Instances
Eq PrimOp Source # | |
Data PrimOp Source # | |
Defined in IR.IR Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PrimOp -> c PrimOp # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PrimOp # toConstr :: PrimOp -> Constr # dataTypeOf :: PrimOp -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PrimOp) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PrimOp) # gmapT :: (forall b. Data b => b -> b) -> PrimOp -> PrimOp # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PrimOp -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PrimOp -> r # gmapQ :: (forall d. Data d => d -> u) -> PrimOp -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PrimOp -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PrimOp -> m PrimOp # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PrimOp -> m PrimOp # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PrimOp -> m PrimOp # | |
Show PrimOp Source # | |
Pretty PrimOp | |
Primitive functions for side-effects and imperative control flow.
Constructors
New |
|
Dup |
|
Drop |
|
Deref |
|
Assign |
|
After |
|
Par |
|
Wait |
|
Loop |
|
Break |
|
Now |
|
Last |
|
PrimOp PrimOp | Inlined C expression code. |
CQuote String | Primitive operator. |
CCall CSym | Direct call to arbitrary C function (NOTE: HACKY). |
FfiCall VarId | Call to well-typed extern symbol. |
Instances
Eq Primitive Source # | |
Data Primitive Source # | |
Defined in IR.IR Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Primitive -> c Primitive # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Primitive # toConstr :: Primitive -> Constr # dataTypeOf :: Primitive -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Primitive) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Primitive) # gmapT :: (forall b. Data b => b -> b) -> Primitive -> Primitive # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Primitive -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Primitive -> r # gmapQ :: (forall d. Data d => d -> u) -> Primitive -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Primitive -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Primitive -> m Primitive # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Primitive -> m Primitive # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Primitive -> m Primitive # | |
Show Primitive Source # | |
Expressions, based on the let-polymorphic lambda calculus.
t
represents the type of this expression, e.g., Flat
. At
various stages, this may represent a richer or simpler type
system. The type is embedded in each data constructor so as to
type-annotate the entire expression tree.
Designed for side effects with call-by-value evaluation order. Basic sequencing can be recovered through let-bindings:
let _ = stmt1 in let _ = stmt2 in ...
Effects of stmt1
take place before that of stmt2
.
Constructors
Var VarId t |
|
Data DConId t |
|
Lit Literal t |
|
App (Expr t) (Expr t) t |
|
Let [(Binder t, Expr t)] (Expr t) t |
The bindings list may only be of length greater than 1 for a set of mutually co-recursive functions. |
Lambda (Binder t) (Expr t) t |
|
Match (Expr t) [(Alt t, Expr t)] t |
|
Prim Primitive [Expr t] t |
|
Exception ExceptType t |
|
Instances
Functor Expr Source # | |
Foldable Expr Source # | |
Defined in IR.IR Methods fold :: Monoid m => Expr m -> m # foldMap :: Monoid m => (a -> m) -> Expr a -> m # foldMap' :: Monoid m => (a -> m) -> Expr a -> m # foldr :: (a -> b -> b) -> b -> Expr a -> b # foldr' :: (a -> b -> b) -> b -> Expr a -> b # foldl :: (b -> a -> b) -> b -> Expr a -> b # foldl' :: (b -> a -> b) -> b -> Expr a -> b # foldr1 :: (a -> a -> a) -> Expr a -> a # foldl1 :: (a -> a -> a) -> Expr a -> a # elem :: Eq a => a -> Expr a -> Bool # maximum :: Ord a => Expr a -> a # | |
Traversable Expr Source # | |
Carrier Expr Source # | Extract the type carried by an |
Eq t => Eq (Expr t) Source # | |
Data t => Data (Expr t) Source # | |
Defined in IR.IR Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Expr t -> c (Expr t) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Expr t) # toConstr :: Expr t -> Constr # dataTypeOf :: Expr t -> DataType # dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (Expr t)) # dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (Expr t)) # gmapT :: (forall b. Data b => b -> b) -> Expr t -> Expr t # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Expr t -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Expr t -> r # gmapQ :: (forall d. Data d => d -> u) -> Expr t -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Expr t -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Expr t -> m (Expr t) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Expr t -> m (Expr t) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Expr t -> m (Expr t) # | |
Show t => Show (Expr t) Source # | |
Pretty (Expr Type) | |
HasFreeVars (Expr t) VarId Source # | |
An alternative in a pattern-match.
Constructors
AltData DConId [Alt t] t |
|
AltLit Literal t |
|
AltBinder (Binder t) |
|
Instances
Functor Alt Source # | |
Foldable Alt Source # | |
Defined in IR.IR Methods fold :: Monoid m => Alt m -> m # foldMap :: Monoid m => (a -> m) -> Alt a -> m # foldMap' :: Monoid m => (a -> m) -> Alt a -> m # foldr :: (a -> b -> b) -> b -> Alt a -> b # foldr' :: (a -> b -> b) -> b -> Alt a -> b # foldl :: (b -> a -> b) -> b -> Alt a -> b # foldl' :: (b -> a -> b) -> b -> Alt a -> b # foldr1 :: (a -> a -> a) -> Alt a -> a # foldl1 :: (a -> a -> a) -> Alt a -> a # elem :: Eq a => a -> Alt a -> Bool # maximum :: Ord a => Alt a -> a # | |
Traversable Alt Source # | |
Carrier Alt Source # | |
Eq t => Eq (Alt t) Source # | |
Data t => Data (Alt t) Source # | |
Defined in IR.IR Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Alt t -> c (Alt t) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Alt t) # dataTypeOf :: Alt t -> DataType # dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (Alt t)) # dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (Alt t)) # gmapT :: (forall b. Data b => b -> b) -> Alt t -> Alt t # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Alt t -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Alt t -> r # gmapQ :: (forall d. Data d => d -> u) -> Alt t -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Alt t -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Alt t -> m (Alt t) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Alt t -> m (Alt t) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Alt t -> m (Alt t) # | |
Show t => Show (Alt t) Source # | |
Pretty (Alt Type) | |
Identifier for data variables, e.g., x
.
Constructors
VarId Identifier |
Instances
Eq VarId Source # | |
Data VarId Source # | |
Defined in Common.Identifiers Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VarId -> c VarId # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VarId # dataTypeOf :: VarId -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c VarId) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VarId) # gmapT :: (forall b. Data b => b -> b) -> VarId -> VarId # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VarId -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VarId -> r # gmapQ :: (forall d. Data d => d -> u) -> VarId -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> VarId -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> VarId -> m VarId # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VarId -> m VarId # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VarId -> m VarId # | |
Ord VarId Source # | |
Show VarId Source # | |
IsString VarId Source # | |
Defined in Common.Identifiers Methods fromString :: String -> VarId # | |
Semigroup VarId Source # | |
Monoid VarId Source # | |
Pretty VarId Source # | |
Defined in Common.Identifiers | |
ToIdent VarId Source # | |
Defined in Common.Identifiers | |
Identifiable VarId Source # | |
HasFreeVars (Expr t) VarId Source # | |
Identifier for type constructors, e.g., Option
.
Constructors
TConId Identifier |
Instances
Eq TConId Source # | |
Data TConId Source # | |
Defined in Common.Identifiers Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TConId -> c TConId # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TConId # toConstr :: TConId -> Constr # dataTypeOf :: TConId -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TConId) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TConId) # gmapT :: (forall b. Data b => b -> b) -> TConId -> TConId # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TConId -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TConId -> r # gmapQ :: (forall d. Data d => d -> u) -> TConId -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TConId -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TConId -> m TConId # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TConId -> m TConId # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TConId -> m TConId # | |
Ord TConId Source # | |
Show TConId Source # | |
IsString TConId Source # | |
Defined in Common.Identifiers Methods fromString :: String -> TConId # | |
Semigroup TConId Source # | |
Monoid TConId Source # | |
Pretty TConId Source # | |
Defined in Common.Identifiers | |
ToIdent TConId Source # | |
Defined in Common.Identifiers | |
Identifiable TConId Source # | |
Identifier for data constructors, e.g., None
.
Constructors
DConId Identifier |
Instances
Eq DConId Source # | |
Data DConId Source # | |
Defined in Common.Identifiers Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DConId -> c DConId # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DConId # toConstr :: DConId -> Constr # dataTypeOf :: DConId -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DConId) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DConId) # gmapT :: (forall b. Data b => b -> b) -> DConId -> DConId # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DConId -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DConId -> r # gmapQ :: (forall d. Data d => d -> u) -> DConId -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DConId -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DConId -> m DConId # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DConId -> m DConId # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DConId -> m DConId # | |
Ord DConId Source # | |
Show DConId Source # | |
IsString DConId Source # | |
Defined in Common.Identifiers Methods fromString :: String -> DConId # | |
Semigroup DConId Source # | |
Monoid DConId Source # | |
Pretty DConId Source # | |
Defined in Common.Identifiers | |
ToIdent DConId Source # | |
Defined in Common.Identifiers | |
Identifiable DConId Source # | |
newtype ExceptType Source #
Constructors
ExceptDefault Literal |
Instances
Eq ExceptType Source # | |
Defined in IR.IR | |
Data ExceptType Source # | |
Defined in IR.IR Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ExceptType -> c ExceptType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ExceptType # toConstr :: ExceptType -> Constr # dataTypeOf :: ExceptType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ExceptType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ExceptType) # gmapT :: (forall b. Data b => b -> b) -> ExceptType -> ExceptType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ExceptType -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ExceptType -> r # gmapQ :: (forall d. Data d => d -> u) -> ExceptType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ExceptType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ExceptType -> m ExceptType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ExceptType -> m ExceptType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ExceptType -> m ExceptType # | |
Show ExceptType Source # | |
Defined in IR.IR Methods showsPrec :: Int -> ExceptType -> ShowS # show :: ExceptType -> String # showList :: [ExceptType] -> ShowS # | |
Pretty ExceptType | |
Defined in IR.Pretty |
Encoding of sslang types.
Structurally speaking, these are very simple. Types are either type variables or type constructors applied to some other types.
Builtin types (and type constructors) include Arrow
, Unit
, Ref
, List
,
and various sizes of tuples; for convenience, those are defined elsewhere using
the GHC PatternSynonyms extension.
Instances
Eq Type Source # | |
Data Type Source # | |
Defined in IR.Types.Type Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Type -> c Type # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Type # dataTypeOf :: Type -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Type) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Type) # gmapT :: (forall b. Data b => b -> b) -> Type -> Type # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r # gmapQ :: (forall d. Data d => d -> u) -> Type -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Type -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Type -> m Type # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Type -> m Type # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Type -> m Type # | |
Show Type Source # | |
Pretty Type Source # | |
Defined in IR.Types.Type | |
Dumpy Type Source # | |
HasType Type Source # | |
HasFreeVars Type TVarId Source # | |
Pretty (Alt Type) | |
Pretty (Expr Type) | |
Pretty (Program Type) | Pretty Typeclass: pretty print the IR Adds * indentation and line breaks * some parens (not minimal parens, but fewer than around every node) Omits * let _ = * type annotations Reverts * curried funcs of one arg back to multiple arg funcs |
data Annotation Source #
An annotation records the annotated portion of a pattern.
Instances
Eq Annotation Source # | |
Defined in IR.Types.Type | |
Data Annotation Source # | |
Defined in IR.Types.Type Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Annotation -> c Annotation # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Annotation # toConstr :: Annotation -> Constr # dataTypeOf :: Annotation -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Annotation) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Annotation) # gmapT :: (forall b. Data b => b -> b) -> Annotation -> Annotation # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Annotation -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Annotation -> r # gmapQ :: (forall d. Data d => d -> u) -> Annotation -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Annotation -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Annotation -> m Annotation # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Annotation -> m Annotation # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Annotation -> m Annotation # | |
Show Annotation Source # | |
Defined in IR.Types.Type Methods showsPrec :: Int -> Annotation -> ShowS # show :: Annotation -> String # showList :: [Annotation] -> ShowS # | |
Pretty Annotation Source # | |
Defined in IR.Types.Type | |
Dumpy Annotation Source # | |
Defined in IR.Types.Type Methods dumpy :: Annotation -> Doc ann Source # |
data Annotations Source #
Expressions are annotated with a (potentially empty) list of Annotation
.
Instances
variantFields :: TypeVariant -> Int Source #
The number of fields in a TypeVariant
.
foldLambda :: [Binder Type] -> Expr Type -> Expr Type Source #
Create a lambda chain given a list of argument-type pairs and a body.
unfoldLambda :: Expr t -> ([Binder t], Expr t) Source #
Collect a curried list of function arguments from a nesting of lambdas.
injectMore :: (Semigroup a, Carrier c) => a -> c a -> c a Source #
unfoldApp :: Expr t -> (Expr t, [(Expr t, t)]) Source #
Collect a curried application into the function and argument list.
The type accompanying each argument represents type produced by the
application, and is extracted from the App
node that this function unwraps.
For example, the term f a b
(where a: A
and b: B
) would be represented by
the following AST:
@
(App (App (Var f (A -> B -> C)) (Var a A) (B -> C)) (Var b B) C)
@
which, when unzipped, gives:
@
(Var f (A -> B -> C)) [(Var a A, B -> C), (Var b B, C)]
@