ddc-core-0.4.3.1: Disciplined Disciple Compiler core language and type checker.

Safe HaskellSafe
LanguageHaskell98

DDC.Type.Exp.Simple

Contents

Synopsis

Abstract Syntax

Types

data Type n Source #

A value type, kind, or sort.

We use the same data type to represent all three universes, as they have a similar algebraic structure.

Constructors

TCon !(TyCon n)

Constructor.

TVar !(Bound n)

Variable.

TAbs !(Bind n) !(Type n)

Abstraction.

TApp !(Type n) !(Type n)

Application.

TForall !(Bind n) !(Type n)

Universal Quantification.

TSum !(TypeSum n)

Least upper bound.

Instances

SpreadT Type Source # 

Methods

spreadT :: Ord n => TypeEnv n -> Type n -> Type n Source #

Rename Type Source # 

Methods

renameWith :: Ord n => Sub n -> Type n -> Type n Source #

FreeVarConT Type Source # 

Methods

freeVarConT :: Ord n => KindEnv n -> Type n -> (Set (Bound n), Set (Bound n)) Source #

SupportX Type Source # 

Methods

support :: Ord n => KindEnv n -> TypeEnv n -> Type n -> Support n Source #

SubstituteT Type Source # 

Methods

substituteWithT :: Ord n => Bound n -> Type n -> Set n -> BindStack n -> Type n -> Type n Source #

SubstituteTX Type Source # 

Methods

substituteWithTX :: Ord n => Type n -> Sub n -> Type n -> Type n Source #

Ord n => MapBoundT Type n Source # 

Methods

mapBoundAtDepthT :: (Int -> Bound n -> Bound n) -> Int -> Type n -> Type n Source #

Show n => Show (Type n) Source # 

Methods

showsPrec :: Int -> Type n -> ShowS #

show :: Type n -> String #

showList :: [Type n] -> ShowS #

data TypeSum n Source #

A least upper bound of several types.

We keep type sums in this normalised format instead of joining them together with a binary operator (like (+)). This makes sums easier to work with, as a given sum type often only has a single physical representation.

Constructors

TypeSumBot 

Fields

TypeSumSet 

Fields

Instances

SpreadT TypeSum Source # 

Methods

spreadT :: Ord n => TypeEnv n -> TypeSum n -> TypeSum n Source #

Rename TypeSum Source # 

Methods

renameWith :: Ord n => Sub n -> TypeSum n -> TypeSum n Source #

SubstituteT TypeSum Source # 

Methods

substituteWithT :: Ord n => Bound n -> Type n -> Set n -> BindStack n -> TypeSum n -> TypeSum n Source #

Ord n => MapBoundT TypeSum n Source # 

Methods

mapBoundAtDepthT :: (Int -> Bound n -> Bound n) -> Int -> TypeSum n -> TypeSum n Source #

Show n => Show (TypeSum n) Source # 

Methods

showsPrec :: Int -> TypeSum n -> ShowS #

show :: TypeSum n -> String #

showList :: [TypeSum n] -> ShowS #

data TypeSumVarCon n Source #

Wraps a variable or constructor that can be added the typeSumElems array.

Constructors

TypeSumVar !(Bound n) 
TypeSumCon !(Bound n) !(Kind n) 

Binding

data Binder n Source #

Constructors

RNone 
RAnon 
RName !n 

Instances

Show n => Show (Binder n) Source # 

Methods

showsPrec :: Int -> Binder n -> ShowS #

show :: Binder n -> String #

showList :: [Binder n] -> ShowS #

data Bind n Source #

A variable binder with its type.

Constructors

BNone !(Type n)

A variable with no uses in the body doesn't need a name.

BAnon !(Type n)

Nameless variable on the deBruijn stack.

BName n !(Type n)

Named variable in the environment.

Instances

SpreadT Bind Source # 

Methods

spreadT :: Ord n => TypeEnv n -> Bind n -> Bind n Source #

