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