ddc-source-tetra-0.4.2.1: Disciplined Disciple Compiler source language.

Safe HaskellSafe
LanguageHaskell98

DDC.Source.Tetra.Module

Contents

Description

Definition of Source Tetra modules.

Synopsis

Modules

data Module l Source

Constructors

Module 

Fields

moduleName :: !ModuleName

Name of this module

moduleExportTypes :: [GName l]

Names of exported types (level-1).

moduleExportValues :: [GName l]

Names of exported values (level-0).

moduleImportModules :: [ModuleName]

Imported modules.

moduleImportTypes :: [(GName l, ImportType (GName l))]

Kinds of imported foreign types.

moduleImportCaps :: [(GName l, ImportCap (GName l))]

Types of imported capabilities.

moduleImportValues :: [(GName l, ImportValue (GName l))]

Types of imported foreign values.

moduleTops :: [Top l]

Top-level things

Instances

isMainModule :: Module l -> Bool Source

Check if this is the Main module.

data ExportSource n :: * -> *

Define thing exported from a module.

Constructors

ExportSourceLocal

A name defined in this module, with an explicit type.

ExportSourceLocalNoType

A named defined in this module, without a type attached. We use this version for source language where we infer the type of the exported thing.

Instances

data ImportType n :: * -> *

Define a foreign type being imported into a module.

Constructors

ImportTypeAbstract

Type imported abstractly.

Used for phantom types of kind Data, as well as regions, effects, and any other type that does not have kind Data. When a type is imported abstractly it has no associated values, so we can just say that we have the type without worrying about how to represent its associated values.

ImportTypeBoxed

Type of some boxed data.

The objects follow the standard heap object layout, but the code that constructs and destructs them may have been written in a different language.

This is used when importing data types defined in Salt modules.

Fields

importTypeBoxed :: !(Kind n)
 

Instances

data ImportCap n :: * -> *

Define a foreign capability being imported into a module.

Constructors

ImportCapAbstract

Capability imported abstractly. For capabilities like (Read r) for some top-level region r we can just say that we have the capability.

Fields

importCapAbstractType :: !(Type n)
 

Instances

Show n => Show (ImportCap n) 
NFData n => NFData (ImportCap n) 

data ImportValue n :: * -> *

Define a foreign value being imported into a module.

Constructors

ImportValueModule

Value imported from a module that we compiled ourselves.

Fields

importValueModuleName :: !ModuleName

Name of the module that we're importing from.

importValueModuleVar :: !n

Name of the the value that we're importing.

importValueModuleType :: !(Type n)

Type of the value that we're importing.

importValueModuleArity :: !(Maybe (Int, Int, Int))

Calling convention for this value, including the number of type parameters, value parameters, and boxings.

ImportValueSea

Value imported via the C calling convention.

Fields

importValueSeaVar :: !String

Name of the symbol being imported. This can be different from the name that we give it in the core language.

importValueSeaType :: !(Type n)

Type of the value that we're importing.

Instances

Module Names

data QualName n :: * -> *

A fully qualified name, including the name of the module it is from.

Constructors

QualName ModuleName n 

Instances

Show n => Show (QualName n) 
NFData n => NFData (QualName n) 

data ModuleName :: *

A hierarchical module name.

Constructors

ModuleName [String] 

isMainModuleName :: ModuleName -> Bool

Check whether this is the name of the "Main" module.

Top-level things

data Top l Source

Constructors

TopClause

Some top-level, possibly recursive clauses.

Fields

topAnnot :: GAnnot l
 
topClause :: GClause l
 
TopData

Data type definition.

Fields

topAnnot :: GAnnot l
 
topDataDef :: DataDef (GName l)
 

Instances

ExpandLanguage l => Expand Top l Source 
Defix Top l Source 
ShowLanguage l => Show (Top l) Source 
NFDataLanguage l => NFData (Top l) Source 

Data type definitions

data DataDef n Source

Data type definitions.

Constructors

DataDef 

Fields

dataDefTypeName :: !n

Data type name.

dataDefParams :: [Bind n]

Type parameters.

dataDefCtors :: [DataCtor n]

Parameters and return type of each constructor.

Instances