| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Calculi.Lambda
- data LambdaTerm c v t
- = Variable v
- | Constant c
- | Apply (LambdaTerm c v t) (LambdaTerm c v t)
- | Lambda (v, t) (LambdaTerm c v t)
- type UntypedLambdaExpr c v = LambdaTerm c v ()
- freeVars :: Ord v => LambdaTerm c v t -> Set v
- data NotKnownErr c v t
- = UnknownType t
- | UnknownVariable v
- | UnknownConstant c
- type LetDeclr c v t = ((v, t), LambdaTerm c v t)
- unlet :: forall c v t. (Ord c, Ord v, Ord t) => [LetDeclr c v t] -> LambdaTerm c v t -> Either [[LetDeclr c v t]] (LambdaTerm c v t)
- letsDependency :: (DynGraph gr, Ord c, Ord v, Ord t) => [LetDeclr c v t] -> gr (LetDeclr c v t) ()
- letsDependency' :: forall gr c v t. (DynGraph gr, Ord c, Ord v, Ord t) => [LetDeclr c v t] -> (NodeMap (LetDeclr c v t), gr (LetDeclr c v t) ())
Typed Lambda Calculus AST.
data LambdaTerm c v t Source #
A simple, typed lambda calculus AST with constants.
Constructors
| Variable v | A reference to a variable. |
| Constant c | A constant value, such as literals or constructors. |
| Apply (LambdaTerm c v t) (LambdaTerm c v t) | An application of one expression to another. |
| Lambda (v, t) (LambdaTerm c v t) | A lambda expression, with a variable definition and a function body. |
Instances
| Bifunctor (LambdaTerm c0) Source # | |
| Bitraversable (LambdaTerm c0) Source # | |
| Bifoldable (LambdaTerm c0) Source # | |
| (Ord m, Ord c, Ord v) => Typecheckable (LambdaTerm c v) (SimplyTyped m) Source # | |
| (Ord c, Ord v, Ord m, Ord p) => Typecheckable (LambdaTerm c v) (SystemF m p) Source # | |
| (Eq c, Eq v, Eq t) => Eq (LambdaTerm c v t) Source # | |
| (Data c, Data v, Data t) => Data (LambdaTerm c v t) Source # | |
| (Ord c, Ord v, Ord t) => Ord (LambdaTerm c v t) Source # | |
| (Show c, Show v, Show t) => Show (LambdaTerm c v t) Source # | |
| (Arbitrary c, Data c, Arbitrary v, Data v, Arbitrary t, Data t) => Arbitrary (LambdaTerm c v t) Source # | |
| type TypingContext (LambdaTerm c v) (SimplyTyped m) Source # | |
| type TypeError (LambdaTerm c v) (SimplyTyped m) Source # | |
| type TypingContext (LambdaTerm c v) (SystemF m p) Source # | |
| type TypeError (LambdaTerm c v) (SystemF m p) Source # | |
type UntypedLambdaExpr c v = LambdaTerm c v () Source #
Analysis Helpers
freeVars :: Ord v => LambdaTerm c v t -> Set v Source #
Find all the unbound variables in an expression.
Name-related errors
data NotKnownErr c v t Source #
Name-related errors, for when there's a variable, type or constant that doesn't appear in the environment that was given to the typechecker.
Constructors
| UnknownType t | A type appears that is not in scope |
| UnknownVariable v | A variable appears that is not in scope |
| UnknownConstant c | A constant appears that is not in scope |
Let declaration helpers
type LetDeclr c v t = ((v, t), LambdaTerm c v t) Source #
Arguments
| :: (Ord c, Ord v, Ord t) | |
| => [LetDeclr c v t] | The list of declarations in a let expression |
| -> LambdaTerm c v t | The body of the let declaration |
| -> Either [[LetDeclr c v t]] (LambdaTerm c v t) | Either a list of cyclic lets or the final expression |
Unlet non-cyclic let expressions.