morte-1.6.9: A bare-bones calculus of constructions

Safe HaskellNone
LanguageHaskell98

Morte.Core

Contents

Description

This module contains the core calculus for the Morte language. This language is a minimalist implementation of the calculus of constructions, which is in turn a specific kind of pure type system. If you are new to pure type systems you may wish to read "Henk: a typed intermediate language".

http://research.microsoft.com/en-us/um/people/simonpj/papers/henk.ps.gz

Morte is a strongly normalizing language, meaning that:

  • Every expression has a unique normal form computed by normalize
  • You test expressions for equality of their normal forms using ==
  • Equational reasoning preserves normal forms

Strong normalization comes at a price: Morte forbids recursion. Instead, you must translate all recursion to F-algebras and translate all corecursion to F-coalgebras. If you are new to F-(co)algebras then you may wish to read Morte.Tutorial or read "Recursive types for free!":

http://homepages.inf.ed.ac.uk/wadler/papers/free-rectypes/free-rectypes.txt

Morte is designed to be a super-optimizing intermediate language with a simple optimization scheme. You optimize a Morte expression by just normalizing the expression. If you normalize a long-lived program encoded as an F-coalgebra you typically get a state machine, and if you normalize a long-lived program encoded as an F-algebra you typically get an unrolled loop.

Strong normalization guarantees that all abstractions encodable in Morte are "free", meaning that they may increase your program's compile times but they will never increase your program's run time because they will normalize to the same code.

Synopsis

Syntax

data Var Source #

Label for a bound variable

The Text field is the variable's name (i.e. "x").

The Int field disambiguates variables with the same name if there are multiple bound variables of the same name in scope. Zero refers to the nearest bound variable and the index increases by one for each bound variable of the same name going outward. The following diagram may help:

                          +-refers to-+
                          |           |
                          v           |
\(x : *) -> \(y : *) -> \(x : *) -> x@0

  +-------------refers to-------------+
  |                                   |
  v                                   |
\(x : *) -> \(y : *) -> \(x : *) -> x@1

This Int behaves like a De Bruijn index in the special case where all variables have the same name.

You can optionally omit the index if it is 0:

                          +refers to+
                          |         |
                          v         |
\(x : *) -> \(y : *) -> \(x : *) -> x

Zero indices are omitted when pretty-printing Vars and non-zero indices appear as a numeric suffix.

Constructors

V Text Int 

Instances

Eq Var Source # 

Methods

(==) :: Var -> Var -> Bool #

(/=) :: Var -> Var -> Bool #

Show Var Source # 

Methods

showsPrec :: Int -> Var -> ShowS #

show :: Var -> String #

showList :: [Var] -> ShowS #

IsString Var Source # 

Methods

fromString :: String -> Var #

Binary Var Source # 

Methods

put :: Var -> Put #

get :: Get Var #

putList :: [Var] -> Put #

NFData Var Source # 

Methods

rnf :: Var -> () #

Buildable Var Source # 

Methods

build :: Var -> Builder #

data Const Source #

Constants for the calculus of constructions

The only axiom is:

⊦ * : □

... and all four rule pairs are valid:

⊦ * ↝ * : *
⊦ □ ↝ * : *
⊦ * ↝ □ : □
⊦ □ ↝ □ : □

Constructors

Star 
Box 

data Path Source #

Path to an external resource

Constructors

File FilePath 
URL Text 

Instances

Eq Path Source # 

Methods

(==) :: Path -> Path -> Bool #

(/=) :: Path -> Path -> Bool #

Ord Path Source # 

Methods

compare :: Path -> Path -> Ordering #

(<) :: Path -> Path -> Bool #

(<=) :: Path -> Path -> Bool #

(>) :: Path -> Path -> Bool #

(>=) :: Path -> Path -> Bool #

max :: Path -> Path -> Path #

min :: Path -> Path -> Path #

Show Path Source # 

Methods

showsPrec :: Int -> Path -> ShowS #

show :: Path -> String #

showList :: [Path] -> ShowS #

Buildable Path Source # 

Methods

build :: Path -> Builder #

newtype X Source #

Like Void, except with an NFData instance in order to avoid orphan instances

Constructors

X 

Fields

Instances

Eq X Source # 

Methods

(==) :: X -> X -> Bool #

(/=) :: X -> X -> Bool #

Show X Source # 

Methods

showsPrec :: Int -> X -> ShowS #

show :: X -> String #

showList :: [X] -> ShowS #

Binary X Source # 

Methods

put :: X -> Put #

get :: Get X #

putList :: [X] -> Put #

NFData X Source # 

Methods

rnf :: X -> () #

Buildable X Source # 

