alice
manual.


Alice Project

module
language
extensions


________ Overview ____________________________________________________

Alice ML extends the SML module system in various ways, by providing:

A syntax summary is given below.


________ Local modules _______________________________________________

Unlike SML, Alice ML has no stratification between core and module language. Core declarations (dec), structure declarations (strdec), and toplevel declarations (topdec) are collapsed into one class. As a consequence, structures can be declared local to an expression (via let) and functors as well as signatures can be nested into structures. For example:

fun sortWithoutDups compare l =
let
    structure Set = MkRedBlackSet (type t = string; val compare = compare)
in
    Set.toList (foldr (flip Set.insert) Set.empty l)
end

________ Open declarations ___________________________________________

Alice ML generalises SML's open declaration and allows not only structure identifiers, but arbitrary structure expressions:

open MkRedBlackSet(Int)
open IntInf : INTEGER
open unpack p : (val it : int -> int)

Note that, for backwards compatibility with SML, a sequence of identifiers is not parsed as a functor application, but as a multiple open declaration:

open MkRedBlackSet Int

is an attempt to open two structures MkRedBlackSet and Int, and will thus produce an error. Parentheses are needed to disambiguate, as in either of the following:

open MkRedBlackSet(Int)
open (MkRedBlackSet Int)

________ Higher-order functors _______________________________________

Functor expressions

A direct consequence of allowing local functor declarations is the presence of higher-order functors, even if a bit cumbersome:

functor F (X : S1) =
struct
    functor G (Y : S2) = struct (* ... *) end
end

structure M = let structure Z = F (X) in G (Y) end

Functors are truly higher-order, so that the above example may be simplified to curried form:

functor F (X : S1) (Y : S2) = struct (* ... *) end

Application can be written as in the core language, without parentheses (see below):

structure M = F X Y

The class of structure expressions (strexp) has been extended to include functor expressions. Similar to fun declarations, functor declarations are mere derived forms. The declaration for F above is just sugar for:

structure F = fct X : S1 => fct Y : S2 => struct (* ... *) end

The keyword fct starts a functor expression very much like fn begins a function expression in the core language. Functor expressions can be arbitrarily mixed with other structure expressions. In contrast to SML, there is no distinction between structure and functor identifiers (see incompatibilities).

Note: The keyword structure and the syntactic classes strid, strexp, etc. are kept for compatibility reasons, despite module now being more appropriate.

Functor signatures

The syntax of signatures has been extended to contain functor types. For example, functor F can be described by the following signature:

structure F : fct X : S1 -> fct Y : S2 -> sig (* ... *) end

If the parameters X and Y do not appear in S2 or the rest of the signature, it may be abbreviated as follows:

structure F : S1 -> S2 -> sig (* ... *) end

As another derived form, the following SML/NJ compatible syntax is provided for functor descriptions in signatures:

functor F (X : S1) (Y : S2) : sig (* ... *) end

________ Signature members ___________________________________________

Nested signatures

Like structures and functors, signatures can also be declared anywhere. In particular, this allows signatures inside structures, and consequently, nested signatures:

signature S =
sig
    signature T = sig (* ... *) end
end

structure X :> S =
struct
    signature T = sig (* ... *) end
end

Nested signatures must always be matched exactly. More precisely, a signature S1 with nested T = T1 matches another signature S2 with nested T = T2 only if T1 matches T2, and also T2 matches T1.

Abstract signatures

Analogously to types, nested signatures may be specified abstractly:

signature S =
sig
    signature T
    structure X : T
end

An abstract signature can be matched by any signature. Abstract signatures are particularly useful as functor parameters, because they allow declaring "polymorphic" functors:

functor F (signature S structure X : S) = (* ... *)

The Alice library contains several examples of such polymorphic functors, for example the functors provided by the component manager.

Note: Abstract signatures render the type system of Alice ML undecidable. We do not consider this a problem in practice, since already the simplest program to make the type checker loop is highly artificial:

signature I =
sig
    signature A
    functor F(X : sig
                      signature A = A
                      functor F(X : A) : sig end
                  end) : sig end
end

signature J =
sig
    signature A = I
    functor F(X : I) : sig end
end

(* Try to check J ≤ I *)
functor Loop(X : J) = X : I

Currently, the Alice compiler has no upper limit on the number of substitutions it does during signature matching, so this example will actually make it loop.


________ Dynamic typing and modules as 1st-class values ______________

Modules can be wrapped up and passed as first-class values as so-called packages. The signature of packed modules can be dynamically checked against given signatures. See the section on packages for a description of the package mechanism.


________ Laziness and concurrency ____________________________________

Like core expressions, modules can be evaluated concurrently or lazily. Like in the core language, this can be accomplished by just preceding a module expression with the respective keyword:

lazy strexp
spawn strexp

Evaluating these expressions returns a lazy or concurrent module future, respectively.

Note however that the most frequent cause of lazy module evaluation is the component system. Every structure that is imported from another component is evaluated lazily.

Syntactic sugar

Derived forms analogous to the core language are provided for defining functors that should evaluate lazily or in a separate threads:

functor lazy F (X : S) = strexp
functor spawn G (X : S) = strexp

An application of F is evaluated lazily, while G will spawn a new thread for evaluation. See below for a precise definition of this derived form.

Lazy structure access

Long identifiers have lazy semantics: accessing a structure X via the dot notation X.l does not request X. The structure is only requested if X.l itself is requested.


________ Fixity specifications _______________________________________

Signatures may contain fixity specifications:

