A module defines a collection of values, datatypes, type synonyms, classes, etc. (see Section 4) in an environment created by a set of imports, resources brought into scope from other modules, and exports some of these resources, making them available to other modules. We use the term entity to refer to a value, type, or class defined in, imported into, or perhaps exported from a module.
A Haskell program is a collection of modules, one of which, by convention, must be called Main and must export the value main. The value of the program is the value of the identifier main in module Main, which must be a computation of type IO t for some type t (see Section 7). When the program is executed, the computation main is performed, and its result (of type t) is discarded.
Modules may reference other modules via explicit import declarations, each giving the name of a module to be imported and specifying its entities to be imported. Modules may be mutually recursive.
Modules are used solely for name-space control, and are not first class values.
A multi-module Haskell program can be converted into a single-module
program by giving each entity a unique name, changing all occurrences
to refer to the appropriate unique name, and then concatenating all the module
bodies. For example, here is a three-module program:
module Main where
import A
import B
main = A.f >> B.f
module A where
f = ...
module B where
f = ...
It is equivalent to the following single-module program:
module Main where
main = af >> bf
af = ...
bf = ...
Because they are mutually recursive,
modules allow a program to be partitioned freely without regard to
dependencies.
The name-space for modules themselves is flat, with each module being associated with a unique module name (which are Haskell identifiers beginning with a capital letter; i.e. modid). There is one distinguished module, Prelude, which is imported into all programs by default (see Section 5.6), plus a set of standard library modules that may be imported as required (see the Haskell Library Report[8]).
A module defines a mutually recursive scope containing declarations for value bindings, data types, type synonyms, classes, etc. (see Section 4).
module | -> | module modid [exports] where body | |
| | body | ||
body | -> | { impdecls ; topdecls } | |
| | { impdecls } | ||
| | { topdecls } | ||
modid | -> | conid | |
impdecls | -> | impdecl1 ; ... ; impdecln | (n>=1) |
topdecls | -> | topdecl1 ; ... ; topdecln | (n>=1) |
A module begins with a header: the keyword module, the module name, and a list of entities (enclosed in round parentheses) to be exported. The header is followed by an optional list of import declarations that specify modules to be imported, optionally restricting the imported bindings. This is followed the module body. The module body is simply a list of top-level declarations (topdecls), as described in Section 4.
An abbreviated form of module, consisting only of the module body, is permitted. If this is used, the header is assumed to be `module Main(main) where'. If the first lexeme in the abbreviated module is not a {, then the layout rule applies for the top level of the module.
exports | -> | ( export1 , ... , exportn [ , ] ) | (n>=0) |
export | -> | qvar | |
| | qtycon [(..) | ( qcname1 , ... , qcnamen )] | (n>=0) | |
| | qtycls [(..) | ( qvar1 , ... , qvarn )] | (n>=0) | |
| | module modid | ||
qcname | -> | qvar | qcon |
An export list identifies the entities to be exported by a module declaration. A module implementation may only export an entity that it declares, or that it imports from some other module. If the export list is omitted, all values, types and classes defined in the module are exported, but not those that are imported.
Entities in an export list may be named as follows:
impdecl | -> | import [qualified] modid [as modid] [impspec] | |
| | (empty declaration) | ||
impspec | -> | ( import1 , ... , importn [ , ] ) | (n>=0) |
| | hiding ( import1 , ... , importn [ , ] ) | (n>=0) | |
import | -> | var | |
| | tycon [ (..) | ( cname1 , ... , cnamen )] | (n>=1) | |
| | tycls [(..) | ( var1 , ... , varn )] | (n>=0) | |
cname | -> | var | con |
The entities exported by a module may be brought into scope in another module with an import declaration at the beginning of the module. The import declaration names the module to be imported and optionally specifies the entities to be imported. A single module may be imported by more than one import declaration. Imported names serve as top level declarations: they scope over the entire body of the module but may be shadowed by local non-top-level bindings. The effect of multiple import declarations is cumulative: an entity is in scope if it is named by any of the import declarations in a module. The ordering of imports is irrelevant.
Exactly which entities are to be imported can be specified in one of three ways:
The list must name only entities exported by the imported module. The list may be empty, in which case nothing except the instances are imported.
The effect of multiple import declarations is strictly cumulative: hiding an entity on one import declaration does not prevent the same entity from being imported by another import from the same module.
An import declaration that uses the qualified keyword brings into scope only the qualified names of the imported entities (Section 5.5.1); if the qualified keyword is omitted, both qualified and unqualified names are brought into scope. The qualifier on the imported name is either the name of the imported module, or the local alias given in the as clause on the import statement (Section 5.3.2). Hence, the qualifier is not necessarily the name of the module in which the entity was originally declared.
The ability to exclude the unqualified names allows full programmer control of
the unqualified namespace: a locally defined entity can share the same
name as a qualified import:
module Ring where
import qualified Prelude -- All Prelude names must be qualified
import List( nub )
l1 + l2 = l1 ++ l2 -- This + differs from the one in the Prelude
l1 * l2 = nub (l1 + l2) -- This * differs from the one in the Prelude
succ = (Prelude.+ 1)
Imported modules may be assigned a local alias in the importing module
using the as clause.
For example, in
import qualified Complex as C
entities must be referenced using `C.' as a qualifier instead of
`Complex.'. This also allows a different module to be substituted
for Complex without changing the qualifiers used for the imported module.
It is legal for more than one module in scope to
use the same qualifier, provided that all names can still be resolved unambiguously.
For example:
module M where
import qualified Foo as A
import qualified Baz as A
x = A.f
This module is legal provided only that Foo and Baz do not both export f.
An as clause may also be used on an un-qualified import statement:
import Foo(f) as A
This declaration brings into scope f and A.f.
Instance declarations cannot be explicitly named on import or export lists. All instances in scope within a module are always exported and any import brings all instances in from the imported module. Thus, an instance declaration is in scope if and only if a chain of import declarations leads to the module containing the instance declaration.
For example, import M() does not bring
any new names in scope from module M, but does bring in any instances
visible in M. A module whose only purpose is to provide instance
declarations can have an empty export list. For example
module MyInstances() where
instance Show (a -> b) where
show fn = "<<function>>"
instance Show (IO a) where
show io = "<<IO action>>"
A qualified name is written as modid.name. Since qualifier names are part of the lexical syntax, no spaces are allowed between the qualifier and the name. Sample parses are shown below.
This | Lexes as this |
f.g | f . g (three tokens) |
F.g | F.g (qualified `g') |
f.. | f .. (two tokens) |
F.. | F.. (qualified `.') |
F. | F . (two tokens) |
A qualified name is brought into scope:
The qualifier does not change the syntactic treatment of a name; for example, Prelude.+ is an infix operator with the same fixity as the definition of + in the Prelude (Section 4.4.2).
Qualifiers may also be applied to names imported by an unqualified import; this allows a qualified import to be replaced with an unqualified one without forcing changes in the references to the imported names.
If a module contains a bound occurrence of a name, such as f or A.f, it must be possible unambiguously to resolve which entity is thereby referred to; that is, there must be only one binding for f or A.f respectively.
It is not an error for there to exist names that cannot be so
resolved, provided that the program does not mention those names. For example:
module A where
import B
import C
tup = (b, c, d, x)
module B( d, b, x, y ) where
import D
x = ...
y = ...
b = ...
module C( d, c, x, y ) where
import D
x = ...
y = ...
c = ...
module D( d ) where
d = ...
Consider the definition of tup.
Every module in a Haskell program must be closed. That is,
every name explicitly mentioned by the source code
must be either defined locally or imported from another module.
Entities that the compiler requires for type checking or other
compile time analysis need not be imported if they are not mentioned
by name. The Haskell compilation system is responsible for finding
any information needed for compilation without the help of the
programmer. That is, the import of a variable x does not
require that the datatypes and classes in the signature of x be
brought into the module along with x unless these entities are
referenced by name in the user program. The Haskell
system silently imports any information that must accompany an
entity for type checking or any other purposes. Such entities need
not even be explicitly exported: the following program is valid even though
T does not escape M1:
module M1(x) where
data T = T
x = T
module M2 where
import M1(x)
y = x
In this example, there is no way to supply an explicit type signature
for y since T is not in scope.
Whether or not T is explicitly exported, module M2 knows
enough about T to correctly type check the program.
The type of an exported entity is unaffected by non-exported type
synonyms. For example, in
module M(x) where
type T = Int
x :: T
x = 1
the type of x is both T and Int; these are interchangeable even
when T is not in scope. That is, the definition of T is available
to any module that encounters it whether or not the name T is
in scope. The only reason to export T is to allow other modules to
refer it by name; the type checker finds the definition of T if
needed whether or not it is exported.
Prelude and library modules differ from other modules in that their semantics (but not their implementation) are a fixed part of the Haskell language definition. This means, for example, that a compiler may optimize calls to functions in the Prelude without consulting the source code of the Prelude.
The Prelude module is imported automatically into all modules as if by the statement `import Prelude', if and only if it is not imported with an explicit import declaration. This provision for explicit import allows values defined in the Prelude to be hidden from the unqualified name space. The Prelude module is always available as a qualified import: an implicit `import qualified Prelude' is part of every module and names prefixed by `Prelude.' can always be used to refer to entities in the Prelude.
The semantics of the entities in Prelude is specified by an implementation of Prelude written in Haskell , given in Appendix A. Some datatypes (such as Int) and functions (such as Int addition) cannot be specified directly in Haskell . Since the treatment of such entities depends on the implementation, they are not formally defined in the appendix. The implementation of Prelude is also incomplete in its treatment of tuples: there should be an infinite family of tuples and their instance declarations, but the implementation only gives a scheme.
Appendix A defines the module Prelude using several other modules: PreludeList, PreludeIO, and so on. These modules are not part of Haskell 98, and they cannot be imported separately. They are simply there to help explain the structure of the Prelude module; they should be considered part of its implementation, not part of the language definition.
The rules about the Prelude have been cast so that it is
possible to use Prelude names for nonstandard purposes; however,
every module that does so must have an import declaration
that makes this nonstandard usage explicit. For example:
module A where
import Prelude hiding (null)
null x = []
Module A redefines null, but it must indicate this by
importing Prelude without null. Furthermore, A exports null,
but every module that imports null unqualified from A must also
hide
null from Prelude just as A does. Thus there is little danger
of accidentally shadowing Prelude names.
It is possible to construct and use a different module to serve in
place of the Prelude. Other than the fact that it is implicitly
imported, the Prelude is an ordinary Haskell module; it is special
only in that some objects in the Prelude are referenced by special
syntactic constructs. Redefining names used by the Prelude does not
affect the meaning of these special constructs. For example, in
module B where
import qualified Prelude
import MyPrelude
...
B imports nothing from Prelude, but the
explicit import qualified Prelude declaration prevents the automatic
import of
Prelude. import MyPrelude brings the
non-standard prelude into scope. As before, the
standard prelude names are hidden explicitly. Special
syntax, such as lists or tuples, always refers to prelude entities:
there is no way to redefine the meaning of [x] in terms of a
different implementation of lists.
It is not possible, however, to hide instance declarations in the Prelude. For example, one cannot define a new instance for Show Char.
The ability to export a datatype without its constructors
allows the construction of abstract datatypes (ADTs). For example,
an ADT for stacks could be defined as:
module Stack( StkType, push, pop, empty ) where
data StkType a = EmptyStk | Stk a (StkType a)
push x s = Stk x s
pop (Stk _ s) = s
empty = EmptyStk
Modules importing Stack cannot construct values of type StkType
because they do not have access to the constructors of the type.
It is also possible to build an ADT on top of an existing type by
using a newtype declaration. For example, stacks can be defined
with lists:
module Stack( StkType, push, pop, empty ) where
newtype StkType a = Stk [a]
push x (Stk s) = Stk (x:s)
pop (Stk (x:s)) = Stk s
empty = Stk []