Rename Bind Source # 

Methods

renameWith :: Ord n => Sub n -> Bind n -> Bind n Source #

SpreadX Bind Source # 

Methods

spreadX :: Ord n => Env n -> Env n -> Bind n -> Bind n Source #

SupportX Bind Source # 

Methods

support :: Ord n => KindEnv n -> TypeEnv n -> Bind n -> Support n Source #

SubstituteT Bind Source # 

Methods

substituteWithT :: Ord n => Bound n -> Type n -> Set n -> BindStack n -> Bind n -> Bind n Source #

SubstituteTX Bind Source # 

Methods

substituteWithTX :: Ord n => Type n -> Sub n -> Bind n -> Bind n Source #

Ord n => MapBoundT Bind n Source # 

Methods

mapBoundAtDepthT :: (Int -> Bound n -> Bound n) -> Int -> Bind n -> Bind n Source #

Show n => Show (Bind n) Source # 

Methods

showsPrec :: Int -> Bind n -> ShowS #

show :: Bind n -> String #

showList :: [Bind n] -> ShowS #

data Bound n Source #

A bound occurrence of a variable, with its type.

If variable hasn't been annotated with its real type then this can be tBot (an empty sum).

Constructors

UIx !Int

Nameless variable that should be on the deBruijn stack.

UName !n

Named variable that should be in the environment.

UPrim !n !(Type n)

Named primitive that has its type attached to it. The types of primitives must be closed.

Instances

SpreadT Bound Source # 

Methods

spreadT :: Ord n => TypeEnv n -> Bound n -> Bound n Source #

SpreadX Bound Source # 

Methods

spreadX :: Ord n => Env n -> Env n -> Bound n -> Bound n Source #

MapBoundT Bound n Source # 

Methods

mapBoundAtDepthT :: (Int -> Bound n -> Bound n) -> Int -> Bound n -> Bound n Source #

MapBoundX Bound n Source # 

Methods

mapBoundAtDepthX :: (Int -> Bound n -> Bound n) -> Int -> Bound n -> Bound n Source #

Show n => Show (Bound n) Source # 

Methods

showsPrec :: Int -> Bound n -> ShowS #

show :: Bound n -> String #

showList :: [Bound n] -> ShowS #

Constructors

data TyCon n Source #

Kind, type and witness constructors.

These are grouped to make it easy to determine the universe that they belong to.

Constructors

TyConSort !SoCon

(level 3) Builtin Sort constructors.

TyConKind !KiCon

(level 2) Builtin Kind constructors.

TyConWitness !TwCon

(level 1) Builtin Spec constructors for the types of witnesses.

TyConSpec !TcCon

(level 1) Builtin Spec constructors for types of other kinds.

TyConBound !(Bound n) !(Kind n)

User defined type constructor.

TyConExists !Int !(Kind n)

An existentially quantified name, with its kind. Used during type checking, but not accepted in source programs.

Instances

SpreadT TyCon Source # 

Methods

spreadT :: Ord n => TypeEnv n -> TyCon n -> TyCon n Source #

Show n => Show (TyCon n) Source # 

Methods

showsPrec :: Int -> TyCon n -> ShowS #

show :: TyCon n -> String #

showList :: [TyCon n] -> ShowS #

data SoCon Source #

Sort constructor.

Constructors

SoConProp

Sort of witness kinds.

SoConComp

Sort of computation kinds.

Instances

Eq SoCon Source # 

Methods

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

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

Ord SoCon Source # 

Methods

compare :: SoCon -> SoCon -> Ordering #

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

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

(>) :: SoCon -> SoCon -> Bool #

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

max :: SoCon -> SoCon -> SoCon #

min :: SoCon -> SoCon -> SoCon #

Show SoCon Source # 

Methods

showsPrec :: Int -> SoCon -> ShowS #

show :: SoCon -> String #

showList :: [SoCon] -> ShowS #

