Refactoring and tidyup of HscMain and related things (also fix #1666)
[ghc-hetmet.git] / compiler / basicTypes / SrcLoc.lhs
1 %
2 % (c) The University of Glasgow, 1992-2006
3 %
4
5 \begin{code}
6 -- | This module contains types that relate to the positions of things
7 -- in source files, and allow tagging of those things with locations
8 module SrcLoc (
9         -- * SrcLoc
10         SrcLoc,                 -- Abstract
11
12         -- ** Constructing SrcLoc
13         mkSrcLoc, mkGeneralSrcLoc,
14
15         noSrcLoc,               -- "I'm sorry, I haven't a clue"
16         generatedSrcLoc,        -- Code generated within the compiler
17         interactiveSrcLoc,      -- Code from an interactive session
18
19         advanceSrcLoc,
20
21         -- ** Unsafely deconstructing SrcLoc
22         -- These are dubious exports, because they crash on some inputs
23         srcLocFile,             -- return the file name part
24         srcLocLine,             -- return the line part
25         srcLocCol,              -- return the column part
26         
27         -- ** Misc. operations on SrcLoc
28         pprDefnLoc,
29         
30         -- ** Predicates on SrcLoc
31         isGoodSrcLoc,
32
33         -- * SrcSpan
34         SrcSpan,                -- Abstract
35
36         -- ** Constructing SrcSpan
37         mkGeneralSrcSpan, mkSrcSpan, 
38         noSrcSpan, 
39         wiredInSrcSpan,         -- Something wired into the compiler
40         srcLocSpan,
41         combineSrcSpans,
42         
43         -- ** Deconstructing SrcSpan
44         srcSpanStart, srcSpanEnd,
45         srcSpanFileName_maybe,
46
47         -- ** Unsafely deconstructing SrcSpan
48         -- These are dubious exports, because they crash on some inputs
49         srcSpanFile, 
50         srcSpanStartLine, srcSpanEndLine, 
51         srcSpanStartCol, srcSpanEndCol,
52
53         -- ** Predicates on SrcSpan
54         isGoodSrcSpan, isOneLineSpan,
55
56         -- * Located
57         Located(..), 
58         
59         -- ** Constructing Located
60         noLoc,
61         mkGeneralLocated,
62         
63         -- ** Deconstructing Located
64         getLoc, unLoc, 
65         
66         -- ** Combining and comparing Located values
67         eqLocated, cmpLocated, combineLocs, addCLoc,
68         leftmost_smallest, leftmost_largest, rightmost, 
69         spans, isSubspanOf
70     ) where
71
72 #include "Typeable.h"
73
74 import Util
75 import Outputable
76 import FastString
77
78 import Data.Bits
79 import Data.Data
80 \end{code}
81
82 %************************************************************************
83 %*                                                                      *
84 \subsection[SrcLoc-SrcLocations]{Source-location information}
85 %*                                                                      *
86 %************************************************************************
87
88 We keep information about the {\em definition} point for each entity;
89 this is the obvious stuff:
90 \begin{code}
91 -- | Represents a single point within a file
92 data SrcLoc
93   = SrcLoc      FastString      -- A precise location (file name)
94                 {-# UNPACK #-} !Int             -- line number, begins at 1
95                 {-# UNPACK #-} !Int             -- column number, begins at 1
96   | UnhelpfulLoc FastString     -- Just a general indication
97 \end{code}
98
99 %************************************************************************
100 %*                                                                      *
101 \subsection[SrcLoc-access-fns]{Access functions}
102 %*                                                                      *
103 %************************************************************************
104
105 \begin{code}
106 mkSrcLoc :: FastString -> Int -> Int -> SrcLoc
107 mkSrcLoc x line col = SrcLoc x line col
108
109 -- | Built-in "bad" 'SrcLoc' values for particular locations
110 noSrcLoc, generatedSrcLoc, interactiveSrcLoc :: SrcLoc
111 noSrcLoc          = UnhelpfulLoc (fsLit "<no location info>")
112 generatedSrcLoc   = UnhelpfulLoc (fsLit "<compiler-generated code>")
113 interactiveSrcLoc = UnhelpfulLoc (fsLit "<interactive session>")
114
115 -- | Creates a "bad" 'SrcLoc' that has no detailed information about its location
116 mkGeneralSrcLoc :: FastString -> SrcLoc
117 mkGeneralSrcLoc = UnhelpfulLoc 
118
119 -- | "Good" 'SrcLoc's have precise information about their location
120 isGoodSrcLoc :: SrcLoc -> Bool
121 isGoodSrcLoc (SrcLoc _ _ _) = True
122 isGoodSrcLoc _other         = False
123
124 -- | Gives the filename of the 'SrcLoc' if it is available, otherwise returns a dummy value
125 srcLocFile :: SrcLoc -> FastString
126 srcLocFile (SrcLoc fname _ _) = fname
127 srcLocFile _other             = (fsLit "<unknown file")
128
129 -- | Raises an error when used on a "bad" 'SrcLoc'
130 srcLocLine :: SrcLoc -> Int
131 srcLocLine (SrcLoc _ l _) = l
132 srcLocLine (UnhelpfulLoc s) = pprPanic "srcLocLine" (ftext s)
133
134 -- | Raises an error when used on a "bad" 'SrcLoc'
135 srcLocCol :: SrcLoc -> Int
136 srcLocCol (SrcLoc _ _ c) = c
137 srcLocCol (UnhelpfulLoc s) = pprPanic "srcLocCol" (ftext s)
138
139 -- | Move the 'SrcLoc' down by one line if the character is a newline,
140 -- to the next 8-char tabstop if it is a tab, and across by one
141 -- character in any other case
142 advanceSrcLoc :: SrcLoc -> Char -> SrcLoc
143 advanceSrcLoc (SrcLoc f l _) '\n' = SrcLoc f  (l + 1) 1
144 advanceSrcLoc (SrcLoc f l c) '\t' = SrcLoc f  l (((((c - 1) `shiftR` 3) + 1)
145                                                   `shiftL` 3) + 1)
146 advanceSrcLoc (SrcLoc f l c) _    = SrcLoc f  l (c + 1)
147 advanceSrcLoc loc            _    = loc -- Better than nothing
148 \end{code}
149
150 %************************************************************************
151 %*                                                                      *
152 \subsection[SrcLoc-instances]{Instance declarations for various names}
153 %*                                                                      *
154 %************************************************************************
155
156 \begin{code}
157 -- SrcLoc is an instance of Ord so that we can sort error messages easily
158 instance Eq SrcLoc where
159   loc1 == loc2 = case loc1 `cmpSrcLoc` loc2 of
160                    EQ     -> True
161                    _other -> False
162
163 instance Ord SrcLoc where
164   compare = cmpSrcLoc
165    
166 cmpSrcLoc :: SrcLoc -> SrcLoc -> Ordering
167 cmpSrcLoc (UnhelpfulLoc s1) (UnhelpfulLoc s2) = s1 `compare` s2
168 cmpSrcLoc (UnhelpfulLoc _)  (SrcLoc _ _ _)    = GT
169 cmpSrcLoc (SrcLoc _ _ _)    (UnhelpfulLoc _)  = LT
170
171 cmpSrcLoc (SrcLoc s1 l1 c1) (SrcLoc s2 l2 c2)      
172   = (s1 `compare` s2) `thenCmp` (l1 `compare` l2) `thenCmp` (c1 `compare` c2)
173
174 instance Outputable SrcLoc where
175     ppr (SrcLoc src_path src_line src_col)
176       = getPprStyle $ \ sty ->
177         if userStyle sty || debugStyle sty then
178             hcat [ pprFastFilePath src_path, char ':', 
179                    int src_line,
180                    char ':', int src_col
181                  ]
182         else
183             hcat [text "{-# LINE ", int src_line, space,
184                   char '\"', pprFastFilePath src_path, text " #-}"]
185
186     ppr (UnhelpfulLoc s)  = ftext s
187
188 INSTANCE_TYPEABLE0(SrcSpan,srcSpanTc,"SrcSpan")
189
190 instance Data SrcSpan where
191   -- don't traverse?
192   toConstr _   = abstractConstr "SrcSpan"
193   gunfold _ _  = error "gunfold"
194   dataTypeOf _ = mkNoRepType "SrcSpan"
195 \end{code}
196
197 %************************************************************************
198 %*                                                                      *
199 \subsection[SrcSpan]{Source Spans}
200 %*                                                                      *
201 %************************************************************************
202
203 \begin{code}
204 {- |
205 A SrcSpan delimits a portion of a text file.  It could be represented
206 by a pair of (line,column) coordinates, but in fact we optimise
207 slightly by using more compact representations for single-line and
208 zero-length spans, both of which are quite common.
209
210 The end position is defined to be the column /after/ the end of the
211 span.  That is, a span of (1,1)-(1,2) is one character long, and a
212 span of (1,1)-(1,1) is zero characters long.
213 -}
214 data SrcSpan
215   = SrcSpanOneLine              -- a common case: a single line
216         { srcSpanFile     :: !FastString,
217           srcSpanLine     :: {-# UNPACK #-} !Int,
218           srcSpanSCol     :: {-# UNPACK #-} !Int,
219           srcSpanECol     :: {-# UNPACK #-} !Int
220         }
221
222   | SrcSpanMultiLine
223         { srcSpanFile     :: !FastString,
224           srcSpanSLine    :: {-# UNPACK #-} !Int,
225           srcSpanSCol     :: {-# UNPACK #-} !Int,
226           srcSpanELine    :: {-# UNPACK #-} !Int,
227           srcSpanECol     :: {-# UNPACK #-} !Int
228         }
229
230   | SrcSpanPoint
231         { srcSpanFile     :: !FastString,
232           srcSpanLine     :: {-# UNPACK #-} !Int,
233           srcSpanCol      :: {-# UNPACK #-} !Int
234         }
235
236   | UnhelpfulSpan !FastString   -- Just a general indication
237                                 -- also used to indicate an empty span
238
239 #ifdef DEBUG
240   deriving (Eq, Show)   -- Show is used by Lexer.x, becuase we
241                         -- derive Show for Token
242 #else
243   deriving Eq
244 #endif
245
246 -- | Built-in "bad" 'SrcSpan's for common sources of location uncertainty
247 noSrcSpan, wiredInSrcSpan :: SrcSpan
248 noSrcSpan      = UnhelpfulSpan (fsLit "<no location info>")
249 wiredInSrcSpan = UnhelpfulSpan (fsLit "<wired into compiler>")
250
251 -- | Create a "bad" 'SrcSpan' that has not location information
252 mkGeneralSrcSpan :: FastString -> SrcSpan
253 mkGeneralSrcSpan = UnhelpfulSpan
254
255 -- | Create a 'SrcSpan' corresponding to a single point
256 srcLocSpan :: SrcLoc -> SrcSpan
257 srcLocSpan (UnhelpfulLoc str) = UnhelpfulSpan str
258 srcLocSpan (SrcLoc file line col) = SrcSpanPoint file line col
259
260 -- | Create a 'SrcSpan' between two points in a file
261 mkSrcSpan :: SrcLoc -> SrcLoc -> SrcSpan
262 mkSrcSpan (UnhelpfulLoc str) _ = UnhelpfulSpan str
263 mkSrcSpan _ (UnhelpfulLoc str) = UnhelpfulSpan str
264 mkSrcSpan loc1 loc2
265   | line1 == line2 = if col1 == col2
266                         then SrcSpanPoint file line1 col1
267                         else SrcSpanOneLine file line1 col1 col2
268   | otherwise      = SrcSpanMultiLine file line1 col1 line2 col2
269   where
270         line1 = srcLocLine loc1
271         line2 = srcLocLine loc2
272         col1 = srcLocCol loc1
273         col2 = srcLocCol loc2
274         file = srcLocFile loc1
275
276 -- | Combines two 'SrcSpan' into one that spans at least all the characters
277 -- within both spans. Assumes the "file" part is the same in both inputs
278 combineSrcSpans :: SrcSpan -> SrcSpan -> SrcSpan
279 combineSrcSpans (UnhelpfulSpan _) r = r -- this seems more useful
280 combineSrcSpans l (UnhelpfulSpan _) = l
281 combineSrcSpans start end 
282  = case line1 `compare` line2 of
283      EQ -> case col1 `compare` col2 of
284                 EQ -> SrcSpanPoint file line1 col1
285                 LT -> SrcSpanOneLine file line1 col1 col2
286                 GT -> SrcSpanOneLine file line1 col2 col1
287      LT -> SrcSpanMultiLine file line1 col1 line2 col2
288      GT -> SrcSpanMultiLine file line2 col2 line1 col1
289   where
290         line1 = srcSpanStartLine start
291         col1  = srcSpanStartCol start
292         line2 = srcSpanEndLine end
293         col2  = srcSpanEndCol end
294         file  = srcSpanFile start
295 \end{code}
296
297 %************************************************************************
298 %*                                                                      *
299 \subsection[SrcSpan-predicates]{Predicates}
300 %*                                                                      *
301 %************************************************************************
302
303 \begin{code}
304 -- | Test if a 'SrcSpan' is "good", i.e. has precise location information
305 isGoodSrcSpan :: SrcSpan -> Bool
306 isGoodSrcSpan SrcSpanOneLine{} = True
307 isGoodSrcSpan SrcSpanMultiLine{} = True
308 isGoodSrcSpan SrcSpanPoint{} = True
309 isGoodSrcSpan _ = False
310
311 isOneLineSpan :: SrcSpan -> Bool
312 -- ^ True if the span is known to straddle only one line.
313 -- For "bad" 'SrcSpan', it returns False
314 isOneLineSpan s
315   | isGoodSrcSpan s = srcSpanStartLine s == srcSpanEndLine s
316   | otherwise       = False             
317
318 \end{code}
319
320 %************************************************************************
321 %*                                                                      *
322 \subsection[SrcSpan-unsafe-access-fns]{Unsafe access functions}
323 %*                                                                      *
324 %************************************************************************
325
326 \begin{code}
327
328 -- | Raises an error when used on a "bad" 'SrcSpan'
329 srcSpanStartLine :: SrcSpan -> Int
330 -- | Raises an error when used on a "bad" 'SrcSpan'
331 srcSpanEndLine :: SrcSpan -> Int
332 -- | Raises an error when used on a "bad" 'SrcSpan'
333 srcSpanStartCol :: SrcSpan -> Int
334 -- | Raises an error when used on a "bad" 'SrcSpan'
335 srcSpanEndCol :: SrcSpan -> Int
336
337 srcSpanStartLine SrcSpanOneLine{ srcSpanLine=l } = l
338 srcSpanStartLine SrcSpanMultiLine{ srcSpanSLine=l } = l
339 srcSpanStartLine SrcSpanPoint{ srcSpanLine=l } = l
340 srcSpanStartLine _ = panic "SrcLoc.srcSpanStartLine"
341
342 srcSpanEndLine SrcSpanOneLine{ srcSpanLine=l } = l
343 srcSpanEndLine SrcSpanMultiLine{ srcSpanELine=l } = l
344 srcSpanEndLine SrcSpanPoint{ srcSpanLine=l } = l
345 srcSpanEndLine _ = panic "SrcLoc.srcSpanEndLine"
346
347 srcSpanStartCol SrcSpanOneLine{ srcSpanSCol=l } = l
348 srcSpanStartCol SrcSpanMultiLine{ srcSpanSCol=l } = l
349 srcSpanStartCol SrcSpanPoint{ srcSpanCol=l } = l
350 srcSpanStartCol _ = panic "SrcLoc.srcSpanStartCol"
351
352 srcSpanEndCol SrcSpanOneLine{ srcSpanECol=c } = c
353 srcSpanEndCol SrcSpanMultiLine{ srcSpanECol=c } = c
354 srcSpanEndCol SrcSpanPoint{ srcSpanCol=c } = c
355 srcSpanEndCol _ = panic "SrcLoc.srcSpanEndCol"
356
357 \end{code}
358
359 %************************************************************************
360 %*                                                                      *
361 \subsection[SrcSpan-access-fns]{Access functions}
362 %*                                                                      *
363 %************************************************************************
364
365 \begin{code}
366
367 -- | Returns the location at the start of the 'SrcSpan' or a "bad" 'SrcSpan' if that is unavailable
368 srcSpanStart :: SrcSpan -> SrcLoc
369 -- | Returns the location at the end of the 'SrcSpan' or a "bad" 'SrcSpan' if that is unavailable
370 srcSpanEnd :: SrcSpan -> SrcLoc
371
372 srcSpanStart (UnhelpfulSpan str) = UnhelpfulLoc str
373 srcSpanStart s = mkSrcLoc (srcSpanFile s) 
374                           (srcSpanStartLine s)
375                           (srcSpanStartCol s)
376
377 srcSpanEnd (UnhelpfulSpan str) = UnhelpfulLoc str
378 srcSpanEnd s = 
379   mkSrcLoc (srcSpanFile s) 
380            (srcSpanEndLine s)
381            (srcSpanEndCol s)
382
383 -- | Obtains the filename for a 'SrcSpan' if it is "good"
384 srcSpanFileName_maybe :: SrcSpan -> Maybe FastString
385 srcSpanFileName_maybe (SrcSpanOneLine { srcSpanFile = nm })   = Just nm
386 srcSpanFileName_maybe (SrcSpanMultiLine { srcSpanFile = nm }) = Just nm
387 srcSpanFileName_maybe (SrcSpanPoint { srcSpanFile = nm})      = Just nm
388 srcSpanFileName_maybe _                                       = Nothing
389
390 \end{code}
391
392 %************************************************************************
393 %*                                                                      *
394 \subsection[SrcSpan-instances]{Instances}
395 %*                                                                      *
396 %************************************************************************
397
398 \begin{code}
399
400 -- We want to order SrcSpans first by the start point, then by the end point.
401 instance Ord SrcSpan where
402   a `compare` b = 
403      (srcSpanStart a `compare` srcSpanStart b) `thenCmp` 
404      (srcSpanEnd   a `compare` srcSpanEnd   b)
405
406
407 instance Outputable SrcSpan where
408     ppr span
409       = getPprStyle $ \ sty ->
410         if userStyle sty || debugStyle sty then
411            pprUserSpan True span
412         else
413            hcat [text "{-# LINE ", int (srcSpanStartLine span), space,
414                  char '\"', pprFastFilePath $ srcSpanFile span, text " #-}"]
415
416 pprUserSpan :: Bool -> SrcSpan -> SDoc
417 pprUserSpan show_path (SrcSpanOneLine src_path line start_col end_col)
418   = hcat [ ppWhen show_path (pprFastFilePath src_path <> colon)
419          , int line, char ':', int start_col
420          , ppUnless (end_col - start_col <= 1)
421                     (char '-' <> int (end_col-1)) 
422             -- For single-character or point spans, we just 
423             -- output the starting column number
424          ]
425           
426
427 pprUserSpan show_path (SrcSpanMultiLine src_path sline scol eline ecol)
428   = hcat [ ppWhen show_path (pprFastFilePath src_path <> colon)
429          , parens (int sline <> char ',' <>  int scol)
430          , char '-'
431          , parens (int eline <> char ',' <>  
432                    if ecol == 0 then int ecol else int (ecol-1))
433          ]
434
435 pprUserSpan show_path (SrcSpanPoint src_path line col)
436   = hcat [ ppWhen show_path $ (pprFastFilePath src_path <> colon)
437          , int line, char ':', int col ]
438
439 pprUserSpan _ (UnhelpfulSpan s)  = ftext s
440
441 pprDefnLoc :: SrcSpan -> SDoc
442 -- ^ Pretty prints information about the 'SrcSpan' in the style "defined at ..."
443 pprDefnLoc loc
444   | isGoodSrcSpan loc = ptext (sLit "Defined at") <+> ppr loc
445   | otherwise         = ppr loc
446 \end{code}
447
448 %************************************************************************
449 %*                                                                      *
450 \subsection[Located]{Attaching SrcSpans to things}
451 %*                                                                      *
452 %************************************************************************
453
454 \begin{code}
455 -- | We attach SrcSpans to lots of things, so let's have a datatype for it.
456 data Located e = L SrcSpan e
457   deriving (Eq, Ord, Typeable, Data)
458
459 unLoc :: Located e -> e
460 unLoc (L _ e) = e
461
462 getLoc :: Located e -> SrcSpan
463 getLoc (L l _) = l
464
465 noLoc :: e -> Located e
466 noLoc e = L noSrcSpan e
467
468 mkGeneralLocated :: String -> e -> Located e
469 mkGeneralLocated s e = L (mkGeneralSrcSpan (fsLit s)) e
470
471 combineLocs :: Located a -> Located b -> SrcSpan
472 combineLocs a b = combineSrcSpans (getLoc a) (getLoc b)
473
474 -- | Combine locations from two 'Located' things and add them to a third thing
475 addCLoc :: Located a -> Located b -> c -> Located c
476 addCLoc a b c = L (combineSrcSpans (getLoc a) (getLoc b)) c
477
478 -- not clear whether to add a general Eq instance, but this is useful sometimes:
479
480 -- | Tests whether the two located things are equal
481 eqLocated :: Eq a => Located a -> Located a -> Bool
482 eqLocated a b = unLoc a == unLoc b
483
484 -- not clear whether to add a general Ord instance, but this is useful sometimes:
485
486 -- | Tests the ordering of the two located things
487 cmpLocated :: Ord a => Located a -> Located a -> Ordering
488 cmpLocated a b = unLoc a `compare` unLoc b
489
490 instance Functor Located where
491   fmap f (L l e) = L l (f e)
492
493 instance Outputable e => Outputable (Located e) where
494   ppr (L l e) = ifPprDebug (braces (pprUserSpan False l)) $$ ppr e
495                 -- Print spans without the file name etc
496 \end{code}
497
498 %************************************************************************
499 %*                                                                      *
500 \subsection{Ordering SrcSpans for InteractiveUI}
501 %*                                                                      *
502 %************************************************************************
503
504 \begin{code}
505 -- | Alternative strategies for ordering 'SrcSpan's
506 leftmost_smallest, leftmost_largest, rightmost :: SrcSpan -> SrcSpan -> Ordering
507 rightmost            = flip compare
508 leftmost_smallest    = compare 
509 leftmost_largest a b = (srcSpanStart a `compare` srcSpanStart b)
510                                 `thenCmp`
511                        (srcSpanEnd b `compare` srcSpanEnd a)
512
513
514 -- | Determines whether a span encloses a given line and column index
515 spans :: SrcSpan -> (Int, Int) -> Bool
516 spans span (l,c) = srcSpanStart span <= loc && loc <= srcSpanEnd span
517    where loc = mkSrcLoc (srcSpanFile span) l c
518
519 -- | Determines whether a span is enclosed by another one
520 isSubspanOf :: SrcSpan -- ^ The span that may be enclosed by the other
521             -> SrcSpan -- ^ The span it may be enclosed by
522             -> Bool
523 isSubspanOf src parent 
524     | srcSpanFileName_maybe parent /= srcSpanFileName_maybe src = False
525     | otherwise = srcSpanStart parent <= srcSpanStart src &&
526                   srcSpanEnd parent   >= srcSpanEnd src
527
528 \end{code}