[project @ 2000-10-24 08:40:09 by simonpj]
[ghc-hetmet.git] / ghc / compiler / deSugar / DsMonad.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
3 %
4 \section[DsMonad]{@DsMonad@: monadery used in desugaring}
5
6 \begin{code}
7 module DsMonad (
8         DsM,
9         initDs, returnDs, thenDs, andDs, mapDs, listDs,
10         mapAndUnzipDs, zipWithDs, foldlDs,
11         uniqSMtoDsM,
12         newTyVarsDs, cloneTyVarsDs,
13         duplicateLocalDs, newSysLocalDs, newSysLocalsDs,
14         newFailLocalDs,
15         getSrcLocDs, putSrcLocDs,
16         getModuleDs,
17         getUniqueDs,
18         getDOptsDs,
19         dsLookupGlobalValue,
20
21         dsWarn, 
22         DsWarnings,
23         DsMatchContext(..), DsMatchKind(..)
24     ) where
25
26 #include "HsVersions.h"
27
28 import Bag              ( emptyBag, snocBag, Bag )
29 import ErrUtils         ( WarnMsg )
30 import Id               ( mkSysLocal, setIdUnique, Id )
31 import Module           ( Module )
32 import Var              ( TyVar, setTyVarUnique )
33 import Outputable
34 import SrcLoc           ( noSrcLoc, SrcLoc )
35 import TcHsSyn          ( TypecheckedPat )
36 import Type             ( Type )
37 import UniqSupply       ( initUs_, splitUniqSupply, uniqFromSupply, uniqsFromSupply,
38                           UniqSM, UniqSupply )
39 import Unique           ( Unique )
40 import Util             ( zipWithEqual )
41 import Name             ( Name, lookupNameEnv )
42 import HscTypes         ( HomeSymbolTable, PersistentCompilerState(..), 
43                           TyThing(..), TypeEnv, lookupTypeEnv )
44 import CmdLineOpts      ( DynFlags )
45
46 infixr 9 `thenDs`
47 \end{code}
48
49 Now the mondo monad magic (yes, @DsM@ is a silly name)---carry around
50 a @UniqueSupply@ and some annotations, which
51 presumably include source-file location information:
52 \begin{code}
53 type DsM result =
54         DynFlags
55         -> UniqSupply
56         -> (Name -> Id)         -- Lookup well-known Ids
57         -> SrcLoc               -- to put in pattern-matching error msgs
58         -> Module               -- module: for SCC profiling
59         -> DsWarnings
60         -> (result, DsWarnings)
61
62 type DsWarnings = Bag WarnMsg           -- The desugarer reports matches which are
63                                         -- completely shadowed or incomplete patterns
64
65 {-# INLINE andDs #-}
66 {-# INLINE thenDs #-}
67 {-# INLINE returnDs #-}
68
69 -- initDs returns the UniqSupply out the end (not just the result)
70
71 initDs  :: DynFlags
72         -> UniqSupply
73         -> (HomeSymbolTable, PersistentCompilerState, TypeEnv)
74         -> Module   -- module name: for profiling
75         -> DsM a
76         -> (a, DsWarnings)
77
78 initDs dflags init_us (hst,pcs,local_type_env) mod action
79   = action dflags init_us lookup noSrcLoc mod emptyBag
80   where
81         -- This lookup is used for well-known Ids, 
82         -- such as fold, build, cons etc, so the chances are
83         -- it'll be found in the package symbol table.  That's
84         -- why we don't merge all these tables
85     pst = pcs_PST pcs
86     lookup n = case lookupTypeEnv pst n of {
87                  Just (AnId v) -> v ;
88                  other -> 
89                case lookupTypeEnv hst n of {
90                  Just (AnId v) -> v ;
91                  other -> 
92                case lookupNameEnv local_type_env n of
93                  Just (AnId v) -> v ;
94                  other         -> pprPanic "initDS: lookup:" (ppr n)
95                }}
96
97 thenDs :: DsM a -> (a -> DsM b) -> DsM b
98 andDs  :: (a -> a -> a) -> DsM a -> DsM a -> DsM a
99
100 thenDs m1 m2 dflags us genv loc mod warns
101   = case splitUniqSupply us                 of { (s1, s2) ->
102     case (m1 dflags s1 genv loc mod warns)  of { (result, warns1) ->
103     m2 result dflags s2 genv loc mod warns1}}
104
105 andDs combiner m1 m2 dflags us genv loc mod warns
106   = case splitUniqSupply us                 of { (s1, s2) ->
107     case (m1 dflags s1 genv loc mod warns)  of { (result1, warns1) ->
108     case (m2 dflags s2 genv loc mod warns1) of { (result2, warns2) ->
109     (combiner result1 result2, warns2) }}}
110
111 returnDs :: a -> DsM a
112 returnDs result dflags us genv loc mod warns = (result, warns)
113
114 listDs :: [DsM a] -> DsM [a]
115 listDs []     = returnDs []
116 listDs (x:xs)
117   = x           `thenDs` \ r  ->
118     listDs xs   `thenDs` \ rs ->
119     returnDs (r:rs)
120
121 mapDs :: (a -> DsM b) -> [a] -> DsM [b]
122
123 mapDs f []     = returnDs []
124 mapDs f (x:xs)
125   = f x         `thenDs` \ r  ->
126     mapDs f xs  `thenDs` \ rs ->
127     returnDs (r:rs)
128
129 foldlDs :: (a -> b -> DsM a) -> a -> [b] -> DsM a
130
131 foldlDs k z []     = returnDs z
132 foldlDs k z (x:xs) = k z x `thenDs` \ r ->
133                      foldlDs k r xs
134
135 mapAndUnzipDs :: (a -> DsM (b, c)) -> [a] -> DsM ([b], [c])
136
137 mapAndUnzipDs f []     = returnDs ([], [])
138 mapAndUnzipDs f (x:xs)
139   = f x                 `thenDs` \ (r1, r2)  ->
140     mapAndUnzipDs f xs  `thenDs` \ (rs1, rs2) ->
141     returnDs (r1:rs1, r2:rs2)
142
143 zipWithDs :: (a -> b -> DsM c) -> [a] -> [b] -> DsM [c]
144
145 zipWithDs f []     ys = returnDs []
146 zipWithDs f (x:xs) (y:ys)
147   = f x y               `thenDs` \ r  ->
148     zipWithDs f xs ys   `thenDs` \ rs ->
149     returnDs (r:rs)
150 \end{code}
151
152 And all this mysterious stuff is so we can occasionally reach out and
153 grab one or more names.  @newLocalDs@ isn't exported---exported
154 functions are defined with it.  The difference in name-strings makes
155 it easier to read debugging output.
156
157 \begin{code}
158 newSysLocalDs, newFailLocalDs :: Type -> DsM Id
159 newSysLocalDs ty dflags us genv loc mod warns
160   = case uniqFromSupply us of { assigned_uniq ->
161     (mkSysLocal SLIT("ds") assigned_uniq ty, warns) }
162
163 newSysLocalsDs tys = mapDs newSysLocalDs tys
164
165 newFailLocalDs ty dflags us genv loc mod warns
166   = case uniqFromSupply us of { assigned_uniq ->
167     (mkSysLocal SLIT("fail") assigned_uniq ty, warns) }
168         -- The UserLocal bit just helps make the code a little clearer
169
170 getUniqueDs :: DsM Unique
171 getUniqueDs dflags us genv loc mod warns
172   = case (uniqFromSupply us) of { assigned_uniq ->
173     (assigned_uniq, warns) }
174
175 getDOptsDs :: DsM DynFlags
176 getDOptsDs dflags us genv loc mod warns
177   = (dflags, warns)
178
179 duplicateLocalDs :: Id -> DsM Id
180 duplicateLocalDs old_local dflags us genv loc mod warns
181   = case uniqFromSupply us of { assigned_uniq ->
182     (setIdUnique old_local assigned_uniq, warns) }
183
184 cloneTyVarsDs :: [TyVar] -> DsM [TyVar]
185 cloneTyVarsDs tyvars dflags us genv loc mod warns
186   = case uniqsFromSupply (length tyvars) us of { uniqs ->
187     (zipWithEqual "cloneTyVarsDs" setTyVarUnique tyvars uniqs, warns) }
188 \end{code}
189
190 \begin{code}
191 newTyVarsDs :: [TyVar] -> DsM [TyVar]
192
193 newTyVarsDs tyvar_tmpls dflags us genv loc mod warns
194   = case uniqsFromSupply (length tyvar_tmpls) us of { uniqs ->
195     (zipWithEqual "newTyVarsDs" setTyVarUnique tyvar_tmpls uniqs, warns) }
196 \end{code}
197
198 We can also reach out and either set/grab location information from
199 the @SrcLoc@ being carried around.
200 \begin{code}
201 uniqSMtoDsM :: UniqSM a -> DsM a
202
203 uniqSMtoDsM u_action dflags us genv loc mod warns
204   = (initUs_ us u_action, warns)
205
206 getSrcLocDs :: DsM SrcLoc
207 getSrcLocDs dflags us genv loc mod warns
208   = (loc, warns)
209
210 putSrcLocDs :: SrcLoc -> DsM a -> DsM a
211 putSrcLocDs new_loc expr dflags us genv old_loc mod warns
212   = expr dflags us genv new_loc mod warns
213
214 dsWarn :: WarnMsg -> DsM ()
215 dsWarn warn dflags us genv loc mod warns = ((), warns `snocBag` warn)
216
217 \end{code}
218
219 \begin{code}
220 getModuleDs :: DsM Module
221 getModuleDs dflags us genv loc mod warns = (mod, warns)
222 \end{code}
223
224 \begin{code}
225 dsLookupGlobalValue :: Name -> DsM Id
226 dsLookupGlobalValue name dflags us genv loc mod warns
227   = (genv name, warns)
228 \end{code}
229
230
231 %************************************************************************
232 %*                                                                      *
233 \subsection{Type synonym @EquationInfo@ and access functions for its pieces}
234 %*                                                                      *
235 %************************************************************************
236
237 \begin{code}
238 data DsMatchContext
239   = DsMatchContext DsMatchKind [TypecheckedPat] SrcLoc
240   | NoMatchContext
241   deriving ()
242
243 data DsMatchKind
244   = FunMatch Id
245   | CaseMatch
246   | LambdaMatch
247   | PatBindMatch
248   | DoBindMatch
249   | ListCompMatch
250   | LetMatch
251   | RecUpdMatch
252   deriving ()
253 \end{code}