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

Safe HaskellSafe
LanguageHaskell98

DDC.Core.Module

Contents

Synopsis

Modules

data Module a n Source #

A module can be mutually recursive with other modules.

Constructors

ModuleCore 

Fields

Instances

Reannotate Module Source # 

Methods

reannotate :: (a -> b) -> Module a n -> Module b n Source #

reannotateM :: Monad m => (a -> m b) -> Module a n -> m (Module b n) Source #

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)

SpreadX (Module a) Source # 

Methods

spreadX :: Ord n => Env n -> Env n -> Module a n -> Module a n Source #

SupportX (Module a) Source # 

Methods

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

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

Methods

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

show :: Module a n -> String #

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

(NFData a, NFData n) => NFData (Module a n) Source # 

Methods

rnf :: Module a n -> () #

data PrettyMode (Module a n) Source # 

isMainModule :: Module a n -> Bool Source #

Check if this is the Main module.

moduleDataDefs :: Ord n => Module a n -> DataDefs n Source #

Get the data type definitions visible in a module.

moduleTypeDefs :: Ord n => Module a n -> [(n, (Kind n, Type n))] Source #

Get the data type definitions visible in a module.

moduleKindEnv :: Ord n => Module a n -> KindEnv n Source #

Get the top-level kind environment of a module, from its imported types.

moduleTypeEnv :: Ord n => Module a n -> TypeEnv n Source #

Get the top-level type environment of a module, from its imported values.

moduleEnvT Source #

Arguments

:: Ord n 
=> KindEnv n

Primitive kind environment.

-> Module a n

Module to extract environemnt from.

-> EnvT n 

Extract the top-level EnvT environment from a module.

This includes kinds for abstract types, data types, and type equations, but not primitive types which are fragment specific.

moduleEnvX Source #

Arguments

:: Ord n 
=> KindEnv n

Primitive kind environment.

-> TypeEnv n

Primitive type environment.

-> DataDefs n

Primitive data type definitions.

-> Module a n

Module to extract environemnt from.

-> EnvX n 

Extract the top-level EnvX environment from a module.

modulesEnvT Source #

Arguments

:: Ord n 
=> KindEnv n

Primitive kind environment.

-> [Module a n]

Modules to build environment from.

-> EnvT n 

Extract the top-level EnvT environment from several modules.

modulesEnvX Source #

Arguments

:: Ord n 
=> KindEnv n

Primitive kind environment.

-> TypeEnv n

Primitive type environment.

-> DataDefs n

Primitive data type definitions.

-> [Module a n]

Modules to build environment from.

-> EnvX n 

Extract the top-level EnvT environment from several modules.

moduleTopBinds :: Ord n => Module a n -> Set n Source #

Get the set of top-level value bindings in a module.

moduleTopBindTypes :: Ord n => Module a n -> Map n (Type n) Source #

Get a map of named top-level bindings to their types.

mapTopBinds :: (Bind n -> Exp a n -> b) -> Module a n -> [b] Source #

Apply a function to all the top-level bindings in a module, producing a list of the results.

Module maps

type ModuleMap a n = Map ModuleName (Module a n) Source #

Map of module names to modules.

modulesExportTypes :: Ord n => ModuleMap a n -> KindEnv n -> KindEnv n Source #

Add the kind environment exported by all these modules to the given one.

modulesExportValues :: Ord n => ModuleMap a n -> TypeEnv n -> TypeEnv n Source #

Add the type environment exported by all these modules to the given one.

Module Names

readModuleName :: String -> Maybe ModuleName Source #

Read a string like M3 as a module name.

isMainModuleName :: ModuleName -> Bool Source #

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

moduleNameMatchesPath :: FilePath -> ModuleName -> Bool Source #

Check whether a module name matches the given file path of the module.

If the module is named M1.M2.M3 then the file needs to be called PATHM1M2/M3.EXT for some base PATH and extension EXT.

Qualified names.

data QualName n Source #

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

Constructors

QualName ModuleName n 

Instances

Show n => Show (QualName n) Source # 

Methods

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

show :: QualName n -> String #

showList :: [QualName n] -> ShowS #

NFData n => NFData (QualName n) Source # 

Methods

rnf :: QualName n -> () #

Export Definitions

data ExportSource n t Source #

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

(Show n, Show t) => Show (ExportSource n t) Source # 
(NFData n, NFData t) => NFData (ExportSource n t) Source # 

Methods

rnf :: ExportSource n t -> () #

takeTypeOfExportSource :: ExportSource n t -> Maybe t Source #

Take the type of an imported thing, if there is one.

mapTypeOfExportSource :: (t -> t) -> ExportSource n t -> ExportSource n t Source #

Apply a function to any type in an ExportSource.

Import Definitions

Import Types

data ImportType n t Source #

Define a 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

Instances

Show t => Show (ImportType n t) Source # 

Methods

showsPrec :: Int -> ImportType n t -> ShowS #

show :: ImportType n t -> String #

showList :: [ImportType n t] -> ShowS #

(NFData n, NFData t) => NFData (ImportType n t) Source # 

Methods

rnf :: ImportType n t -> () #

kindOfImportType :: ImportType n t -> t Source #

Take the kind of an ImportType.

mapKindOfImportType :: (t -> t) -> ImportType n t -> ImportType n t Source #

Apply a function to the kind of an ImportType

Import Capabilities

data ImportCap n t Source #

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

Instances

Show t => Show (ImportCap n t) Source # 

Methods

showsPrec :: Int -> ImportCap n t -> ShowS #

show :: ImportCap n t -> String #

showList :: [ImportCap n t] -> ShowS #

(NFData n, NFData t) => NFData (ImportCap n t) Source # 

Methods

rnf :: ImportCap n t -> () #

typeOfImportCap :: ImportCap n t -> t Source #

Take the type of an ImportCap.

mapTypeOfImportCap :: (t -> t) -> ImportCap n t -> ImportCap n t Source #

Apply a function to the type in an ImportCapability.

Import Types

data ImportValue n t Source #

Define a foreign value being imported into a module.

Constructors

ImportValueModule

Value imported from a module that we compiled ourselves.

Fields

ImportValueSea

Value imported via the C calling convention.

Fields

Instances

(Show n, Show t) => Show (ImportValue n t) Source # 

Methods

showsPrec :: Int -> ImportValue n t -> ShowS #

show :: ImportValue n t -> String #

showList :: [ImportValue n t] -> ShowS #

(NFData n, NFData t) => NFData (ImportValue n t) Source # 

Methods

rnf :: ImportValue n t -> () #

typeOfImportValue :: ImportValue n t -> t Source #

Take the type of an imported thing.

mapTypeOfImportValue :: (t -> t) -> ImportValue n t -> ImportValue n t Source #

Apply a function to the type in an ImportValue.