data KiCon Source #

Kind constructor.

Constructors

KiConFun

Function kind constructor. This is only well formed when it is fully applied.

KiConWitness

Kind of witnesses.

KiConData

Kind of data values.

KiConRegion

Kind of regions.

KiConEffect

Kind of effects.

KiConClosure

Kind of closures.

Instances

Eq KiCon Source # 

Methods

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

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

Ord KiCon Source # 

Methods

compare :: KiCon -> KiCon -> Ordering #

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

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

(>) :: KiCon -> KiCon -> Bool #

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

max :: KiCon -> KiCon -> KiCon #

min :: KiCon -> KiCon -> KiCon #

Show KiCon Source # 

Methods

showsPrec :: Int -> KiCon -> ShowS #

show :: KiCon -> String #

showList :: [KiCon] -> ShowS #

data TwCon Source #

Witness type constructors.

Constructors

TwConImpl 
TwConPure

Purity of some effect.

TwConConst

Constancy of some region.

TwConDeepConst

Constancy of material regions in some type

TwConMutable

Mutability of some region.

TwConDeepMutable

Mutability of material regions in some type.

TwConDistinct Int

Distinctness of some n regions

TwConDisjoint

Non-interfering effects are disjoint. Used for rewrite rules.

Instances

Eq TwCon Source # 

Methods

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

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

Ord TwCon Source # 

Methods

compare :: TwCon -> TwCon -> Ordering #

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

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

(>) :: TwCon -> TwCon -> Bool #

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

max :: TwCon -> TwCon -> TwCon #

min :: TwCon -> TwCon -> TwCon #

Show TwCon Source # 

Methods

showsPrec :: Int -> TwCon -> ShowS #

show :: TwCon -> String #

showList :: [TwCon] -> ShowS #

data TcCon Source #

Other constructors at the spec level.

Constructors

TcConUnit

The unit data type constructor is baked in.

TcConFun

Pure function.

TcConSusp

A suspended computation.

TcConRead

Read of some region.

TcConHeadRead

Read the head region in a data type.

TcConDeepRead

Read of all material regions in a data type.

TcConWrite

Write of some region.

TcConDeepWrite

Write to all material regions in some data type.

TcConAlloc

Allocation into some region.

TcConDeepAlloc

Allocation into all material regions in some data type.

Instances

Eq TcCon Source # 

Methods

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

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

Ord TcCon Source # 

Methods

compare :: TcCon -> TcCon -> Ordering #

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

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

(>) :: TcCon -> TcCon -> Bool #

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

max :: TcCon -> TcCon -> TcCon #

min :: TcCon -> TcCon -> TcCon #

Show TcCon Source # 

Methods

showsPrec :: Int -> TcCon -> ShowS #

show :: TcCon -> String #

showList :: [TcCon] -> ShowS #

Aliases

type Sort n = Type n Source #

Sorts are types at level 3.

type Kind n = Type n Source #

Kinds are types at level 2

type Region n = Type n Source #

Alias for region types.

type Effect n = Type n Source #

Alias for effect types.

type Closure n = Type n Source #

Alias for closure types.

Predicates

Binders

Atoms

isTVar :: Type n -> Bool Source #

Check whether a type is a TVar

isBot :: Type n -> Bool Source #

Test if some type is an empty TSum

isAtomT :: Type n -> Bool Source #

Check whether a type is a TVar, TCon or is Bottom.

isTExists :: Type n -> Bool Source #

Check whether this type is an existential variable.

Kinds

isDataKind :: Kind n -> Bool Source #

Check if some kind is the data kind.

isRegionKind :: Region n -> Bool Source #

Check if some kind is the region kind.

isEffectKind :: Kind n -> Bool Source #

Check if some kind is the effect kind.

isClosureKind :: Kind n -> Bool Source #

Check if some kind is the closure kind.

isWitnessKind :: Kind n -> Bool Source #

Check if some kind is the witness kind.