signature S =
sig
    type t
    infix 2 ++
    val x :    t
    val op++ : t * t -> t
end

To match a signature with infix specifications, a structure must provide the same infix status directives. The infix environment is part of a structure's principal signature.

Opening structures

Opening a structure with infix specifications pulls in the according infix status into the local environment:

structure M :> S = struct (* ... *) end

open M
val z = x ++ x

Some modules of the Alice library, e.g., in the constraint modeling structure, define infix operators that can be used conveniently this way.

Note: This feature produces a syntactic incompatibility with SML showing up in some rare cases.


________ Syntactic enhancements ______________________________________

Parentheses

Parentheses may be used freely in module and signature expressions:

structure X :> (S' where type t = int) = (F (A))

Parentheses may be dropped from functor arguments:

structure Y = F A B

The derived form for functor arguments, allowing a list dec of declarations being given instead of a structure expression, has been generalized: in a structure expression, parentheses may either enclose another strexp, or a dec. For example,

structure Z = (type t = int val x = 9)

Analogously, in a signature expression, parentheses may enclose either another sigexp, or a spec:

signature S = (type t val x : int)

Functor parameters may also be specified as a spec, generalising the SML functor binding derived forms:

structure F = fct (type t val x : int) => struct val x = x end

Module wildcards

Structure bindings may contain a wildcard instead of a structure identifier:

structure _ = Pickle.SaveVal (type t = int  val x = 43)

In this example, the functor application is performed solely for its side effect, and does not return any interesting result.

Similarly, wildcards are allowed for functor parameters:

functor F (_ : S) = struct (* don't actually need argument *) end

They are also allowed in signatures:

signature FF = fct (_ : A) -> B

However, the same signature may be written more compactly as:

signature FF = A -> B

Recursion using withtype

As in the core language, datatype specifications may be made recursive with type declarations using the withtype keyword:

signature S =
sig
    datatype 'a tree   = TREE of 'a forest
    withtype 'a forest = 'a tree list
end

The op keyword

The keyword op is allowed in value, constructor and exception specifications:

signature S =
sig
    datatype 'a list = nil | op:: of 'a * 'a list
    val op+ : int * int -> int
    exception op!!!
end

________ Syntax ______________________________________________________

The syntax for modules very much resembles the syntax of core language expressions. Derived forms have been marked with (*).

Expressions

exp ::= ...
pack atstrexp : atsigexp transparent packing
pack atstrexp :> atsigexp opaque packing (*)

Structures

atstrexp ::= struct dec end structure
longstrid structure identifier
let dec in strexp end local declarations
( strexp ) parentheses
( dec ) structure (*)
appstrexp ::= atstrexp
appstrexp atstrexp functor application
strexp ::= appstrexp
strexp : sigexp transparent constraint
strexp :> sigexp opaque constraint
unpack infexp : sigexp unpacking
fct strpat => strexp functor
lazy strexp laziness
spawn strexp concurrency
atstrpat ::= ( strid : sigexp ) parameter (*)
( _ : sigexp ) anonymous parameter (*)
( spec ) signature as parameter (*)
strpat ::= atstrpat atomic (*)
strid : sigexp parameter
_ : sigexp anonymous parameter (*)

Signatures

atsigexp ::= sig spec end ground signature
longsigid signature identifier
( sigexp ) parentheses
( spec ) signature (*)
sigexp ::= atsigexp
sigexp where rea specialization
fct strpat -> sigexp functor
atsigexp -> sigexp non-dependent functor (*)
rea ::= type tyvarseq longtycon = ty

Specifications

spec ::= ...
functor fundesc functor specification (*)
signature sigdesc signature specification
fundesc ::= strid atstrpat1 ... atstrpatn : sigexp <and fundesc> functor description (n≥1) (*)
sigdesc ::= sigid <= sigexp> <and sigdesc> signature description

Declarations

dec ::= ...
open strexp generalised open1 (*)
strbind ::= ...
_ <: sigexp> = strexp <and strbind> anonymous structure (*)
funbind ::= <lazy | spawn> strid atstrpat1 ... atstrpatn: | :> sigexp> = strexp <and funbind> functor binding (n≥1) (*)

1) The structure expression strexp does not have the form longstrid1 ... longstridn.

Derived forms

( dec ) struct dec end
_ : sigexp strid : sigexp 1
( strid : sigexp ) strid : sigexp
( _ : sigexp ) strid : sigexp 1
( spec ) strid : ( spec ) 12
open strexp local structure strid = strexp in open strid end 1
functor funbind structure funbind
<lazy|spawnstrid atstrpat1 ... atstrpatn < : | :> sigexp= strexp <and funbind> strid = fct atstrpat1 => ... fct atstrpatn => <lazy|spawnstrexp < : | :> sigexp<and funbind>
_ <: sigexp= strexp <and strbind> strid <: sigexp= strexp <and strbind1
( spec ) sig spec end
atsigexp -> sigexp fct strid : atsigexp -> sigexp 1
functor fundesc structure fundesc
strid atstrpat1 ... atstrpatn: sigexp <and fundesc> strid :fct atstrpat1 -> ... fct atstrpatn -> sigexp <and fundesc>

1) The identifier strid is new.

2) If the strpat occurs in a functor expression fct strpat => strexp, then strexp is rewritten to strexp' by replacing any occurrence of an identifier x bound in spec to strid.x. Likewise, if it occurs in a functor signature fct strpat -> sigexp, then sigexp is rewritten to sigexp' by similar substitution.



last modified 2007/03/05 12:14