edd9a2cfdfd3ce3beb25dcc0f4a8915b41a82d60
[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         dsLookupGlobalValue,
19
20         ValueEnv,
21         dsWarn, 
22         DsWarnings,
23         DsMatchContext(..), DsMatchKind(..)
24     ) where
25
26 #include "HsVersions.h"
27
28 import Bag              ( emptyBag, snocBag, bagToList, Bag )
29 import ErrUtils         ( WarnMsg, pprBagOfErrors )
30 import HsSyn            ( OutPat )
31 import Id               ( mkSysLocal, setIdUnique, Id )
32 import Module           ( Module )
33 import Name             ( Name, maybeWiredInIdName )
34 import Var              ( TyVar, setTyVarUnique )
35 import VarEnv
36 import Outputable
37 import SrcLoc           ( noSrcLoc, SrcLoc )
38 import TcHsSyn          ( TypecheckedPat )
39 import TcEnv            ( ValueEnv )
40 import Type             ( Type )
41 import UniqSupply       ( initUs_, splitUniqSupply, uniqFromSupply, uniqsFromSupply,
42                           UniqSM, UniqSupply )
43 import Unique           ( Unique )
44 import UniqFM           ( lookupWithDefaultUFM )
45 import Util             ( zipWithEqual )
46
47 infixr 9 `thenDs`
48 \end{code}
49
50 Now the mondo monad magic (yes, @DsM@ is a silly name)---carry around
51 a @UniqueSupply@ and some annotations, which
52 presumably include source-file location information:
53 \begin{code}
54 type DsM result =
55         UniqSupply
56         -> ValueEnv
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  :: UniqSupply
72         -> ValueEnv
73         -> Module   -- module name: for profiling
74         -> DsM a
75         -> (a, DsWarnings)
76
77 initDs init_us genv mod action
78   = action init_us genv noSrcLoc mod emptyBag
79
80 thenDs :: DsM a -> (a -> DsM b) -> DsM b
81 andDs  :: (a -> a -> a) -> DsM a -> DsM a -> DsM a
82
83 thenDs m1 m2 us genv loc mod warns
84   = case splitUniqSupply us                 of { (s1, s2) ->
85     case (m1 s1 genv loc mod warns)  of { (result, warns1) ->
86     m2 result s2 genv loc mod warns1}}
87
88 andDs combiner m1 m2 us genv loc mod warns
89   = case splitUniqSupply us                 of { (s1, s2) ->
90     case (m1 s1 genv loc mod warns)  of { (result1, warns1) ->
91     case (m2 s2 genv loc mod warns1) of { (result2, warns2) ->
92     (combiner result1 result2, warns2) }}}
93
94 returnDs :: a -> DsM a
95 returnDs result us genv loc mod warns = (result, warns)
96
97 listDs :: [DsM a] -> DsM [a]
98 listDs []     = returnDs []
99 listDs (x:xs)
100   = x           `thenDs` \ r  ->
101     listDs xs   `thenDs` \ rs ->
102     returnDs (r:rs)
103
104 mapDs :: (a -> DsM b) -> [a] -> DsM [b]
105
106 mapDs f []     = returnDs []
107 mapDs f (x:xs)
108   = f x         `thenDs` \ r  ->
109     mapDs f xs  `thenDs` \ rs ->
110     returnDs (r:rs)
111
112 foldlDs :: (a -> b -> DsM a) -> a -> [b] -> DsM a
113
114 foldlDs k z []     = returnDs z
115 foldlDs k z (x:xs) = k z x `thenDs` \ r ->
116                      foldlDs k r xs
117
118 mapAndUnzipDs :: (a -> DsM (b, c)) -> [a] -> DsM ([b], [c])
119
120 mapAndUnzipDs f []     = returnDs ([], [])
121 mapAndUnzipDs f (x:xs)
122   = f x                 `thenDs` \ (r1, r2)  ->
123     mapAndUnzipDs f xs  `thenDs` \ (rs1, rs2) ->
124     returnDs (r1:rs1, r2:rs2)
125
126 zipWithDs :: (a -> b -> DsM c) -> [a] -> [b] -> DsM [c]
127
128 zipWithDs f []     ys = returnDs []
129 zipWithDs f (x:xs) (y:ys)
130   = f x y               `thenDs` \ r  ->
131     zipWithDs f xs ys   `thenDs` \ rs ->
132     returnDs (r:rs)
133 \end{code}
134
135 And all this mysterious stuff is so we can occasionally reach out and
136 grab one or more names.  @newLocalDs@ isn't exported---exported
137 functions are defined with it.  The difference in name-strings makes
138 it easier to read debugging output.
139
140 \begin{code}
141 newSysLocalDs, newFailLocalDs :: Type -> DsM Id
142 newSysLocalDs ty us genv loc mod warns
143   = case uniqFromSupply us of { assigned_uniq ->
144     (mkSysLocal SLIT("ds") assigned_uniq ty, warns) }
145
146 newSysLocalsDs tys = mapDs newSysLocalDs tys
147
148 newFailLocalDs ty us genv loc mod warns
149   = case uniqFromSupply us of { assigned_uniq ->
150     (mkSysLocal SLIT("fail") assigned_uniq ty, warns) }
151         -- The UserLocal bit just helps make the code a little clearer
152
153 getUniqueDs :: DsM Unique
154 getUniqueDs us genv loc mod warns
155   = case (uniqFromSupply us) of { assigned_uniq ->
156     (assigned_uniq, warns) }
157
158 duplicateLocalDs :: Id -> DsM Id
159 duplicateLocalDs old_local us genv loc mod warns
160   = case uniqFromSupply us of { assigned_uniq ->
161     (setIdUnique old_local assigned_uniq, warns) }
162
163 cloneTyVarsDs :: [TyVar] -> DsM [TyVar]
164 cloneTyVarsDs tyvars us genv loc mod warns
165   = case uniqsFromSupply (length tyvars) us of { uniqs ->
166     (zipWithEqual "cloneTyVarsDs" setTyVarUnique tyvars uniqs, warns) }
167 \end{code}
168
169 \begin{code}
170 newTyVarsDs :: [TyVar] -> DsM [TyVar]
171
172 newTyVarsDs tyvar_tmpls us genv loc mod warns
173   = case uniqsFromSupply (length tyvar_tmpls) us of { uniqs ->
174     (zipWithEqual "newTyVarsDs" setTyVarUnique tyvar_tmpls uniqs, warns) }
175 \end{code}
176
177 We can also reach out and either set/grab location information from
178 the @SrcLoc@ being carried around.
179 \begin{code}
180 uniqSMtoDsM :: UniqSM a -> DsM a
181
182 uniqSMtoDsM u_action us genv loc mod warns
183   = (initUs_ us u_action, warns)
184
185 getSrcLocDs :: DsM SrcLoc
186 getSrcLocDs us genv loc mod warns
187   = (loc, warns)
188
189 putSrcLocDs :: SrcLoc -> DsM a -> DsM a
190 putSrcLocDs new_loc expr us genv old_loc mod warns
191   = expr us genv new_loc mod warns
192
193 dsWarn :: WarnMsg -> DsM ()
194 dsWarn warn us genv loc mod warns = ((), warns `snocBag` warn)
195
196 \end{code}
197
198 \begin{code}
199 getModuleDs :: DsM Module
200 getModuleDs us genv loc mod warns = (mod, warns)
201 \end{code}
202
203 \begin{code}
204 dsLookupGlobalValue :: Name -> DsM Id
205 dsLookupGlobalValue name us genv loc mod warns
206   = case maybeWiredInIdName name of
207         Just id -> (id, warns)
208         Nothing -> (lookupWithDefaultUFM genv def name, warns)
209   where
210     def = pprPanic "tcLookupGlobalValue:" (ppr name)
211 \end{code}
212
213
214 %************************************************************************
215 %*                                                                      *
216 \subsection{Type synonym @EquationInfo@ and access functions for its pieces}
217 %*                                                                      *
218 %************************************************************************
219
220 \begin{code}
221 data DsMatchContext
222   = DsMatchContext DsMatchKind [TypecheckedPat] SrcLoc
223   | NoMatchContext
224   deriving ()
225
226 data DsMatchKind
227   = FunMatch Id
228   | CaseMatch
229   | LambdaMatch
230   | PatBindMatch
231   | DoBindMatch
232   | ListCompMatch
233   | LetMatch
234   deriving ()
235 \end{code}