Data Types

isAlgDataType :: Eq n => Type n -> Bool Source #

Check whether this type is that of algebraic data.

It needs to have an explicit data constructor out the front, and not a type variable. The constructor must not be the function constructor, and must return a value of kind *.

isWitnessType :: Eq n => Type n -> Bool Source #

Check whether type is a witness constructor

isConstWitType :: Eq n => Type n -> Bool Source #

Check whether this is the type of a Const witness.

isMutableWitType :: Eq n => Type n -> Bool Source #

Check whether this is the type of a Mutable witness.

isDistinctWitType :: Eq n => Type n -> Bool Source #

Check whether this is the type of a Distinct witness.

Effect Types

isReadEffect :: Effect n -> Bool Source #

Check whether this is an atomic read effect.

isWriteEffect :: Effect n -> Bool Source #

Check whether this is an atomic write effect.

isAllocEffect :: Effect n -> Bool Source #

Check whether this is an atomic alloc effect.

isSomeReadEffect :: Effect n -> Bool Source #

Check whether an effect is some sort of read effect. Matches Read HeadRead and DeepRead.

isSomeWriteEffect :: Effect n -> Bool Source #

Check whether an effect is some sort of allocation effect. Matches Alloc and DeepAlloc

isSomeAllocEffect :: Effect n -> Bool Source #

Check whether an effect is some sort of allocation effect. Matches Alloc and DeepAlloc

Relations

Equivalence

equivT :: Ord n => EnvT n -> Type n -> Type n -> Bool Source #

Check equivalence of types.

Checks equivalence up to alpha-renaming, as well as crushing of effects and trimming of closures.

  • Return False if we find any free variables.
  • We assume the types are well-kinded, so that the type annotations on bound variables match the binders. If this is not the case then you get an indeterminate result.

equivWithBindsT Source #

Arguments

:: Ord n 
=> EnvT n

Environment of types.

-> [Bind n]

Stack of binders for first type.

-> [Bind n]

Stack of binders for second type.

-> Type n

First type to compare.

-> Type n

Second type to compare.

-> Bool 

Like equivT but take the initial stacks of type binders.

equivTyCon :: Eq n => TyCon n -> TyCon n -> Bool Source #

Check if two TyCons are equivalent. We need to handle TyConBound specially incase it's kind isn't attached,

Subsumption

subsumesT :: Ord n => EnvT n -> Kind n -> Type n -> Type n -> Bool Source #

Check whether the first type subsumes the second.

Both arguments are converted to sums, and we check that every element of the second sum is equivalent to an element in the first.

This only works for well formed types of effect and closure kind. Other types will yield False.

Transforms

Crushing

crushSomeT :: Ord n => EnvT n -> Type n -> Type n Source #

Crush compound effects and closure terms. We check for a crushable term before calling crushT because that function will recursively crush the components. As equivT is already recursive, we don't want a doubly-recursive function that tries to re-crush the same non-crushable type over and over.

crushEffect :: Ord n => EnvT n -> Effect n -> Effect n Source #

Crush compound effect terms into their components.

For example, crushing DeepRead (List r1 (Int r2)) yields (Read r1 + Read r2).

Compounds

Binds

takeNameOfBind :: Bind n -> Maybe n Source #

Take the variable name of a bind. If this is an anonymous binder then there won't be a name.

typeOfBind :: Bind n -> Type n Source #

Take the type of a bind.

replaceTypeOfBind :: Type n -> Bind n -> Bind n Source #

Replace the type of a bind with a new one.

Binders

binderOfBind :: Bind n -> Binder n Source #

Take the binder of a bind.

makeBindFromBinder :: Binder n -> Type n -> Bind n Source #

Make a bind from a binder and its type.

partitionBindsByType :: Eq n => [Bind n] -> [([Binder n], Type n)] Source #

Make lists of binds that have the same type.

Bounds

takeNameOfBound :: Bound n -> Maybe n Source #

