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

Safe HaskellNone
LanguageHaskell98

DDC.Core.Fragment

Contents

Description

The ambient Disciple Core language is specialised to concrete languages by adding primitive operations and optionally restricting the set of available language features. This specialisation results in user-facing language fragments such as Disciple Core Tetra and Disciple Core Salt.

Synopsis

Langauge fragments

data Fragment n err Source #

Carries all the information we need to work on a particular fragment of the Disciple Core language.

Constructors

Fragment 

Fields

Instances

Show (Fragment n err) Source # 

Methods

showsPrec :: Int -> Fragment n err -> ShowS #

show :: Fragment n err -> String #

showList :: [Fragment n err] -> ShowS #

mapProfileOfFragment :: (Profile n -> Profile n) -> Fragment n err -> Fragment n err Source #

Apply a function to the profile in a fragment.

data Profile n Source #

The fragment profile describes the language features and primitive operators available in the language.

Constructors

Profile 

Fields

mapFeaturesOfProfile :: (Features -> Features) -> Profile n -> Profile n Source #

Apply a function to the Features of a Profile.

zeroProfile :: Profile n Source #

A language profile with no features or primitive operators.

This provides a simple first-order language.

Fragment features

data Feature Source #

Language feature supported by a fragment.

Constructors

TrackedEffects

Track effect type information.

TrackedClosures

Track closure type information.

FunctionalEffects

Attach latent effects to function types.

FunctionalClosures

Attach latent closures to function types.

EffectCapabilities

Treat effects as capabilities.

ImplicitRun

Insert implicit run casts for effectful applications.

ImplicitBox

Insert implicit box casts for bodies of abstractions.

PartialPrims

Partially applied primitive operators.

PartialApplication

Partially applied functions

GeneralApplication

Function application where the thing being applied is not a variable. Most backend languages (like LLVM) don't support this.

NestedFunctions

Nested function bindings. The output of the lambda-lifter should not contain these.

GeneralLetRec

Recursive let-expressions where the right hand sides are not lambda abstractions.

DebruijnBinders

Debruijn binders. Most backends will want to use real names, instead of indexed binders.

UnboundLevel0Vars

Allow data and witness vars without binding occurrences if they are annotated directly with their types. This lets us work with open terms.

UnboxedInstantiation

Allow non-primitive functions to be instantiated at unboxed types. Our existing backends can't handle this, because boxed and unboxed objects have different representations.

NameShadowing

Allow name shadowing.

UnusedBindings

Allow unused named data and witness bindings.

UnusedMatches

Allow unused named matches.

zeroFeatures :: Features Source #

An emtpy feature set, with all flags set to False.

setFeature :: Feature -> Bool -> Features -> Features Source #

Set a language Flag in the Profile.

Compliance

complies Source #

Arguments

:: (Ord n, Show n, Complies c) 
=> Profile n

Fragment profile giving the supported language features and primitive operators.

-> c a n

The thing to check.

-> Maybe (Error a n) 

Check whether a core thing complies with a language fragment profile.

compliesWithEnvs Source #

Arguments

:: (Ord n, Show n, Complies c) 
=> Profile n

Fragment profile giving the supported language features and primitive operators.

-> KindEnv n

Starting kind environment.

-> TypeEnv n

Starting type environment.

-> c a n

The thing to check.

-> Maybe (Error a n) 

Like complies but with some starting environments.

class Complies c Source #

Class of things we can check language fragment compliance for.

Minimal complete definition

compliesX

Instances

Complies Alt Source # 

Methods

compliesX :: (Ord n, Show n) => Profile n -> Env n -> Env n -> Context -> Alt a n -> CheckM a n (Set n, Set n)

Complies Exp Source # 

Methods

compliesX :: (Ord n, Show n) => Profile n -> Env n -> Env n -> Context -> Exp a n -> CheckM a n (Set n, Set n)

Complies Module Source # 

Methods

compliesX :: (Ord n, Show n) => Profile n -> Env n -> Env n -> Context -> Module a n -> CheckM a n (Set n, Set n)

data Error a n Source #

Language fragment compliance violations.

Constructors

ErrorUnsupported !Feature

Found an unsupported language feature.

ErrorUndefinedPrim !n

Found an undefined primitive operator.

ErrorUndefinedVar !n

Found an unbound variable.

ErrorShadowedBind !n

Found a variable binder that shadows another one at a higher scope, but the profile doesn't permit this.

ErrorUnusedBind !n

Found a bound variable with no uses, but the profile doesn't permit this.

ErrorNakedType !(Type n)

Found a naked type that isn't used as a function argument.

ErrorNakedWitness !(Witness a n)

Found a naked witness that isn't used as a function argument.

Instances

(Show a, Show n) => Show (Error a n) Source # 

Methods

showsPrec :: Int -> Error a n -> ShowS #

show :: Error a n -> String #

showList :: [Error a n] -> ShowS #

(Pretty n, Eq n) => Pretty (Error a n) Source # 

Associated Types

data PrettyMode (Error a n) :: * Source #

Methods

pprDefaultMode :: PrettyMode (Error a n) Source #

ppr :: Error a n -> Doc Source #

pprPrec :: Int -> Error a n -> Doc Source #

pprModePrec :: PrettyMode (Error a n) -> Int -> Error a n -> Doc Source #