{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE PatternSynonyms #-}
module SrcLoc (
RealSrcLoc,
SrcLoc(..),
mkSrcLoc, mkRealSrcLoc, mkGeneralSrcLoc,
noSrcLoc,
generatedSrcLoc,
interactiveSrcLoc,
advanceSrcLoc,
srcLocFile,
srcLocLine,
srcLocCol,
RealSrcSpan,
SrcSpan(..),
mkGeneralSrcSpan, mkSrcSpan, mkRealSrcSpan,
noSrcSpan,
wiredInSrcSpan,
interactiveSrcSpan,
srcLocSpan, realSrcLocSpan,
combineSrcSpans,
srcSpanFirstCharacter,
srcSpanStart, srcSpanEnd,
realSrcSpanStart, realSrcSpanEnd,
srcSpanFileName_maybe,
pprUserRealSpan,
srcSpanFile,
srcSpanStartLine, srcSpanEndLine,
srcSpanStartCol, srcSpanEndCol,
isGoodSrcSpan, isOneLineSpan,
containsSpan,
Located,
RealLocated,
GenLocated(..),
noLoc,
mkGeneralLocated,
getLoc, unLoc,
unRealSrcSpan, getRealSrcSpan,
mapLoc,
eqLocated, cmpLocated, combineLocs, addCLoc,
leftmost_smallest, leftmost_largest, rightmost,
spans, isSubspanOf, sortLocated,
HasSrcSpan(..), SrcSpanLess, dL, cL,
pattern LL, onHasSrcSpan, liftL
) where
import GhcPrelude
import Util
import Json
import Outputable
import FastString
import Control.DeepSeq
import Data.Bits
import Data.Data
import Data.List (sortBy, intercalate)
import Data.Ord
data RealSrcLoc
= SrcLoc FastString
{-# UNPACK #-} !Int
{-# UNPACK #-} !Int
deriving (RealSrcLoc -> RealSrcLoc -> Bool
(RealSrcLoc -> RealSrcLoc -> Bool)
-> (RealSrcLoc -> RealSrcLoc -> Bool) -> Eq RealSrcLoc
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RealSrcLoc -> RealSrcLoc -> Bool
$c/= :: RealSrcLoc -> RealSrcLoc -> Bool
== :: RealSrcLoc -> RealSrcLoc -> Bool
$c== :: RealSrcLoc -> RealSrcLoc -> Bool
Eq, Eq RealSrcLoc
Eq RealSrcLoc
-> (RealSrcLoc -> RealSrcLoc -> Ordering)
-> (RealSrcLoc -> RealSrcLoc -> Bool)
-> (RealSrcLoc -> RealSrcLoc -> Bool)
-> (RealSrcLoc -> RealSrcLoc -> Bool)
-> (RealSrcLoc -> RealSrcLoc -> Bool)
-> (RealSrcLoc -> RealSrcLoc -> RealSrcLoc)
-> (RealSrcLoc -> RealSrcLoc -> RealSrcLoc)
-> Ord RealSrcLoc
RealSrcLoc -> RealSrcLoc -> Bool
RealSrcLoc -> RealSrcLoc -> Ordering
RealSrcLoc -> RealSrcLoc -> RealSrcLoc
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RealSrcLoc -> RealSrcLoc -> RealSrcLoc
$cmin :: RealSrcLoc -> RealSrcLoc -> RealSrcLoc
max :: RealSrcLoc -> RealSrcLoc -> RealSrcLoc
$cmax :: RealSrcLoc -> RealSrcLoc -> RealSrcLoc
>= :: RealSrcLoc -> RealSrcLoc -> Bool
$c>= :: RealSrcLoc -> RealSrcLoc -> Bool
> :: RealSrcLoc -> RealSrcLoc -> Bool
$c> :: RealSrcLoc -> RealSrcLoc -> Bool
<= :: RealSrcLoc -> RealSrcLoc -> Bool
$c<= :: RealSrcLoc -> RealSrcLoc -> Bool
< :: RealSrcLoc -> RealSrcLoc -> Bool
$c< :: RealSrcLoc -> RealSrcLoc -> Bool
compare :: RealSrcLoc -> RealSrcLoc -> Ordering
$ccompare :: RealSrcLoc -> RealSrcLoc -> Ordering
$cp1Ord :: Eq RealSrcLoc
Ord)
data SrcLoc
= RealSrcLoc {-# UNPACK #-}!RealSrcLoc
| UnhelpfulLoc FastString
deriving (SrcLoc -> SrcLoc -> Bool
(SrcLoc -> SrcLoc -> Bool)
-> (SrcLoc -> SrcLoc -> Bool) -> Eq SrcLoc
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SrcLoc -> SrcLoc -> Bool
$c/= :: SrcLoc -> SrcLoc -> Bool
== :: SrcLoc -> SrcLoc -> Bool
$c== :: SrcLoc -> SrcLoc -> Bool
Eq, Eq SrcLoc
Eq SrcLoc
-> (SrcLoc -> SrcLoc -> Ordering)
-> (SrcLoc -> SrcLoc -> Bool)
-> (SrcLoc -> SrcLoc -> Bool)
-> (SrcLoc -> SrcLoc -> Bool)
-> (SrcLoc -> SrcLoc -> Bool)
-> (SrcLoc -> SrcLoc -> SrcLoc)
-> (SrcLoc -> SrcLoc -> SrcLoc)
-> Ord SrcLoc
SrcLoc -> SrcLoc -> Bool
SrcLoc -> SrcLoc -> Ordering
SrcLoc -> SrcLoc -> SrcLoc
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SrcLoc -> SrcLoc -> SrcLoc
$cmin :: SrcLoc -> SrcLoc -> SrcLoc
max :: SrcLoc -> SrcLoc -> SrcLoc
$cmax :: SrcLoc -> SrcLoc -> SrcLoc
>= :: SrcLoc -> SrcLoc -> Bool
$c>= :: SrcLoc -> SrcLoc -> Bool
> :: SrcLoc -> SrcLoc -> Bool
$c> :: SrcLoc -> SrcLoc -> Bool
<= :: SrcLoc -> SrcLoc -> Bool
$c<= :: SrcLoc -> SrcLoc -> Bool
< :: SrcLoc -> SrcLoc -> Bool
$c< :: SrcLoc -> SrcLoc -> Bool
compare :: SrcLoc -> SrcLoc -> Ordering
$ccompare :: SrcLoc -> SrcLoc -> Ordering
$cp1Ord :: Eq SrcLoc
Ord, Int -> SrcLoc -> ShowS
[SrcLoc] -> ShowS
SrcLoc -> String
(Int -> SrcLoc -> ShowS)
-> (SrcLoc -> String) -> ([SrcLoc] -> ShowS) -> Show SrcLoc
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SrcLoc] -> ShowS
$cshowList :: [SrcLoc] -> ShowS
show :: SrcLoc -> String
$cshow :: SrcLoc -> String
showsPrec :: Int -> SrcLoc -> ShowS
$cshowsPrec :: Int -> SrcLoc -> ShowS
Show)
mkSrcLoc :: FastString -> Int -> Int -> SrcLoc
mkSrcLoc :: FastString -> Int -> Int -> SrcLoc
mkSrcLoc FastString
x Int
line Int
col = RealSrcLoc -> SrcLoc
RealSrcLoc (FastString -> Int -> Int -> RealSrcLoc
mkRealSrcLoc FastString
x Int
line Int
col)
mkRealSrcLoc :: FastString -> Int -> Int -> RealSrcLoc
mkRealSrcLoc :: FastString -> Int -> Int -> RealSrcLoc
mkRealSrcLoc FastString
x Int
line Int
col = FastString -> Int -> Int -> RealSrcLoc
SrcLoc FastString
x Int
line Int
col
noSrcLoc, generatedSrcLoc, interactiveSrcLoc :: SrcLoc
noSrcLoc :: SrcLoc
noSrcLoc = FastString -> SrcLoc
UnhelpfulLoc (String -> FastString
fsLit String
"<no location info>")
generatedSrcLoc :: SrcLoc
generatedSrcLoc = FastString -> SrcLoc
UnhelpfulLoc (String -> FastString
fsLit String
"<compiler-generated code>")
interactiveSrcLoc :: SrcLoc
interactiveSrcLoc = FastString -> SrcLoc
UnhelpfulLoc (String -> FastString
fsLit String
"<interactive>")
mkGeneralSrcLoc :: FastString -> SrcLoc
mkGeneralSrcLoc :: FastString -> SrcLoc
mkGeneralSrcLoc = FastString -> SrcLoc
UnhelpfulLoc
srcLocFile :: RealSrcLoc -> FastString
srcLocFile :: RealSrcLoc -> FastString
srcLocFile (SrcLoc FastString
fname Int
_ Int
_) = FastString
fname
srcLocLine :: RealSrcLoc -> Int
srcLocLine :: RealSrcLoc -> Int
srcLocLine (SrcLoc FastString
_ Int
l Int
_) = Int
l
srcLocCol :: RealSrcLoc -> Int
srcLocCol :: RealSrcLoc -> Int
srcLocCol (SrcLoc FastString
_ Int
_ Int
c) = Int
c
advanceSrcLoc :: RealSrcLoc -> Char -> RealSrcLoc
advanceSrcLoc :: RealSrcLoc -> Char -> RealSrcLoc
advanceSrcLoc (SrcLoc FastString
f Int
l Int
_) Char
'\n' = FastString -> Int -> Int -> RealSrcLoc
SrcLoc FastString
f (Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Int
1
advanceSrcLoc (SrcLoc FastString
f Int
l Int
c) Char
'\t' = FastString -> Int -> Int -> RealSrcLoc
SrcLoc FastString
f Int
l (((((Int
c Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftR` Int
3) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftL` Int
3) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
advanceSrcLoc (SrcLoc FastString
f Int
l Int
c) Char
_ = FastString -> Int -> Int -> RealSrcLoc
SrcLoc FastString
f Int
l (Int
c Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
sortLocated :: HasSrcSpan a => [a] -> [a]
sortLocated :: [a] -> [a]
sortLocated [a]
things = (a -> a -> Ordering) -> [a] -> [a]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy ((a -> SrcSpan) -> a -> a -> Ordering
forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing a -> SrcSpan
forall a. HasSrcSpan a => a -> SrcSpan
getLoc) [a]
things
instance Outputable RealSrcLoc where
ppr :: RealSrcLoc -> SDoc
ppr (SrcLoc FastString
src_path Int
src_line Int
src_col)
= [SDoc] -> SDoc
hcat [ FastString -> SDoc
pprFastFilePath FastString
src_path SDoc -> SDoc -> SDoc
<> SDoc
colon
, Int -> SDoc
int Int
src_line SDoc -> SDoc -> SDoc
<> SDoc
colon
, Int -> SDoc
int Int
src_col ]
instance Outputable SrcLoc where
ppr :: SrcLoc -> SDoc
ppr (RealSrcLoc RealSrcLoc
l) = RealSrcLoc -> SDoc
forall a. Outputable a => a -> SDoc
ppr RealSrcLoc
l
ppr (UnhelpfulLoc FastString
s) = FastString -> SDoc
ftext FastString
s
instance Data RealSrcSpan where
toConstr :: RealSrcSpan -> Constr
toConstr RealSrcSpan
_ = String -> Constr
abstractConstr String
"RealSrcSpan"
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RealSrcSpan
gunfold forall b r. Data b => c (b -> r) -> c r
_ forall r. r -> c r
_ = String -> Constr -> c RealSrcSpan
forall a. HasCallStack => String -> a
error String
"gunfold"
dataTypeOf :: RealSrcSpan -> DataType
dataTypeOf RealSrcSpan
_ = String -> DataType
mkNoRepType String
"RealSrcSpan"
instance Data SrcSpan where
toConstr :: SrcSpan -> Constr
toConstr SrcSpan
_ = String -> Constr
abstractConstr String
"SrcSpan"
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SrcSpan
gunfold forall b r. Data b => c (b -> r) -> c r
_ forall r. r -> c r
_ = String -> Constr -> c SrcSpan
forall a. HasCallStack => String -> a
error String
"gunfold"
dataTypeOf :: SrcSpan -> DataType
dataTypeOf SrcSpan
_ = String -> DataType
mkNoRepType String
"SrcSpan"
data RealSrcSpan
= RealSrcSpan'
{ RealSrcSpan -> FastString
srcSpanFile :: !FastString,
RealSrcSpan -> Int
srcSpanSLine :: {-# UNPACK #-} !Int,
RealSrcSpan -> Int
srcSpanSCol :: {-# UNPACK #-} !Int,
RealSrcSpan -> Int
srcSpanELine :: {-# UNPACK #-} !Int,
RealSrcSpan -> Int
srcSpanECol :: {-# UNPACK #-} !Int
}
deriving RealSrcSpan -> RealSrcSpan -> Bool
(RealSrcSpan -> RealSrcSpan -> Bool)
-> (RealSrcSpan -> RealSrcSpan -> Bool) -> Eq RealSrcSpan
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RealSrcSpan -> RealSrcSpan -> Bool
$c/= :: RealSrcSpan -> RealSrcSpan -> Bool
== :: RealSrcSpan -> RealSrcSpan -> Bool
$c== :: RealSrcSpan -> RealSrcSpan -> Bool
Eq
data SrcSpan =
RealSrcSpan !RealSrcSpan
| UnhelpfulSpan !FastString
deriving (SrcSpan -> SrcSpan -> Bool
(SrcSpan -> SrcSpan -> Bool)
-> (SrcSpan -> SrcSpan -> Bool) -> Eq SrcSpan
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SrcSpan -> SrcSpan -> Bool
$c/= :: SrcSpan -> SrcSpan -> Bool
== :: SrcSpan -> SrcSpan -> Bool
$c== :: SrcSpan -> SrcSpan -> Bool
Eq, Eq SrcSpan
Eq SrcSpan
-> (SrcSpan -> SrcSpan -> Ordering)
-> (SrcSpan -> SrcSpan -> Bool)
-> (SrcSpan -> SrcSpan -> Bool)
-> (SrcSpan -> SrcSpan -> Bool)
-> (SrcSpan -> SrcSpan -> Bool)
-> (SrcSpan -> SrcSpan -> SrcSpan)
-> (SrcSpan -> SrcSpan -> SrcSpan)
-> Ord SrcSpan
SrcSpan -> SrcSpan -> Bool
SrcSpan -> SrcSpan -> Ordering
SrcSpan -> SrcSpan -> SrcSpan
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SrcSpan -> SrcSpan -> SrcSpan
$cmin :: SrcSpan -> SrcSpan -> SrcSpan
max :: SrcSpan -> SrcSpan -> SrcSpan
$cmax :: SrcSpan -> SrcSpan -> SrcSpan
>= :: SrcSpan -> SrcSpan -> Bool
$c>= :: SrcSpan -> SrcSpan -> Bool
> :: SrcSpan -> SrcSpan -> Bool
$c> :: SrcSpan -> SrcSpan -> Bool
<= :: SrcSpan -> SrcSpan -> Bool
$c<= :: SrcSpan -> SrcSpan -> Bool
< :: SrcSpan -> SrcSpan -> Bool
$c< :: SrcSpan -> SrcSpan -> Bool
compare :: SrcSpan -> SrcSpan -> Ordering
$ccompare :: SrcSpan -> SrcSpan -> Ordering
$cp1Ord :: Eq SrcSpan
Ord, Int -> SrcSpan -> ShowS
[SrcSpan] -> ShowS
SrcSpan -> String
(Int -> SrcSpan -> ShowS)
-> (SrcSpan -> String) -> ([SrcSpan] -> ShowS) -> Show SrcSpan
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SrcSpan] -> ShowS
$cshowList :: [SrcSpan] -> ShowS
show :: SrcSpan -> String
$cshow :: SrcSpan -> String
showsPrec :: Int -> SrcSpan -> ShowS
$cshowsPrec :: Int -> SrcSpan -> ShowS
Show)
instance ToJson SrcSpan where
json :: SrcSpan -> JsonDoc
json (UnhelpfulSpan {} ) = JsonDoc
JSNull
json (RealSrcSpan RealSrcSpan
rss) = RealSrcSpan -> JsonDoc
forall a. ToJson a => a -> JsonDoc
json RealSrcSpan
rss
instance ToJson RealSrcSpan where
json :: RealSrcSpan -> JsonDoc
json (RealSrcSpan'{Int
FastString
srcSpanECol :: Int
srcSpanELine :: Int
srcSpanSCol :: Int
srcSpanSLine :: Int
srcSpanFile :: FastString
srcSpanECol :: RealSrcSpan -> Int
srcSpanELine :: RealSrcSpan -> Int
srcSpanSCol :: RealSrcSpan -> Int
srcSpanSLine :: RealSrcSpan -> Int
srcSpanFile :: RealSrcSpan -> FastString
..}) = [(String, JsonDoc)] -> JsonDoc
JSObject [ (String
"file", String -> JsonDoc
JSString (FastString -> String
unpackFS FastString
srcSpanFile))
, (String
"startLine", Int -> JsonDoc
JSInt Int
srcSpanSLine)
, (String
"startCol", Int -> JsonDoc
JSInt Int
srcSpanSCol)
, (String
"endLine", Int -> JsonDoc
JSInt Int
srcSpanELine)
, (String
"endCol", Int -> JsonDoc
JSInt Int
srcSpanECol)
]
instance NFData SrcSpan where
rnf :: SrcSpan -> ()
rnf SrcSpan
x = SrcSpan
x SrcSpan -> () -> ()
`seq` ()
noSrcSpan, wiredInSrcSpan, interactiveSrcSpan :: SrcSpan
noSrcSpan :: SrcSpan
noSrcSpan = FastString -> SrcSpan
UnhelpfulSpan (String -> FastString
fsLit String
"<no location info>")
wiredInSrcSpan :: SrcSpan
wiredInSrcSpan = FastString -> SrcSpan
UnhelpfulSpan (String -> FastString
fsLit String
"<wired into compiler>")
interactiveSrcSpan :: SrcSpan
interactiveSrcSpan = FastString -> SrcSpan
UnhelpfulSpan (String -> FastString
fsLit String
"<interactive>")
mkGeneralSrcSpan :: FastString -> SrcSpan
mkGeneralSrcSpan :: FastString -> SrcSpan
mkGeneralSrcSpan = FastString -> SrcSpan
UnhelpfulSpan
srcLocSpan :: SrcLoc -> SrcSpan
srcLocSpan :: SrcLoc -> SrcSpan
srcLocSpan (UnhelpfulLoc FastString
str) = FastString -> SrcSpan
UnhelpfulSpan FastString
str
srcLocSpan (RealSrcLoc RealSrcLoc
l) = RealSrcSpan -> SrcSpan
RealSrcSpan (RealSrcLoc -> RealSrcSpan
realSrcLocSpan RealSrcLoc
l)
realSrcLocSpan :: RealSrcLoc -> RealSrcSpan
realSrcLocSpan :: RealSrcLoc -> RealSrcSpan
realSrcLocSpan (SrcLoc FastString
file Int
line Int
col) = FastString -> Int -> Int -> Int -> Int -> RealSrcSpan
RealSrcSpan' FastString
file Int
line Int
col Int
line Int
col
mkRealSrcSpan :: RealSrcLoc -> RealSrcLoc -> RealSrcSpan
mkRealSrcSpan :: RealSrcLoc -> RealSrcLoc -> RealSrcSpan
mkRealSrcSpan RealSrcLoc
loc1 RealSrcLoc
loc2 = FastString -> Int -> Int -> Int -> Int -> RealSrcSpan
RealSrcSpan' FastString
file Int
line1 Int
col1 Int
line2 Int
col2
where
line1 :: Int
line1 = RealSrcLoc -> Int
srcLocLine RealSrcLoc
loc1
line2 :: Int
line2 = RealSrcLoc -> Int
srcLocLine RealSrcLoc
loc2
col1 :: Int
col1 = RealSrcLoc -> Int
srcLocCol RealSrcLoc
loc1
col2 :: Int
col2 = RealSrcLoc -> Int
srcLocCol RealSrcLoc
loc2
file :: FastString
file = RealSrcLoc -> FastString
srcLocFile RealSrcLoc
loc1
isOneLineRealSpan :: RealSrcSpan -> Bool
isOneLineRealSpan :: RealSrcSpan -> Bool
isOneLineRealSpan (RealSrcSpan' FastString
_ Int
line1 Int
_ Int
line2 Int
_)
= Int
line1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
line2
isPointRealSpan :: RealSrcSpan -> Bool
isPointRealSpan :: RealSrcSpan -> Bool
isPointRealSpan (RealSrcSpan' FastString
_ Int
line1 Int
col1 Int
line2 Int
col2)
= Int
line1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
line2 Bool -> Bool -> Bool
&& Int
col1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
col2
mkSrcSpan :: SrcLoc -> SrcLoc -> SrcSpan
mkSrcSpan :: SrcLoc -> SrcLoc -> SrcSpan
mkSrcSpan (UnhelpfulLoc FastString
str) SrcLoc
_ = FastString -> SrcSpan
UnhelpfulSpan FastString
str
mkSrcSpan SrcLoc
_ (UnhelpfulLoc FastString
str) = FastString -> SrcSpan
UnhelpfulSpan FastString
str
mkSrcSpan (RealSrcLoc RealSrcLoc
loc1) (RealSrcLoc RealSrcLoc
loc2)
= RealSrcSpan -> SrcSpan
RealSrcSpan (RealSrcLoc -> RealSrcLoc -> RealSrcSpan
mkRealSrcSpan RealSrcLoc
loc1 RealSrcLoc
loc2)
combineSrcSpans :: SrcSpan -> SrcSpan -> SrcSpan
combineSrcSpans :: SrcSpan -> SrcSpan -> SrcSpan
combineSrcSpans (UnhelpfulSpan FastString
_) SrcSpan
r = SrcSpan
r
combineSrcSpans SrcSpan
l (UnhelpfulSpan FastString
_) = SrcSpan
l
combineSrcSpans (RealSrcSpan RealSrcSpan
span1) (RealSrcSpan RealSrcSpan
span2)
| RealSrcSpan -> FastString
srcSpanFile RealSrcSpan
span1 FastString -> FastString -> Bool
forall a. Eq a => a -> a -> Bool
== RealSrcSpan -> FastString
srcSpanFile RealSrcSpan
span2
= RealSrcSpan -> SrcSpan
RealSrcSpan (RealSrcSpan -> RealSrcSpan -> RealSrcSpan
combineRealSrcSpans RealSrcSpan
span1 RealSrcSpan
span2)
| Bool
otherwise = FastString -> SrcSpan
UnhelpfulSpan (String -> FastString
fsLit String
"<combineSrcSpans: files differ>")
combineRealSrcSpans :: RealSrcSpan -> RealSrcSpan -> RealSrcSpan
combineRealSrcSpans :: RealSrcSpan -> RealSrcSpan -> RealSrcSpan
combineRealSrcSpans RealSrcSpan
span1 RealSrcSpan
span2
= FastString -> Int -> Int -> Int -> Int -> RealSrcSpan
RealSrcSpan' FastString
file Int
line_start Int
col_start Int
line_end Int
col_end
where
(Int
line_start, Int
col_start) = (Int, Int) -> (Int, Int) -> (Int, Int)
forall a. Ord a => a -> a -> a
min (RealSrcSpan -> Int
srcSpanStartLine RealSrcSpan
span1, RealSrcSpan -> Int
srcSpanStartCol RealSrcSpan
span1)
(RealSrcSpan -> Int
srcSpanStartLine RealSrcSpan
span2, RealSrcSpan -> Int
srcSpanStartCol RealSrcSpan
span2)
(Int
line_end, Int
col_end) = (Int, Int) -> (Int, Int) -> (Int, Int)
forall a. Ord a => a -> a -> a
max (RealSrcSpan -> Int
srcSpanEndLine RealSrcSpan
span1, RealSrcSpan -> Int
srcSpanEndCol RealSrcSpan
span1)
(RealSrcSpan -> Int
srcSpanEndLine RealSrcSpan
span2, RealSrcSpan -> Int
srcSpanEndCol RealSrcSpan
span2)
file :: FastString
file = RealSrcSpan -> FastString
srcSpanFile RealSrcSpan
span1
srcSpanFirstCharacter :: SrcSpan -> SrcSpan
srcSpanFirstCharacter :: SrcSpan -> SrcSpan
srcSpanFirstCharacter l :: SrcSpan
l@(UnhelpfulSpan {}) = SrcSpan
l
srcSpanFirstCharacter (RealSrcSpan RealSrcSpan
span) = RealSrcSpan -> SrcSpan
RealSrcSpan (RealSrcSpan -> SrcSpan) -> RealSrcSpan -> SrcSpan
forall a b. (a -> b) -> a -> b
$ RealSrcLoc -> RealSrcLoc -> RealSrcSpan
mkRealSrcSpan RealSrcLoc
loc1 RealSrcLoc
loc2
where
loc1 :: RealSrcLoc
loc1@(SrcLoc FastString
f Int
l Int
c) = RealSrcSpan -> RealSrcLoc
realSrcSpanStart RealSrcSpan
span
loc2 :: RealSrcLoc
loc2 = FastString -> Int -> Int -> RealSrcLoc
SrcLoc FastString
f Int
l (Int
cInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
isGoodSrcSpan :: SrcSpan -> Bool
isGoodSrcSpan :: SrcSpan -> Bool
isGoodSrcSpan (RealSrcSpan RealSrcSpan
_) = Bool
True
isGoodSrcSpan (UnhelpfulSpan FastString
_) = Bool
False
isOneLineSpan :: SrcSpan -> Bool
isOneLineSpan :: SrcSpan -> Bool
isOneLineSpan (RealSrcSpan RealSrcSpan
s) = RealSrcSpan -> Int
srcSpanStartLine RealSrcSpan
s Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== RealSrcSpan -> Int
srcSpanEndLine RealSrcSpan
s
isOneLineSpan (UnhelpfulSpan FastString
_) = Bool
False
containsSpan :: RealSrcSpan -> RealSrcSpan -> Bool
containsSpan :: RealSrcSpan -> RealSrcSpan -> Bool
containsSpan RealSrcSpan
s1 RealSrcSpan
s2
= (RealSrcSpan -> Int
srcSpanStartLine RealSrcSpan
s1, RealSrcSpan -> Int
srcSpanStartCol RealSrcSpan
s1)
(Int, Int) -> (Int, Int) -> Bool
forall a. Ord a => a -> a -> Bool
<= (RealSrcSpan -> Int
srcSpanStartLine RealSrcSpan
s2, RealSrcSpan -> Int
srcSpanStartCol RealSrcSpan
s2)
Bool -> Bool -> Bool
&& (RealSrcSpan -> Int
srcSpanEndLine RealSrcSpan
s1, RealSrcSpan -> Int
srcSpanEndCol RealSrcSpan
s1)
(Int, Int) -> (Int, Int) -> Bool
forall a. Ord a => a -> a -> Bool
>= (RealSrcSpan -> Int
srcSpanEndLine RealSrcSpan
s2, RealSrcSpan -> Int
srcSpanEndCol RealSrcSpan
s2)
Bool -> Bool -> Bool
&& (RealSrcSpan -> FastString
srcSpanFile RealSrcSpan
s1 FastString -> FastString -> Bool
forall a. Eq a => a -> a -> Bool
== RealSrcSpan -> FastString
srcSpanFile RealSrcSpan
s2)
srcSpanStartLine :: RealSrcSpan -> Int
srcSpanEndLine :: RealSrcSpan -> Int
srcSpanStartCol :: RealSrcSpan -> Int
srcSpanEndCol :: RealSrcSpan -> Int
srcSpanStartLine :: RealSrcSpan -> Int
srcSpanStartLine RealSrcSpan'{ srcSpanSLine :: RealSrcSpan -> Int
srcSpanSLine=Int
l } = Int
l
srcSpanEndLine :: RealSrcSpan -> Int
srcSpanEndLine RealSrcSpan'{ srcSpanELine :: RealSrcSpan -> Int
srcSpanELine=Int
l } = Int
l
srcSpanStartCol :: RealSrcSpan -> Int
srcSpanStartCol RealSrcSpan'{ srcSpanSCol :: RealSrcSpan -> Int
srcSpanSCol=Int
l } = Int
l
srcSpanEndCol :: RealSrcSpan -> Int
srcSpanEndCol RealSrcSpan'{ srcSpanECol :: RealSrcSpan -> Int
srcSpanECol=Int
c } = Int
c
srcSpanStart :: SrcSpan -> SrcLoc
srcSpanStart :: SrcSpan -> SrcLoc
srcSpanStart (UnhelpfulSpan FastString
str) = FastString -> SrcLoc
UnhelpfulLoc FastString
str
srcSpanStart (RealSrcSpan RealSrcSpan
s) = RealSrcLoc -> SrcLoc
RealSrcLoc (RealSrcSpan -> RealSrcLoc
realSrcSpanStart RealSrcSpan
s)
srcSpanEnd :: SrcSpan -> SrcLoc
srcSpanEnd :: SrcSpan -> SrcLoc
srcSpanEnd (UnhelpfulSpan FastString
str) = FastString -> SrcLoc
UnhelpfulLoc FastString
str
srcSpanEnd (RealSrcSpan RealSrcSpan
s) = RealSrcLoc -> SrcLoc
RealSrcLoc (RealSrcSpan -> RealSrcLoc
realSrcSpanEnd RealSrcSpan
s)
realSrcSpanStart :: RealSrcSpan -> RealSrcLoc
realSrcSpanStart :: RealSrcSpan -> RealSrcLoc
realSrcSpanStart RealSrcSpan
s = FastString -> Int -> Int -> RealSrcLoc
mkRealSrcLoc (RealSrcSpan -> FastString
srcSpanFile RealSrcSpan
s)
(RealSrcSpan -> Int
srcSpanStartLine RealSrcSpan
s)
(RealSrcSpan -> Int
srcSpanStartCol RealSrcSpan
s)
realSrcSpanEnd :: RealSrcSpan -> RealSrcLoc
realSrcSpanEnd :: RealSrcSpan -> RealSrcLoc
realSrcSpanEnd RealSrcSpan
s = FastString -> Int -> Int -> RealSrcLoc
mkRealSrcLoc (RealSrcSpan -> FastString
srcSpanFile RealSrcSpan
s)
(RealSrcSpan -> Int
srcSpanEndLine RealSrcSpan
s)
(RealSrcSpan -> Int
srcSpanEndCol RealSrcSpan
s)
srcSpanFileName_maybe :: SrcSpan -> Maybe FastString
srcSpanFileName_maybe :: SrcSpan -> Maybe FastString
srcSpanFileName_maybe (RealSrcSpan RealSrcSpan
s) = FastString -> Maybe FastString
forall a. a -> Maybe a
Just (RealSrcSpan -> FastString
srcSpanFile RealSrcSpan
s)
srcSpanFileName_maybe (UnhelpfulSpan FastString
_) = Maybe FastString
forall a. Maybe a
Nothing
instance Ord RealSrcSpan where
RealSrcSpan
a compare :: RealSrcSpan -> RealSrcSpan -> Ordering
`compare` RealSrcSpan
b =
(RealSrcSpan -> RealSrcLoc
realSrcSpanStart RealSrcSpan
a RealSrcLoc -> RealSrcLoc -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` RealSrcSpan -> RealSrcLoc
realSrcSpanStart RealSrcSpan
b) Ordering -> Ordering -> Ordering
`thenCmp`
(RealSrcSpan -> RealSrcLoc
realSrcSpanEnd RealSrcSpan
a RealSrcLoc -> RealSrcLoc -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` RealSrcSpan -> RealSrcLoc
realSrcSpanEnd RealSrcSpan
b)
instance Show RealSrcLoc where
show :: RealSrcLoc -> String
show (SrcLoc FastString
filename Int
row Int
col)
= String
"SrcLoc " String -> ShowS
forall a. [a] -> [a] -> [a]
++ FastString -> String
forall a. Show a => a -> String
show FastString
filename String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
row String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
col
instance Show RealSrcSpan where
show :: RealSrcSpan -> String
show span :: RealSrcSpan
span@(RealSrcSpan' FastString
file Int
sl Int
sc Int
el Int
ec)
| RealSrcSpan -> Bool
isPointRealSpan RealSrcSpan
span
= String
"SrcSpanPoint " String -> ShowS
forall a. [a] -> [a] -> [a]
++ FastString -> String
forall a. Show a => a -> String
show FastString
file String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
" " ((Int -> String) -> [Int] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Int -> String
forall a. Show a => a -> String
show [Int
sl,Int
sc])
| RealSrcSpan -> Bool
isOneLineRealSpan RealSrcSpan
span
= String
"SrcSpanOneLine " String -> ShowS
forall a. [a] -> [a] -> [a]
++ FastString -> String
forall a. Show a => a -> String
show FastString
file String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
" " ((Int -> String) -> [Int] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Int -> String
forall a. Show a => a -> String
show [Int
sl,Int
sc,Int
ec])
| Bool
otherwise
= String
"SrcSpanMultiLine " String -> ShowS
forall a. [a] -> [a] -> [a]
++ FastString -> String
forall a. Show a => a -> String
show FastString
file String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
" " ((Int -> String) -> [Int] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Int -> String
forall a. Show a => a -> String
show [Int
sl,Int
sc,Int
el,Int
ec])
instance Outputable RealSrcSpan where
ppr :: RealSrcSpan -> SDoc
ppr RealSrcSpan
span = Bool -> RealSrcSpan -> SDoc
pprUserRealSpan Bool
True RealSrcSpan
span
instance Outputable SrcSpan where
ppr :: SrcSpan -> SDoc
ppr SrcSpan
span = Bool -> SrcSpan -> SDoc
pprUserSpan Bool
True SrcSpan
span
pprUserSpan :: Bool -> SrcSpan -> SDoc
pprUserSpan :: Bool -> SrcSpan -> SDoc
pprUserSpan Bool
_ (UnhelpfulSpan FastString
s) = FastString -> SDoc
ftext FastString
s
pprUserSpan Bool
show_path (RealSrcSpan RealSrcSpan
s) = Bool -> RealSrcSpan -> SDoc
pprUserRealSpan Bool
show_path RealSrcSpan
s
pprUserRealSpan :: Bool -> RealSrcSpan -> SDoc
pprUserRealSpan :: Bool -> RealSrcSpan -> SDoc
pprUserRealSpan Bool
show_path span :: RealSrcSpan
span@(RealSrcSpan' FastString
src_path Int
line Int
col Int
_ Int
_)
| RealSrcSpan -> Bool
isPointRealSpan RealSrcSpan
span
= [SDoc] -> SDoc
hcat [ Bool -> SDoc -> SDoc
ppWhen Bool
show_path (FastString -> SDoc
pprFastFilePath FastString
src_path SDoc -> SDoc -> SDoc
<> SDoc
colon)
, Int -> SDoc
int Int
line SDoc -> SDoc -> SDoc
<> SDoc
colon
, Int -> SDoc
int Int
col ]
pprUserRealSpan Bool
show_path span :: RealSrcSpan
span@(RealSrcSpan' FastString
src_path Int
line Int
scol Int
_ Int
ecol)
| RealSrcSpan -> Bool
isOneLineRealSpan RealSrcSpan
span
= [SDoc] -> SDoc
hcat [ Bool -> SDoc -> SDoc
ppWhen Bool
show_path (FastString -> SDoc
pprFastFilePath FastString
src_path SDoc -> SDoc -> SDoc
<> SDoc
colon)
, Int -> SDoc
int Int
line SDoc -> SDoc -> SDoc
<> SDoc
colon
, Int -> SDoc
int Int
scol
, Bool -> SDoc -> SDoc
ppUnless (Int
ecol Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
scol Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
1) (Char -> SDoc
char Char
'-' SDoc -> SDoc -> SDoc
<> Int -> SDoc
int (Int
ecol Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)) ]
pprUserRealSpan Bool
show_path (RealSrcSpan' FastString
src_path Int
sline Int
scol Int
eline Int
ecol)
= [SDoc] -> SDoc
hcat [ Bool -> SDoc -> SDoc
ppWhen Bool
show_path (FastString -> SDoc
pprFastFilePath FastString
src_path SDoc -> SDoc -> SDoc
<> SDoc
colon)
, SDoc -> SDoc
parens (Int -> SDoc
int Int
sline SDoc -> SDoc -> SDoc
<> SDoc
comma SDoc -> SDoc -> SDoc
<> Int -> SDoc
int Int
scol)
, Char -> SDoc
char Char
'-'
, SDoc -> SDoc
parens (Int -> SDoc
int Int
eline SDoc -> SDoc -> SDoc
<> SDoc
comma SDoc -> SDoc -> SDoc
<> Int -> SDoc
int Int
ecol') ]
where
ecol' :: Int
ecol' = if Int
ecol Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 then Int
ecol else Int
ecol Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1
data GenLocated l e = L l e
deriving (GenLocated l e -> GenLocated l e -> Bool
(GenLocated l e -> GenLocated l e -> Bool)
-> (GenLocated l e -> GenLocated l e -> Bool)
-> Eq (GenLocated l e)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall l e.
(Eq l, Eq e) =>
GenLocated l e -> GenLocated l e -> Bool
/= :: GenLocated l e -> GenLocated l e -> Bool
$c/= :: forall l e.
(Eq l, Eq e) =>
GenLocated l e -> GenLocated l e -> Bool
== :: GenLocated l e -> GenLocated l e -> Bool
$c== :: forall l e.
(Eq l, Eq e) =>
GenLocated l e -> GenLocated l e -> Bool
Eq, Eq (GenLocated l e)
Eq (GenLocated l e)
-> (GenLocated l e -> GenLocated l e -> Ordering)
-> (GenLocated l e -> GenLocated l e -> Bool)
-> (GenLocated l e -> GenLocated l e -> Bool)
-> (GenLocated l e -> GenLocated l e -> Bool)
-> (GenLocated l e -> GenLocated l e -> Bool)
-> (GenLocated l e -> GenLocated l e -> GenLocated l e)
-> (GenLocated l e -> GenLocated l e -> GenLocated l e)
-> Ord (GenLocated l e)
GenLocated l e -> GenLocated l e -> Bool
GenLocated l e -> GenLocated l e -> Ordering
GenLocated l e -> GenLocated l e -> GenLocated l e
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall l e. (Ord l, Ord e) => Eq (GenLocated l e)
forall l e.
(Ord l, Ord e) =>
GenLocated l e -> GenLocated l e -> Bool
forall l e.
(Ord l, Ord e) =>
GenLocated l e -> GenLocated l e -> Ordering
forall l e.
(Ord l, Ord e) =>
GenLocated l e -> GenLocated l e -> GenLocated l e
min :: GenLocated l e -> GenLocated l e -> GenLocated l e
$cmin :: forall l e.
(Ord l, Ord e) =>
GenLocated l e -> GenLocated l e -> GenLocated l e
max :: GenLocated l e -> GenLocated l e -> GenLocated l e
$cmax :: forall l e.
(Ord l, Ord e) =>
GenLocated l e -> GenLocated l e -> GenLocated l e
>= :: GenLocated l e -> GenLocated l e -> Bool
$c>= :: forall l e.
(Ord l, Ord e) =>
GenLocated l e -> GenLocated l e -> Bool
> :: GenLocated l e -> GenLocated l e -> Bool
$c> :: forall l e.
(Ord l, Ord e) =>
GenLocated l e -> GenLocated l e -> Bool
<= :: GenLocated l e -> GenLocated l e -> Bool
$c<= :: forall l e.
(Ord l, Ord e) =>
GenLocated l e -> GenLocated l e -> Bool
< :: GenLocated l e -> GenLocated l e -> Bool
$c< :: forall l e.
(Ord l, Ord e) =>
GenLocated l e -> GenLocated l e -> Bool
compare :: GenLocated l e -> GenLocated l e -> Ordering
$ccompare :: forall l e.
(Ord l, Ord e) =>
GenLocated l e -> GenLocated l e -> Ordering
$cp1Ord :: forall l e. (Ord l, Ord e) => Eq (GenLocated l e)
Ord, Typeable (GenLocated l e)
DataType
Constr
Typeable (GenLocated l e)
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> GenLocated l e -> c (GenLocated l e))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (GenLocated l e))
-> (GenLocated l e -> Constr)
-> (GenLocated l e -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (GenLocated l e)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (GenLocated l e)))
-> ((forall b. Data b => b -> b)
-> GenLocated l e -> GenLocated l e)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> GenLocated l e -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> GenLocated l e -> r)
-> (forall u.
(forall d. Data d => d -> u) -> GenLocated l e -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> GenLocated l e -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> GenLocated l e -> m (GenLocated l e))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> GenLocated l e -> m (GenLocated l e))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> GenLocated l e -> m (GenLocated l e))
-> Data (GenLocated l e)
GenLocated l e -> DataType
GenLocated l e -> Constr
(forall b. Data b => b -> b) -> GenLocated l e -> GenLocated l e
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> GenLocated l e -> c (GenLocated l e)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (GenLocated l e)
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (GenLocated l e))
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> GenLocated l e -> u
forall u. (forall d. Data d => d -> u) -> GenLocated l e -> [u]
forall l e. (Data l, Data e) => Typeable (GenLocated l e)
forall l e. (Data l, Data e) => GenLocated l e -> DataType
forall l e. (Data l, Data e) => GenLocated l e -> Constr
forall l e.
(Data l, Data e) =>
(forall b. Data b => b -> b) -> GenLocated l e -> GenLocated l e
forall l e u.
(Data l, Data e) =>
Int -> (forall d. Data d => d -> u) -> GenLocated l e -> u
forall l e u.
(Data l, Data e) =>
(forall d. Data d => d -> u) -> GenLocated l e -> [u]
forall l e r r'.
(Data l, Data e) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> GenLocated l e -> r
forall l e r r'.
(Data l, Data e) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> GenLocated l e -> r
forall l e (m :: * -> *).
(Data l, Data e, Monad m) =>
(forall d. Data d => d -> m d)
-> GenLocated l e -> m (GenLocated l e)
forall l e (m :: * -> *).
(Data l, Data e, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> GenLocated l e -> m (GenLocated l e)
forall l e (c :: * -> *).
(Data l, Data e) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (GenLocated l e)
forall l e (c :: * -> *).
(Data l, Data e) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> GenLocated l e -> c (GenLocated l e)
forall l e (t :: * -> *) (c :: * -> *).
(Data l, Data e, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (GenLocated l e))
forall l e (t :: * -> * -> *) (c :: * -> *).
(Data l, Data e, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (GenLocated l e))
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> GenLocated l e -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> GenLocated l e -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> GenLocated l e -> m (GenLocated l e)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> GenLocated l e -> m (GenLocated l e)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (GenLocated l e)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> GenLocated l e -> c (GenLocated l e)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (GenLocated l e))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (GenLocated l e))
$cL :: Constr
$tGenLocated :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> GenLocated l e -> m (GenLocated l e)
$cgmapMo :: forall l e (m :: * -> *).
(Data l, Data e, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> GenLocated l e -> m (GenLocated l e)
gmapMp :: (forall d. Data d => d -> m d)
-> GenLocated l e -> m (GenLocated l e)
$cgmapMp :: forall l e (m :: * -> *).
(Data l, Data e, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> GenLocated l e -> m (GenLocated l e)
gmapM :: (forall d. Data d => d -> m d)
-> GenLocated l e -> m (GenLocated l e)
$cgmapM :: forall l e (m :: * -> *).
(Data l, Data e, Monad m) =>
(forall d. Data d => d -> m d)
-> GenLocated l e -> m (GenLocated l e)
gmapQi :: Int -> (forall d. Data d => d -> u) -> GenLocated l e -> u
$cgmapQi :: forall l e u.
(Data l, Data e) =>
Int -> (forall d. Data d => d -> u) -> GenLocated l e -> u
gmapQ :: (forall d. Data d => d -> u) -> GenLocated l e -> [u]
$cgmapQ :: forall l e u.
(Data l, Data e) =>
(forall d. Data d => d -> u) -> GenLocated l e -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> GenLocated l e -> r
$cgmapQr :: forall l e r r'.
(Data l, Data e) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> GenLocated l e -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> GenLocated l e -> r
$cgmapQl :: forall l e r r'.
(Data l, Data e) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> GenLocated l e -> r
gmapT :: (forall b. Data b => b -> b) -> GenLocated l e -> GenLocated l e
$cgmapT :: forall l e.
(Data l, Data e) =>
(forall b. Data b => b -> b) -> GenLocated l e -> GenLocated l e
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (GenLocated l e))
$cdataCast2 :: forall l e (t :: * -> * -> *) (c :: * -> *).
(Data l, Data e, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (GenLocated l e))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (GenLocated l e))
$cdataCast1 :: forall l e (t :: * -> *) (c :: * -> *).
(Data l, Data e, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (GenLocated l e))
dataTypeOf :: GenLocated l e -> DataType
$cdataTypeOf :: forall l e. (Data l, Data e) => GenLocated l e -> DataType
toConstr :: GenLocated l e -> Constr
$ctoConstr :: forall l e. (Data l, Data e) => GenLocated l e -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (GenLocated l e)
$cgunfold :: forall l e (c :: * -> *).
(Data l, Data e) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (GenLocated l e)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> GenLocated l e -> c (GenLocated l e)
$cgfoldl :: forall l e (c :: * -> *).
(Data l, Data e) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> GenLocated l e -> c (GenLocated l e)
$cp1Data :: forall l e. (Data l, Data e) => Typeable (GenLocated l e)
Data, a -> GenLocated l b -> GenLocated l a
(a -> b) -> GenLocated l a -> GenLocated l b
(forall a b. (a -> b) -> GenLocated l a -> GenLocated l b)
-> (forall a b. a -> GenLocated l b -> GenLocated l a)
-> Functor (GenLocated l)
forall a b. a -> GenLocated l b -> GenLocated l a
forall a b. (a -> b) -> GenLocated l a -> GenLocated l b
forall l a b. a -> GenLocated l b -> GenLocated l a
forall l a b. (a -> b) -> GenLocated l a -> GenLocated l b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> GenLocated l b -> GenLocated l a
$c<$ :: forall l a b. a -> GenLocated l b -> GenLocated l a
fmap :: (a -> b) -> GenLocated l a -> GenLocated l b
$cfmap :: forall l a b. (a -> b) -> GenLocated l a -> GenLocated l b
Functor, GenLocated l a -> Bool
(a -> m) -> GenLocated l a -> m
(a -> b -> b) -> b -> GenLocated l a -> b
(forall m. Monoid m => GenLocated l m -> m)
-> (forall m a. Monoid m => (a -> m) -> GenLocated l a -> m)
-> (forall m a. Monoid m => (a -> m) -> GenLocated l a -> m)
-> (forall a b. (a -> b -> b) -> b -> GenLocated l a -> b)
-> (forall a b. (a -> b -> b) -> b -> GenLocated l a -> b)
-> (forall b a. (b -> a -> b) -> b -> GenLocated l a -> b)
-> (forall b a. (b -> a -> b) -> b -> GenLocated l a -> b)
-> (forall a. (a -> a -> a) -> GenLocated l a -> a)
-> (forall a. (a -> a -> a) -> GenLocated l a -> a)
-> (forall a. GenLocated l a -> [a])
-> (forall a. GenLocated l a -> Bool)
-> (forall a. GenLocated l a -> Int)
-> (forall a. Eq a => a -> GenLocated l a -> Bool)
-> (forall a. Ord a => GenLocated l a -> a)
-> (forall a. Ord a => GenLocated l a -> a)
-> (forall a. Num a => GenLocated l a -> a)
-> (forall a. Num a => GenLocated l a -> a)
-> Foldable (GenLocated l)
forall a. Eq a => a -> GenLocated l a -> Bool
forall a. Num a => GenLocated l a -> a
forall a. Ord a => GenLocated l a -> a
forall m. Monoid m => GenLocated l m -> m
forall a. GenLocated l a -> Bool
forall a. GenLocated l a -> Int
forall a. GenLocated l a -> [a]
forall a. (a -> a -> a) -> GenLocated l a -> a
forall l a. Eq a => a -> GenLocated l a -> Bool
forall l a. Num a => GenLocated l a -> a
forall l a. Ord a => GenLocated l a -> a
forall m a. Monoid m => (a -> m) -> GenLocated l a -> m
forall l m. Monoid m => GenLocated l m -> m
forall l a. GenLocated l a -> Bool
forall l a. GenLocated l a -> Int
forall l a. GenLocated l a -> [a]
forall b a. (b -> a -> b) -> b -> GenLocated l a -> b
forall a b. (a -> b -> b) -> b -> GenLocated l a -> b
forall l a. (a -> a -> a) -> GenLocated l a -> a
forall l m a. Monoid m => (a -> m) -> GenLocated l a -> m
forall l b a. (b -> a -> b) -> b -> GenLocated l a -> b
forall l a b. (a -> b -> b) -> b -> GenLocated l a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: GenLocated l a -> a
$cproduct :: forall l a. Num a => GenLocated l a -> a
sum :: GenLocated l a -> a
$csum :: forall l a. Num a => GenLocated l a -> a
minimum :: GenLocated l a -> a
$cminimum :: forall l a. Ord a => GenLocated l a -> a
maximum :: GenLocated l a -> a
$cmaximum :: forall l a. Ord a => GenLocated l a -> a
elem :: a -> GenLocated l a -> Bool
$celem :: forall l a. Eq a => a -> GenLocated l a -> Bool
length :: GenLocated l a -> Int
$clength :: forall l a. GenLocated l a -> Int
null :: GenLocated l a -> Bool
$cnull :: forall l a. GenLocated l a -> Bool
toList :: GenLocated l a -> [a]
$ctoList :: forall l a. GenLocated l a -> [a]
foldl1 :: (a -> a -> a) -> GenLocated l a -> a
$cfoldl1 :: forall l a. (a -> a -> a) -> GenLocated l a -> a
foldr1 :: (a -> a -> a) -> GenLocated l a -> a
$cfoldr1 :: forall l a. (a -> a -> a) -> GenLocated l a -> a
foldl' :: (b -> a -> b) -> b -> GenLocated l a -> b
$cfoldl' :: forall l b a. (b -> a -> b) -> b -> GenLocated l a -> b
foldl :: (b -> a -> b) -> b -> GenLocated l a -> b
$cfoldl :: forall l b a. (b -> a -> b) -> b -> GenLocated l a -> b
foldr' :: (a -> b -> b) -> b -> GenLocated l a -> b
$cfoldr' :: forall l a b. (a -> b -> b) -> b -> GenLocated l a -> b
foldr :: (a -> b -> b) -> b -> GenLocated l a -> b
$cfoldr :: forall l a b. (a -> b -> b) -> b -> GenLocated l a -> b
foldMap' :: (a -> m) -> GenLocated l a -> m
$cfoldMap' :: forall l m a. Monoid m => (a -> m) -> GenLocated l a -> m
foldMap :: (a -> m) -> GenLocated l a -> m
$cfoldMap :: forall l m a. Monoid m => (a -> m) -> GenLocated l a -> m
fold :: GenLocated l m -> m
$cfold :: forall l m. Monoid m => GenLocated l m -> m
Foldable, Functor (GenLocated l)
Foldable (GenLocated l)
Functor (GenLocated l)
-> Foldable (GenLocated l)
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> GenLocated l a -> f (GenLocated l b))
-> (forall (f :: * -> *) a.
Applicative f =>
GenLocated l (f a) -> f (GenLocated l a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> GenLocated l a -> m (GenLocated l b))
-> (forall (m :: * -> *) a.
Monad m =>
GenLocated l (m a) -> m (GenLocated l a))
-> Traversable (GenLocated l)
(a -> f b) -> GenLocated l a -> f (GenLocated l b)
forall l. Functor (GenLocated l)
forall l. Foldable (GenLocated l)
forall l (m :: * -> *) a.
Monad m =>
GenLocated l (m a) -> m (GenLocated l a)
forall l (f :: * -> *) a.
Applicative f =>
GenLocated l (f a) -> f (GenLocated l a)
forall l (m :: * -> *) a b.
Monad m =>
(a -> m b) -> GenLocated l a -> m (GenLocated l b)
forall l (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> GenLocated l a -> f (GenLocated l b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
GenLocated l (m a) -> m (GenLocated l a)
forall (f :: * -> *) a.
Applicative f =>
GenLocated l (f a) -> f (GenLocated l a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> GenLocated l a -> m (GenLocated l b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> GenLocated l a -> f (GenLocated l b)
sequence :: GenLocated l (m a) -> m (GenLocated l a)
$csequence :: forall l (m :: * -> *) a.
Monad m =>
GenLocated l (m a) -> m (GenLocated l a)
mapM :: (a -> m b) -> GenLocated l a -> m (GenLocated l b)
$cmapM :: forall l (m :: * -> *) a b.
Monad m =>
(a -> m b) -> GenLocated l a -> m (GenLocated l b)
sequenceA :: GenLocated l (f a) -> f (GenLocated l a)
$csequenceA :: forall l (f :: * -> *) a.
Applicative f =>
GenLocated l (f a) -> f (GenLocated l a)
traverse :: (a -> f b) -> GenLocated l a -> f (GenLocated l b)
$ctraverse :: forall l (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> GenLocated l a -> f (GenLocated l b)
$cp2Traversable :: forall l. Foldable (GenLocated l)
$cp1Traversable :: forall l. Functor (GenLocated l)
Traversable)
type Located = GenLocated SrcSpan
type RealLocated = GenLocated RealSrcSpan
mapLoc :: (a -> b) -> GenLocated l a -> GenLocated l b
mapLoc :: (a -> b) -> GenLocated l a -> GenLocated l b
mapLoc = (a -> b) -> GenLocated l a -> GenLocated l b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap
unLoc :: HasSrcSpan a => a -> SrcSpanLess a
unLoc :: a -> SrcSpanLess a
unLoc (a -> Located (SrcSpanLess a)
forall a. HasSrcSpan a => a -> Located (SrcSpanLess a)
dL->L SrcSpan
_ SrcSpanLess a
e) = SrcSpanLess a
e
getLoc :: HasSrcSpan a => a -> SrcSpan
getLoc :: a -> SrcSpan
getLoc (a -> Located (SrcSpanLess a)
forall a. HasSrcSpan a => a -> Located (SrcSpanLess a)
dL->L SrcSpan
l SrcSpanLess a
_) = SrcSpan
l
noLoc :: HasSrcSpan a => SrcSpanLess a -> a
noLoc :: SrcSpanLess a -> a
noLoc SrcSpanLess a
e = SrcSpan -> SrcSpanLess a -> a
forall a. HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a
cL SrcSpan
noSrcSpan SrcSpanLess a
e
mkGeneralLocated :: HasSrcSpan e => String -> SrcSpanLess e -> e
mkGeneralLocated :: String -> SrcSpanLess e -> e
mkGeneralLocated String
s SrcSpanLess e
e = SrcSpan -> SrcSpanLess e -> e
forall a. HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a
cL (FastString -> SrcSpan
mkGeneralSrcSpan (String -> FastString
fsLit String
s)) SrcSpanLess e
e
combineLocs :: (HasSrcSpan a , HasSrcSpan b) => a -> b -> SrcSpan
combineLocs :: a -> b -> SrcSpan
combineLocs a
a b
b = SrcSpan -> SrcSpan -> SrcSpan
combineSrcSpans (a -> SrcSpan
forall a. HasSrcSpan a => a -> SrcSpan
getLoc a
a) (b -> SrcSpan
forall a. HasSrcSpan a => a -> SrcSpan
getLoc b
b)
addCLoc :: (HasSrcSpan a , HasSrcSpan b , HasSrcSpan c) =>
a -> b -> SrcSpanLess c -> c
addCLoc :: a -> b -> SrcSpanLess c -> c
addCLoc a
a b
b SrcSpanLess c
c = SrcSpan -> SrcSpanLess c -> c
forall a. HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a
cL (SrcSpan -> SrcSpan -> SrcSpan
combineSrcSpans (a -> SrcSpan
forall a. HasSrcSpan a => a -> SrcSpan
getLoc a
a) (b -> SrcSpan
forall a. HasSrcSpan a => a -> SrcSpan
getLoc b
b)) SrcSpanLess c
c
eqLocated :: (HasSrcSpan a , Eq (SrcSpanLess a)) => a -> a -> Bool
eqLocated :: a -> a -> Bool
eqLocated a
a a
b = a -> SrcSpanLess a
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc a
a SrcSpanLess a -> SrcSpanLess a -> Bool
forall a. Eq a => a -> a -> Bool
== a -> SrcSpanLess a
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc a
b
cmpLocated :: (HasSrcSpan a , Ord (SrcSpanLess a)) => a -> a -> Ordering
cmpLocated :: a -> a -> Ordering
cmpLocated a
a a
b = a -> SrcSpanLess a
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc a
a SrcSpanLess a -> SrcSpanLess a -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` a -> SrcSpanLess a
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc a
b
instance (Outputable l, Outputable e) => Outputable (GenLocated l e) where
ppr :: GenLocated l e -> SDoc
ppr (L l
l e
e) =
SDoc -> SDoc
whenPprDebug (SDoc -> SDoc
braces (l -> SDoc
forall a. Outputable a => a -> SDoc
ppr l
l))
SDoc -> SDoc -> SDoc
$$ e -> SDoc
forall a. Outputable a => a -> SDoc
ppr e
e
leftmost_smallest, leftmost_largest, rightmost :: SrcSpan -> SrcSpan -> Ordering
rightmost :: SrcSpan -> SrcSpan -> Ordering
rightmost = (SrcSpan -> SrcSpan -> Ordering) -> SrcSpan -> SrcSpan -> Ordering
forall a b c. (a -> b -> c) -> b -> a -> c
flip SrcSpan -> SrcSpan -> Ordering
forall a. Ord a => a -> a -> Ordering
compare
leftmost_smallest :: SrcSpan -> SrcSpan -> Ordering
leftmost_smallest = SrcSpan -> SrcSpan -> Ordering
forall a. Ord a => a -> a -> Ordering
compare
leftmost_largest :: SrcSpan -> SrcSpan -> Ordering
leftmost_largest SrcSpan
a SrcSpan
b = (SrcSpan -> SrcLoc
srcSpanStart SrcSpan
a SrcLoc -> SrcLoc -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` SrcSpan -> SrcLoc
srcSpanStart SrcSpan
b)
Ordering -> Ordering -> Ordering
`thenCmp`
(SrcSpan -> SrcLoc
srcSpanEnd SrcSpan
b SrcLoc -> SrcLoc -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` SrcSpan -> SrcLoc
srcSpanEnd SrcSpan
a)
spans :: SrcSpan -> (Int, Int) -> Bool
spans :: SrcSpan -> (Int, Int) -> Bool
spans (UnhelpfulSpan FastString
_) (Int, Int)
_ = String -> Bool
forall a. String -> a
panic String
"spans UnhelpfulSpan"
spans (RealSrcSpan RealSrcSpan
span) (Int
l,Int
c) = RealSrcSpan -> RealSrcLoc
realSrcSpanStart RealSrcSpan
span RealSrcLoc -> RealSrcLoc -> Bool
forall a. Ord a => a -> a -> Bool
<= RealSrcLoc
loc Bool -> Bool -> Bool
&& RealSrcLoc
loc RealSrcLoc -> RealSrcLoc -> Bool
forall a. Ord a => a -> a -> Bool
<= RealSrcSpan -> RealSrcLoc
realSrcSpanEnd RealSrcSpan
span
where loc :: RealSrcLoc
loc = FastString -> Int -> Int -> RealSrcLoc
mkRealSrcLoc (RealSrcSpan -> FastString
srcSpanFile RealSrcSpan
span) Int
l Int
c
isSubspanOf :: SrcSpan
-> SrcSpan
-> Bool
isSubspanOf :: SrcSpan -> SrcSpan -> Bool
isSubspanOf SrcSpan
src SrcSpan
parent
| SrcSpan -> Maybe FastString
srcSpanFileName_maybe SrcSpan
parent Maybe FastString -> Maybe FastString -> Bool
forall a. Eq a => a -> a -> Bool
/= SrcSpan -> Maybe FastString
srcSpanFileName_maybe SrcSpan
src = Bool
False
| Bool
otherwise = SrcSpan -> SrcLoc
srcSpanStart SrcSpan
parent SrcLoc -> SrcLoc -> Bool
forall a. Ord a => a -> a -> Bool
<= SrcSpan -> SrcLoc
srcSpanStart SrcSpan
src Bool -> Bool -> Bool
&&
SrcSpan -> SrcLoc
srcSpanEnd SrcSpan
parent SrcLoc -> SrcLoc -> Bool
forall a. Ord a => a -> a -> Bool
>= SrcSpan -> SrcLoc
srcSpanEnd SrcSpan
src
type family SrcSpanLess a
class HasSrcSpan a where
composeSrcSpan :: Located (SrcSpanLess a) -> a
decomposeSrcSpan :: a -> Located (SrcSpanLess a)
type instance SrcSpanLess (GenLocated l e) = e
instance HasSrcSpan (Located a) where
composeSrcSpan :: Located (SrcSpanLess (Located a)) -> Located a
composeSrcSpan = Located (SrcSpanLess (Located a)) -> Located a
forall a. a -> a
id
decomposeSrcSpan :: Located a -> Located (SrcSpanLess (Located a))
decomposeSrcSpan = Located a -> Located (SrcSpanLess (Located a))
forall a. a -> a
id
dL :: HasSrcSpan a => a -> Located (SrcSpanLess a)
dL :: a -> Located (SrcSpanLess a)
dL = a -> Located (SrcSpanLess a)
forall a. HasSrcSpan a => a -> Located (SrcSpanLess a)
decomposeSrcSpan
cL :: HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a
cL :: SrcSpan -> SrcSpanLess a -> a
cL SrcSpan
sp SrcSpanLess a
e = Located (SrcSpanLess a) -> a
forall a. HasSrcSpan a => Located (SrcSpanLess a) -> a
composeSrcSpan (SrcSpan -> SrcSpanLess a -> Located (SrcSpanLess a)
forall l e. l -> e -> GenLocated l e
L SrcSpan
sp SrcSpanLess a
e)
pattern LL :: HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a
pattern $bLL :: SrcSpan -> SrcSpanLess a -> a
$mLL :: forall r a.
HasSrcSpan a =>
a -> (SrcSpan -> SrcSpanLess a -> r) -> (Void# -> r) -> r
LL sp e <- (dL->L sp e)
where
LL SrcSpan
sp SrcSpanLess a
e = SrcSpan -> SrcSpanLess a -> a
forall a. HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a
cL SrcSpan
sp SrcSpanLess a
e
onHasSrcSpan :: (HasSrcSpan a , HasSrcSpan b) =>
(SrcSpanLess a -> SrcSpanLess b) -> a -> b
onHasSrcSpan :: (SrcSpanLess a -> SrcSpanLess b) -> a -> b
onHasSrcSpan SrcSpanLess a -> SrcSpanLess b
f (a -> Located (SrcSpanLess a)
forall a. HasSrcSpan a => a -> Located (SrcSpanLess a)
dL->L SrcSpan
l SrcSpanLess a
e) = SrcSpan -> SrcSpanLess b -> b
forall a. HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a
cL SrcSpan
l (SrcSpanLess a -> SrcSpanLess b
f SrcSpanLess a
e)
liftL :: (HasSrcSpan a, HasSrcSpan b, Monad m) =>
(SrcSpanLess a -> m (SrcSpanLess b)) -> a -> m b
liftL :: (SrcSpanLess a -> m (SrcSpanLess b)) -> a -> m b
liftL SrcSpanLess a -> m (SrcSpanLess b)
f (a -> Located (SrcSpanLess a)
forall a. HasSrcSpan a => a -> Located (SrcSpanLess a)
dL->L SrcSpan
loc SrcSpanLess a
a) = do
SrcSpanLess b
a' <- SrcSpanLess a -> m (SrcSpanLess b)
f SrcSpanLess a
a
b -> m b
forall (m :: * -> *) a. Monad m => a -> m a
return (b -> m b) -> b -> m b
forall a b. (a -> b) -> a -> b
$ SrcSpan -> SrcSpanLess b -> b
forall a. HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a
cL SrcSpan
loc SrcSpanLess b
a'
getRealSrcSpan :: RealLocated a -> RealSrcSpan
getRealSrcSpan :: RealLocated a -> RealSrcSpan
getRealSrcSpan (L RealSrcSpan
l a
_) = RealSrcSpan
l
unRealSrcSpan :: RealLocated a -> a
unRealSrcSpan :: RealLocated a -> a
unRealSrcSpan (L RealSrcSpan
_ a
e) = a
e