Take the name of bound variable. If this is a deBruijn index then there won't be a name.

takeTypeOfBound :: Bound n -> Maybe (Type n) Source #

Get the attached type of a Bound, if any.

boundMatchesBind :: Eq n => Bound n -> Bind n -> Bool Source #

Check whether a bound maches a bind. UName and BName match if they have the same name. UIx 0 _ and BAnon _ always match. Yields False for other combinations of bounds and binds.

namedBoundMatchesBind :: Eq n => Bound n -> Bind n -> Bool Source #

Check whether a named bound matches a named bind. Yields False if they are not named or have different names.

takeSubstBoundOfBind :: Bind n -> Maybe (Bound n) Source #

Convert a Bind to a Bound, ready for substitution.

Returns UName for BName, UIx 0 for BAnon and Nothing for BNone, because there's nothing to substitute.

takeSubstBoundsOfBinds :: [Bind n] -> [Bound n] Source #

Convert some Binds to Bounds

replaceTypeOfBound :: Type n -> Bound n -> Bound n Source #

If this Bound is a UPrim then replace it's embedded type with a new one, otherwise return it unharmed.

Sorts

sComp :: Type n Source #

Sort of kinds of computational types.

sProp :: Type n Source #

Sort of kinds of propositional types.

Kinds

kData :: Type n Source #

Kind of data types.

kRegion :: Type n Source #

Kind of region types.

kEffect :: Type n Source #

Kind of effect types.

kClosure :: Type n Source #

Kind of closure types.

kWitness :: Type n Source #

Kind of witness types.

kFun :: Kind n -> Kind n -> Kind n infixr 9 Source #

Construct a kind function.

kFuns :: [Kind n] -> Kind n -> Kind n Source #

Construct some kind functions.

takeKFun :: Kind n -> Maybe (Kind n, Kind n) Source #

Destruct a kind function

takeKFuns :: Kind n -> ([Kind n], Kind n) Source #

Destruct a chain of kind functions into the arguments

takeKFuns' :: Kind n -> [Kind n] Source #

Like takeKFuns, but return argument and return kinds in the same list.

takeResultKind :: Kind n -> Kind n Source #

Take the result kind of a kind function, or return the same kind unharmed if it's not a kind function.

Quantifiers

tForall :: Kind n -> (Type n -> Type n) -> Type n Source #

Build an anonymous type abstraction, with a single parameter.

tForall' :: Int -> Kind n -> (Type n -> Type n) -> Type n Source #

Build an anonymous type abstraction, with a single parameter. Starting the next index from the given value.

tForalls :: [Kind n] -> ([Type n] -> Type n) -> Type n Source #

Build an anonymous type abstraction, with several parameters. Starting the next index from the given value.

tForalls' :: Int -> [Kind n] -> ([Type n] -> Type n) -> Type n Source #

Build an anonymous type abstraction, with several parameters. Starting the next index from the given value.

takeTForalls :: Type n -> Maybe ([Bind n], Type n) Source #

Split nested foralls from the front of a type, or Nothing if there was no outer forall.

eraseTForalls :: Ord n => Type n -> Type n Source #

Erase all TForall quantifiers from a type.

Sums

tBot :: Kind n -> Type n Source #

Construct an empty type sum.

tSum :: Ord n => Kind n -> [Type n] -> Type n Source #

Applications

tApp :: Type n -> Type n -> Type n Source #

Construct a type application.

($:) :: Type n -> Type n -> Type n Source #

Construct a type application.

tApps :: Type n -> [Type n] -> Type n Source #

Construct a sequence of type applications.

takeTApps :: Type n -> [Type n] Source #

Flatten a sequence ot type applications into the function part and arguments, if any.

takeTyConApps :: Type n -> Maybe (TyCon n, [Type n]) Source #

Flatten a sequence of type applications, returning the type constructor and arguments, if there is one.

takePrimTyConApps :: Type n -> Maybe (n, [Type n]) Source #

