[project @ 1996-01-08 20:28:12 by partain]
[ghc-hetmet.git] / ghc / compiler / typecheck / Typecheck.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1995
3 %
4 \section[Typecheck]{Outside-world interfaces to the typechecker}
5
6 \begin{code}
7 #include "HsVersions.h"
8
9 module Typecheck (
10         typecheckModule,
11
12         -- and to make the interface self-sufficient...
13         Module, Bag, CE(..), Binds, FixityDecl, E, Expr, InPat,
14         RenamedPat(..), TypecheckedPat, Id, Inst, Maybe, MaybeErr,
15         Name, PprStyle, PrettyRep, ProtoName, Error(..), Pretty(..),
16         InstInfo, SplitUniqSupply, GlobalSwitch, UniqFM
17     ) where
18
19 import TcMonad          -- typechecking monad machinery
20 import AbsSyn           -- the stuff being typechecked
21
22 import E                ( nullE, E )
23 import Maybes           ( MaybeErr(..) )
24 import SrcLoc           ( mkUnknownSrcLoc, SrcLoc )
25 import TcModule         -- tcModule, and associated stuff
26 import Util             -- for pragmas only
27 \end{code}
28
29 The typechecker stuff lives inside a complicated world of @TcM@
30 monadery.  This module provides three interfaces into that world, one
31 for typechecking a module, another for typechecking an expression, and
32 one for typechecking an interface.  This last one works as if
33 @typecheckModule@ was applied to the very simple module:
34 \begin{verbatim}
35 module EmptyModule where
36
37 import InterfaceOfInterest
38 \end{verbatim}
39 This is used when we want to augment an @E@ with information from an
40 interface.  (Used in the interpreter.)
41
42 \begin{code}
43 typecheckModule ::
44        (GlobalSwitch -> Bool)   -- cmd-line switch checker
45     -> SplitUniqSupply          -- name supply in
46     -> GlobalNameFuns           -- renamer info (for doing derivings)
47     -> RenamedModule            -- input module
48         
49     ->  ------- OUTPUTS -----------
50         -- depends v much on whether typechecking succeeds or not!
51     MaybeErr
52        -- SUCCESS ...
53        (((TypecheckedBinds,     -- binds from class decls; does NOT
54                                 --    include default-methods bindings
55          TypecheckedBinds,      -- binds from instance decls; INCLUDES
56                                 --    class default-methods binds
57          TypecheckedBinds,      -- binds from value decls
58          [(Inst, TypecheckedExpr)]),
59
60         ([RenamedFixityDecl],   -- things for the interface generator
61          [Id],                  -- to look at...
62          CE,
63          TCE,
64          Bag InstInfo),
65
66         FiniteMap TyCon [[Maybe UniType]],
67                                 -- source tycon specialisation requests
68
69 --UNUSED:       E,                      -- new cumulative E (with everything)
70         E,                      -- E just for stuff from THIS module
71                 -- NB: if you want the diff between two prev Es: i.e.,
72                 -- things in cumulative E that were added because of
73                 -- this module's import-ery, just do:
74                 --      bigE `minusE` thisModuleE
75
76         PprStyle->Pretty))      -- stuff to print for -ddump-deriving
77
78        -- FAILURE ...
79        (Bag Error)              -- pretty-print this to find out what went wrong
80
81 typecheckModule sw_chkr us renamer_name_funs modyule
82   = initTc sw_chkr us (tcModule nullE renamer_name_funs modyule)
83 \end{code}