Methods

build :: X -> Builder #

data Expr a Source #

Syntax tree for expressions

Constructors

Const Const
Const c        ~  c
Var Var
Var (V x 0)    ~  x
Var (V x n)    ~  x@n
Lam Text (Expr a) (Expr a)
Lam x     A b  ~  λ(x : A) → b
Pi Text (Expr a) (Expr a)
Pi x      A B  ~  ∀(x : A) → B
Pi unused A B  ~        A  → B
App (Expr a) (Expr a)
App f a        ~  f a
Embed a
Embed path     ~  #path

Instances

Monad Expr Source # 

Methods

(>>=) :: Expr a -> (a -> Expr b) -> Expr b #

(>>) :: Expr a -> Expr b -> Expr b #

return :: a -> Expr a #

fail :: String -> Expr a #

Functor Expr Source # 

Methods

fmap :: (a -> b) -> Expr a -> Expr b #

(<$) :: a -> Expr b -> Expr a #

Applicative Expr Source # 

Methods

pure :: a -> Expr a #

(<*>) :: Expr (a -> b) -> Expr a -> Expr b #

(*>) :: Expr a -> Expr b -> Expr b #

(<*) :: Expr a -> Expr b -> Expr a #

Foldable Expr Source # 

Methods

fold :: Monoid m => Expr m -> 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 #

toList :: Expr a -> [a] #

null :: Expr a -> Bool #

length :: Expr a -> Int #

elem :: Eq a => a -> Expr a -> Bool #

maximum :: Ord a => Expr a -> a #

minimum :: Ord a => Expr a -> a #

sum :: Num a => Expr a -> a #

product :: Num a => Expr a -> a #

Traversable Expr Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Expr a -> f (Expr b) #

sequenceA :: Applicative f => Expr (f a) -> f (Expr a) #

mapM :: Monad m => (a -> m b) -> Expr a -> m (Expr b) #

sequence :: Monad m => Expr (m a) -> m (Expr a) #

Eq a => Eq (Expr a) Source # 

Methods

(==) :: Expr a -> Expr a -> Bool #

(/=) :: Expr a -> Expr a -> Bool #

Show a => Show (Expr a) Source # 

Methods

showsPrec :: Int -> Expr a -> ShowS #

show :: Expr a -> String #

showList :: [Expr a] -> ShowS #

IsString (Expr a) Source # 

Methods

fromString :: String -> Expr a #

Binary a => Binary (Expr a) Source # 

Methods

put :: Expr a -> Put #

get :: Get (Expr a) #

putList :: [Expr a] -> Put #

NFData a => NFData (Expr a) Source # 

Methods

rnf :: Expr a -> () #

Buildable a => Buildable (Expr a) Source #

Generates a syntactically valid Morte program

Methods

build :: Expr a -> Builder #

data Context a Source #

Bound variable names and their types

Variable names may appear more than once in the Context. The Var x@n refers to the nth occurrence of x in the Context (using 0-based numbering).

Instances

Functor Context Source # 

Methods

fmap :: (a -> b) -> Context a -> Context b #

(<$) :: a -> Context b -> Context a #

NFData a => NFData (Context a) Source # 

Methods

rnf :: Context a -> () #

Core functions

typeWith :: Context (Expr X) -> Expr X -> Either TypeError (Expr X) Source #

Type-check an expression and return the expression's type if type-checking suceeds or an error if type-checking fails

typeWith does not necessarily normalize the type since full normalization is not necessary for just type-checking. If you actually care about the returned type then you may want to normalize it afterwards.

typeOf :: Expr X -> Either TypeError (Expr X) Source #

typeOf is the same as typeWith with an empty context, meaning that the expression must be closed (i.e. no free variables), otherwise type-checking will fail.

normalize :: Expr a -> Expr a Source #

Reduce an expression to its normal form, performing both beta reduction and eta reduction

normalize does not type-check the expression. You may want to type-check expressions before normalizing them since normalization can convert an ill-typed expression into a well-typed expression.

Utilities

shift :: Int -> Text -> Expr a -> Expr a Source #

shift n x adds n to the index of all free variables named x within an Expr

subst :: Text -> Int -> Expr a -> Expr a -> Expr a Source #

Substitute all occurrences of a variable with an expression

subst x n C B  ~  B[x@n := C]

pretty :: Buildable a => a -> Text Source #

Pretty-print a value

buildExpr :: Buildable a => Expr a -> Builder Source #

Pretty-print an expression as a Builder, using Unicode symbols

buildExprASCII :: Buildable a => Expr a -> Builder Source #

Pretty-print an expression as a Builder, using ASCII symbols

Errors