Flatten a sequence of type applications, returning the type constructor and arguments, if there is one. Only accept primitive type constructors.

takeDataTyConApps :: Type n -> Maybe (TyCon n, [Type n]) Source #

Flatten a sequence of type applications, returning the type constructor and arguments, if there is one. Only accept data type constructors.

takePrimeRegion :: Type n -> Maybe (Type n) Source #

Take the prime region variable of a data type. This corresponds to the region the outermost constructor is allocated into.

Functions

tFun :: Type n -> Type n -> Type n infixr 9 Source #

Construct a pure function type.

tFunOfList :: [Type n] -> Maybe (Type n) Source #

Construct a function type from a list containing the parameter and return types. Yields Nothing if the list is empty.

tFunOfParamResult :: [Type n] -> Type n -> Type n Source #

Construct a function type from a list of parameter types and the return type.

takeTFun :: Type n -> Maybe (Type n, Type n) Source #

Yield the argument and result type of a function type.

takeTFunArgResult :: Type n -> ([Type n], Type n) Source #

Destruct the type of a function, returning just the argument and result types.

takeTFunWitArgResult :: Type n -> ([Type n], [Type n], Type n) Source #

Destruct the type of a function, returning the witness argument, value argument and result types. The function type must have the witness implications before the value arguments, eg T1 => T2 -> T3 -> T4 -> T5.

takeTFunAllArgResult :: Type n -> ([Type n], Type n) Source #

Destruct the type of a possibly polymorphic function returning all kinds of quantifiers, witness arguments, and value arguments in the order they appear, along with the type of the result.

arityOfType :: Type n -> Int Source #

Determine the arity of an expression by looking at its type. Count all the function arrows, and foralls.

This assumes the type is in prenex form, meaning that all the quantifiers are at the front.

dataArityOfType :: Type n -> Int Source #

The data arity of a type is the number of data values it takes. Unlike arityOfType we ignore type and witness parameters.

Suspensions

tSusp :: Effect n -> Type n -> Type n Source #

Construct a suspension type.

takeTSusp :: Type n -> Maybe (Effect n, Type n) Source #

Take the effect and result type of a suspension type.

takeTSusps :: Type n -> ([Effect n], Type n) Source #

Split off enclosing suspension types.

Implications

tImpl :: Type n -> Type n -> Type n infixr 9 Source #

Construct a witness implication type.

Units

tUnit :: Type n Source #

The unit type.

Variables

tIx :: Kind n -> Int -> Type n Source #

Construct a deBruijn index.

takeTExists :: Type n -> Maybe Int Source #

Take an existential variable from a type.

Effect types

tRead :: Type n -> Type n Source #

Read effect type constructor.

tDeepRead :: Type n -> Type n Source #

Deep Read effect type constructor.

tHeadRead :: Type n -> Type n Source #

Head Read effect type constructor.

tWrite :: Type n -> Type n Source #

Write effect type constructor.

tDeepWrite :: Type n -> Type n Source #

Deep Write effect type constructor.

tAlloc :: Type n -> Type n Source #

Alloc effect type constructor.

tDeepAlloc :: Type n -> Type n Source #

Deep Alloc effect type constructor.

Witness types

tPure :: Type n -> Type n Source #

Pure witness type constructor.

tConst :: Type n -> Type n Source #

Const witness type constructor.

tDeepConst :: Type n -> Type n Source #

Deep Const witness type constructor.

tMutable :: Type n -> Type n Source #

Mutable witness type constructor.

tDeepMutable :: Type n -> Type n Source #

Deep Mutable witness type constructor.

tDistinct :: Int -> [Type n] -> Type n Source #

Distinct witness type constructor.

tConData0 :: n -> Kind n -> Type n Source #

Build a nullary type constructor of the given kind.

tConData1 :: n -> Kind n -> Type n -> Type n Source #

Build a type constructor application of one argumnet.