{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE PatternSynonyms #-}
module GHC.Types.SrcLoc (
RealSrcLoc,
SrcLoc(..),
mkSrcLoc, mkRealSrcLoc, mkGeneralSrcLoc,
noSrcLoc,
generatedSrcLoc,
interactiveSrcLoc,
advanceSrcLoc,
advanceBufPos,
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,
BufPos(..),
BufSpan(..),
Located,
RealLocated,
GenLocated(..),
noLoc,
mkGeneralLocated,
getLoc, unLoc,
unRealSrcSpan, getRealSrcSpan,
mapLoc,
eqLocated, cmpLocated, combineLocs, addCLoc,
leftmost_smallest, leftmost_largest, rightmost_smallest,
spans, isSubspanOf, isRealSubspanOf, sortLocated,
sortRealLocated,
lookupSrcLoc, lookupSrcSpan,
liftL,
PsLoc(..),
PsSpan(..),
PsLocated,
advancePsLoc,
mkPsSpan,
psSpanStart,
psSpanEnd,
mkSrcSpanPs,
) where
import GHC.Prelude
import GHC.Utils.Misc
import GHC.Utils.Json
import GHC.Utils.Outputable
import GHC.Data.FastString
import Control.DeepSeq
import Control.Applicative (liftA2)
import Data.Bits
import Data.Data
import Data.List (sortBy, intercalate)
import Data.Function (on)
import qualified Data.Map as Map
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
External instance of the constraint type Eq Int
External instance of the constraint type Eq FastString
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
External instance of the constraint type Ord FastString
Instance of class: Eq of the constraint type Eq RealSrcLoc
External instance of the constraint type Ord Int
Instance of class: Ord of the constraint type Ord RealSrcLoc
Instance of class: Eq of the constraint type Eq RealSrcLoc
Ord)
newtype BufPos = BufPos { BufPos -> Int
bufPos :: Int }
deriving (BufPos -> BufPos -> Bool
(BufPos -> BufPos -> Bool)
-> (BufPos -> BufPos -> Bool) -> Eq BufPos
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BufPos -> BufPos -> Bool
$c/= :: BufPos -> BufPos -> Bool
== :: BufPos -> BufPos -> Bool
$c== :: BufPos -> BufPos -> Bool
External instance of the constraint type Eq Int
Eq, Eq BufPos
Eq BufPos
-> (BufPos -> BufPos -> Ordering)
-> (BufPos -> BufPos -> Bool)
-> (BufPos -> BufPos -> Bool)
-> (BufPos -> BufPos -> Bool)
-> (BufPos -> BufPos -> Bool)
-> (BufPos -> BufPos -> BufPos)
-> (BufPos -> BufPos -> BufPos)
-> Ord BufPos
BufPos -> BufPos -> Bool
BufPos -> BufPos -> Ordering
BufPos -> BufPos -> BufPos
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 :: BufPos -> BufPos -> BufPos
$cmin :: BufPos -> BufPos -> BufPos
max :: BufPos -> BufPos -> BufPos
$cmax :: BufPos -> BufPos -> BufPos
>= :: BufPos -> BufPos -> Bool
$c>= :: BufPos -> BufPos -> Bool
> :: BufPos -> BufPos -> Bool
$c> :: BufPos -> BufPos -> Bool
<= :: BufPos -> BufPos -> Bool
$c<= :: BufPos -> BufPos -> Bool
< :: BufPos -> BufPos -> Bool
$c< :: BufPos -> BufPos -> Bool
compare :: BufPos -> BufPos -> Ordering
$ccompare :: BufPos -> BufPos -> Ordering
Instance of class: Eq of the constraint type Eq BufPos
Instance of class: Eq of the constraint type Eq BufPos
External instance of the constraint type Ord Int
Ord, Int -> BufPos -> ShowS
[BufPos] -> ShowS
BufPos -> String
(Int -> BufPos -> ShowS)
-> (BufPos -> String) -> ([BufPos] -> ShowS) -> Show BufPos
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BufPos] -> ShowS
$cshowList :: [BufPos] -> ShowS
show :: BufPos -> String
$cshow :: BufPos -> String
showsPrec :: Int -> BufPos -> ShowS
$cshowsPrec :: Int -> BufPos -> ShowS
External instance of the constraint type Show Int
External instance of the constraint type Ord Int
Show)
data SrcLoc
= RealSrcLoc !RealSrcLoc !(Maybe BufPos)
| 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
Instance of class: Eq of the constraint type Eq BufPos
External instance of the constraint type forall a. Eq a => Eq (Maybe a)
Instance of class: Eq of the constraint type Eq BufPos
External instance of the constraint type Eq FastString
Instance of class: Eq of the constraint type Eq RealSrcLoc
Eq, 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
External instance of the constraint type Show FastString
Instance of class: Show of the constraint type Show BufPos
External instance of the constraint type forall a. Show a => Show (Maybe a)
External instance of the constraint type Ord Int
Instance of class: Show of the constraint type Show RealSrcLoc
Instance of class: Show of the constraint type Show BufPos
Show)
mkSrcLoc :: FastString -> Int -> Int -> SrcLoc
mkSrcLoc :: FastString -> Int -> Int -> SrcLoc
mkSrcLoc FastString
x Int
line Int
col = RealSrcLoc -> Maybe BufPos -> SrcLoc
RealSrcLoc (FastString -> Int -> Int -> RealSrcLoc
mkRealSrcLoc FastString
x Int
line Int
col) Maybe BufPos
forall a. Maybe a
Nothing
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
External instance of the constraint type Num Int
+ Int
1) Int
1
advanceSrcLoc (SrcLoc FastString
f Int
l Int
c) Char
'\t' = FastString -> Int -> Int -> RealSrcLoc
SrcLoc FastString
f Int
l (Int -> Int
advance_tabstop Int
c)
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
External instance of the constraint type Num Int
+ Int
1)
advance_tabstop :: Int -> Int
advance_tabstop :: Int -> Int
advance_tabstop Int
c = ((((Int
c Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- Int
1) Int -> Int -> Int
forall a. Bits a => a -> Int -> a
External instance of the constraint type Bits Int
`shiftR` Int
3) Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Int
1) Int -> Int -> Int
forall a. Bits a => a -> Int -> a
External instance of the constraint type Bits Int
`shiftL` Int
3) Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Int
1
advanceBufPos :: BufPos -> BufPos
advanceBufPos :: BufPos -> BufPos
advanceBufPos (BufPos Int
i) = Int -> BufPos
BufPos (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
1)
sortLocated :: [Located a] -> [Located a]
sortLocated :: [Located a] -> [Located a]
sortLocated = (Located a -> Located a -> Ordering) -> [Located a] -> [Located a]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (SrcSpan -> SrcSpan -> Ordering
leftmost_smallest (SrcSpan -> SrcSpan -> Ordering)
-> (Located a -> SrcSpan) -> Located a -> Located a -> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` Located a -> SrcSpan
forall l e. GenLocated l e -> l
getLoc)
sortRealLocated :: [RealLocated a] -> [RealLocated a]
sortRealLocated :: [RealLocated a] -> [RealLocated a]
sortRealLocated = (RealLocated a -> RealLocated a -> Ordering)
-> [RealLocated a] -> [RealLocated a]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (RealSrcSpan -> RealSrcSpan -> Ordering
forall a. Ord a => a -> a -> Ordering
Instance of class: Ord of the constraint type Ord RealSrcSpan
compare (RealSrcSpan -> RealSrcSpan -> Ordering)
-> (RealLocated a -> RealSrcSpan)
-> RealLocated a
-> RealLocated a
-> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` RealLocated a -> RealSrcSpan
forall l e. GenLocated l e -> l
getLoc)
lookupSrcLoc :: SrcLoc -> Map.Map RealSrcLoc a -> Maybe a
lookupSrcLoc :: SrcLoc -> Map RealSrcLoc a -> Maybe a
lookupSrcLoc (RealSrcLoc RealSrcLoc
l Maybe BufPos
_) = RealSrcLoc -> Map RealSrcLoc a -> Maybe a
forall k a. Ord k => k -> Map k a -> Maybe a
Instance of class: Ord of the constraint type Ord RealSrcLoc
Map.lookup RealSrcLoc
l
lookupSrcLoc (UnhelpfulLoc FastString
_) = Maybe a -> Map RealSrcLoc a -> Maybe a
forall a b. a -> b -> a
const Maybe a
forall a. Maybe a
Nothing
lookupSrcSpan :: SrcSpan -> Map.Map RealSrcSpan a -> Maybe a
lookupSrcSpan :: SrcSpan -> Map RealSrcSpan a -> Maybe a
lookupSrcSpan (RealSrcSpan RealSrcSpan
l Maybe BufSpan
_) = RealSrcSpan -> Map RealSrcSpan a -> Maybe a
forall k a. Ord k => k -> Map k a -> Maybe a
Instance of class: Ord of the constraint type Ord RealSrcSpan
Map.lookup RealSrcSpan
l
lookupSrcSpan (UnhelpfulSpan FastString
_) = Maybe a -> Map RealSrcSpan a -> Maybe a
forall a b. a -> b -> a
const Maybe a
forall a. Maybe a
Nothing
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 Maybe BufPos
_) = RealSrcLoc -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable RealSrcLoc
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
External instance of the constraint type Eq Int
External instance of the constraint type Eq FastString
Eq
data BufSpan =
BufSpan { BufSpan -> BufPos
bufSpanStart, BufSpan -> BufPos
bufSpanEnd :: {-# UNPACK #-} !BufPos }
deriving (BufSpan -> BufSpan -> Bool
(BufSpan -> BufSpan -> Bool)
-> (BufSpan -> BufSpan -> Bool) -> Eq BufSpan
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BufSpan -> BufSpan -> Bool
$c/= :: BufSpan -> BufSpan -> Bool
== :: BufSpan -> BufSpan -> Bool
$c== :: BufSpan -> BufSpan -> Bool
Instance of class: Eq of the constraint type Eq BufPos
Instance of class: Eq of the constraint type Eq BufPos
Eq, Eq BufSpan
Eq BufSpan
-> (BufSpan -> BufSpan -> Ordering)
-> (BufSpan -> BufSpan -> Bool)
-> (BufSpan -> BufSpan -> Bool)
-> (BufSpan -> BufSpan -> Bool)
-> (BufSpan -> BufSpan -> Bool)
-> (BufSpan -> BufSpan -> BufSpan)
-> (BufSpan -> BufSpan -> BufSpan)
-> Ord BufSpan
BufSpan -> BufSpan -> Bool
BufSpan -> BufSpan -> Ordering
BufSpan -> BufSpan -> BufSpan
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 :: BufSpan -> BufSpan -> BufSpan
$cmin :: BufSpan -> BufSpan -> BufSpan
max :: BufSpan -> BufSpan -> BufSpan
$cmax :: BufSpan -> BufSpan -> BufSpan
>= :: BufSpan -> BufSpan -> Bool
$c>= :: BufSpan -> BufSpan -> Bool
> :: BufSpan -> BufSpan -> Bool
$c> :: BufSpan -> BufSpan -> Bool
<= :: BufSpan -> BufSpan -> Bool
$c<= :: BufSpan -> BufSpan -> Bool
< :: BufSpan -> BufSpan -> Bool
$c< :: BufSpan -> BufSpan -> Bool
compare :: BufSpan -> BufSpan -> Ordering
$ccompare :: BufSpan -> BufSpan -> Ordering
Instance of class: Eq of the constraint type Eq BufSpan
Instance of class: Ord of the constraint type Ord BufPos
Instance of class: Ord of the constraint type Ord BufSpan
Instance of class: Eq of the constraint type Eq BufSpan
Ord, Int -> BufSpan -> ShowS
[BufSpan] -> ShowS
BufSpan -> String
(Int -> BufSpan -> ShowS)
-> (BufSpan -> String) -> ([BufSpan] -> ShowS) -> Show BufSpan
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BufSpan] -> ShowS
$cshowList :: [BufSpan] -> ShowS
show :: BufSpan -> String
$cshow :: BufSpan -> String
showsPrec :: Int -> BufSpan -> ShowS
$cshowsPrec :: Int -> BufSpan -> ShowS
Instance of class: Show of the constraint type Show BufPos
External instance of the constraint type Ord Int
Instance of class: Show of the constraint type Show BufPos
Show)
data SrcSpan =
RealSrcSpan !RealSrcSpan !(Maybe BufSpan)
| 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
Instance of class: Eq of the constraint type Eq BufSpan
External instance of the constraint type forall a. Eq a => Eq (Maybe a)
External instance of the constraint type Eq FastString
Instance of class: Eq of the constraint type Eq RealSrcSpan
Instance of class: Eq of the constraint type Eq BufSpan
Eq, 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
Instance of class: Show of the constraint type Show BufSpan
External instance of the constraint type Show FastString
External instance of the constraint type forall a. Show a => Show (Maybe a)
External instance of the constraint type Ord Int
Instance of class: Show of the constraint type Show RealSrcSpan
Instance of class: Show of the constraint type Show BufSpan
Show)
instance ToJson SrcSpan where
json :: SrcSpan -> JsonDoc
json (UnhelpfulSpan {} ) = JsonDoc
JSNull
json (RealSrcSpan RealSrcSpan
rss Maybe BufSpan
_) = RealSrcSpan -> JsonDoc
forall a. ToJson a => a -> JsonDoc
Instance of class: ToJson of the constraint type ToJson RealSrcSpan
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 Maybe BufPos
mb) = RealSrcSpan -> Maybe BufSpan -> SrcSpan
RealSrcSpan (RealSrcLoc -> RealSrcSpan
realSrcLocSpan RealSrcLoc
l) ((BufPos -> BufSpan) -> Maybe BufPos -> Maybe BufSpan
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Maybe
fmap (\BufPos
b -> BufPos -> BufPos -> BufSpan
BufSpan BufPos
b BufPos
b) Maybe BufPos
mb)
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
External instance of the constraint type Eq Int
== 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
External instance of the constraint type Eq Int
== Int
line2 Bool -> Bool -> Bool
&& Int
col1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Int
== 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 Maybe BufPos
mbpos1) (RealSrcLoc RealSrcLoc
loc2 Maybe BufPos
mbpos2)
= RealSrcSpan -> Maybe BufSpan -> SrcSpan
RealSrcSpan (RealSrcLoc -> RealSrcLoc -> RealSrcSpan
mkRealSrcSpan RealSrcLoc
loc1 RealSrcLoc
loc2) ((BufPos -> BufPos -> BufSpan)
-> Maybe BufPos -> Maybe BufPos -> Maybe BufSpan
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
External instance of the constraint type Applicative Maybe
liftA2 BufPos -> BufPos -> BufSpan
BufSpan Maybe BufPos
mbpos1 Maybe BufPos
mbpos2)
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 Maybe BufSpan
mbspan1) (RealSrcSpan RealSrcSpan
span2 Maybe BufSpan
mbspan2)
| RealSrcSpan -> FastString
srcSpanFile RealSrcSpan
span1 FastString -> FastString -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq FastString
== RealSrcSpan -> FastString
srcSpanFile RealSrcSpan
span2
= RealSrcSpan -> Maybe BufSpan -> SrcSpan
RealSrcSpan (RealSrcSpan -> RealSrcSpan -> RealSrcSpan
combineRealSrcSpans RealSrcSpan
span1 RealSrcSpan
span2) ((BufSpan -> BufSpan -> BufSpan)
-> Maybe BufSpan -> Maybe BufSpan -> Maybe BufSpan
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
External instance of the constraint type Applicative Maybe
liftA2 BufSpan -> BufSpan -> BufSpan
combineBufSpans Maybe BufSpan
mbspan1 Maybe BufSpan
mbspan2)
| 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
External instance of the constraint type forall a b. (Ord a, Ord b) => Ord (a, b)
External instance of the constraint type Ord Int
External instance of the constraint type Ord Int
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
External instance of the constraint type forall a b. (Ord a, Ord b) => Ord (a, b)
External instance of the constraint type Ord Int
External instance of the constraint type Ord Int
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
combineBufSpans :: BufSpan -> BufSpan -> BufSpan
combineBufSpans :: BufSpan -> BufSpan -> BufSpan
combineBufSpans BufSpan
span1 BufSpan
span2 = BufPos -> BufPos -> BufSpan
BufSpan BufPos
start BufPos
end
where
start :: BufPos
start = BufPos -> BufPos -> BufPos
forall a. Ord a => a -> a -> a
Instance of class: Ord of the constraint type Ord BufPos
min (BufSpan -> BufPos
bufSpanStart BufSpan
span1) (BufSpan -> BufPos
bufSpanStart BufSpan
span2)
end :: BufPos
end = BufPos -> BufPos -> BufPos
forall a. Ord a => a -> a -> a
Instance of class: Ord of the constraint type Ord BufPos
max (BufSpan -> BufPos
bufSpanEnd BufSpan
span1) (BufSpan -> BufPos
bufSpanEnd BufSpan
span2)
srcSpanFirstCharacter :: SrcSpan -> SrcSpan
srcSpanFirstCharacter :: SrcSpan -> SrcSpan
srcSpanFirstCharacter l :: SrcSpan
l@(UnhelpfulSpan {}) = SrcSpan
l
srcSpanFirstCharacter (RealSrcSpan RealSrcSpan
span Maybe BufSpan
mbspan) =
RealSrcSpan -> Maybe BufSpan -> SrcSpan
RealSrcSpan (RealSrcLoc -> RealSrcLoc -> RealSrcSpan
mkRealSrcSpan RealSrcLoc
loc1 RealSrcLoc
loc2) ((BufSpan -> BufSpan) -> Maybe BufSpan -> Maybe BufSpan
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Maybe
fmap BufSpan -> BufSpan
mkBufSpan Maybe BufSpan
mbspan)
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
External instance of the constraint type Num Int
+Int
1)
mkBufSpan :: BufSpan -> BufSpan
mkBufSpan BufSpan
bspan =
let bpos1 :: BufPos
bpos1@(BufPos Int
i) = BufSpan -> BufPos
bufSpanStart BufSpan
bspan
bpos2 :: BufPos
bpos2 = Int -> BufPos
BufPos (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
1)
in BufPos -> BufPos -> BufSpan
BufSpan BufPos
bpos1 BufPos
bpos2
isGoodSrcSpan :: SrcSpan -> Bool
isGoodSrcSpan :: SrcSpan -> Bool
isGoodSrcSpan (RealSrcSpan RealSrcSpan
_ Maybe BufSpan
_) = Bool
True
isGoodSrcSpan (UnhelpfulSpan FastString
_) = Bool
False
isOneLineSpan :: SrcSpan -> Bool
isOneLineSpan :: SrcSpan -> Bool
isOneLineSpan (RealSrcSpan RealSrcSpan
s Maybe BufSpan
_) = RealSrcSpan -> Int
srcSpanStartLine RealSrcSpan
s Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Int
== 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
External instance of the constraint type forall a b. (Ord a, Ord b) => Ord (a, b)
External instance of the constraint type Ord Int
External instance of the constraint type Ord Int
<= (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
External instance of the constraint type forall a b. (Ord a, Ord b) => Ord (a, b)
External instance of the constraint type Ord Int
External instance of the constraint type Ord Int
>= (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
External instance of the constraint type Eq FastString
== 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 Maybe BufSpan
b) = RealSrcLoc -> Maybe BufPos -> SrcLoc
RealSrcLoc (RealSrcSpan -> RealSrcLoc
realSrcSpanStart RealSrcSpan
s) ((BufSpan -> BufPos) -> Maybe BufSpan -> Maybe BufPos
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Maybe
fmap BufSpan -> BufPos
bufSpanStart Maybe BufSpan
b)
srcSpanEnd :: SrcSpan -> SrcLoc
srcSpanEnd :: SrcSpan -> SrcLoc
srcSpanEnd (UnhelpfulSpan FastString
str) = FastString -> SrcLoc
UnhelpfulLoc FastString
str
srcSpanEnd (RealSrcSpan RealSrcSpan
s Maybe BufSpan
b) = RealSrcLoc -> Maybe BufPos -> SrcLoc
RealSrcLoc (RealSrcSpan -> RealSrcLoc
realSrcSpanEnd RealSrcSpan
s) ((BufSpan -> BufPos) -> Maybe BufSpan -> Maybe BufPos
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Maybe
fmap BufSpan -> BufPos
bufSpanEnd Maybe BufSpan
b)
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 Maybe BufSpan
_) = 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
Instance of class: Ord of the constraint type Ord RealSrcLoc
`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
Instance of class: Ord of the constraint type Ord RealSrcLoc
`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
External instance of the constraint type Show FastString
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
External instance of the constraint type Show Int
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
External instance of the constraint type Show Int
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
External instance of the constraint type Show FastString
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
External instance of the constraint type Show Int
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
External instance of the constraint type Show FastString
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
External instance of the constraint type Show Int
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
External instance of the constraint type Show FastString
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
External instance of the constraint type Show Int
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 Maybe BufSpan
_) = 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
External instance of the constraint type Num Int
- Int
scol Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
<= Int
1) (Char -> SDoc
char Char
'-' SDoc -> SDoc -> SDoc
<> Int -> SDoc
int (Int
ecol Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- 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
External instance of the constraint type Eq Int
== Int
0 then Int
ecol else Int
ecol Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- 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
Evidence bound by a type signature of the constraint type Eq e
Evidence bound by a type signature of the constraint type Eq l
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
Instance of class: Eq of the constraint type forall l e. (Eq l, Eq e) => Eq (GenLocated l e)
External instance of the constraint type forall a. Ord a => Eq a
Evidence bound by a type signature of the constraint type Ord l
External instance of the constraint type forall a. Ord a => Eq a
Evidence bound by a type signature of the constraint type Ord e
External instance of the constraint type forall a. Ord a => Eq a
Evidence bound by a type signature of the constraint type Ord e
External instance of the constraint type forall a. Ord a => Eq a
External instance of the constraint type forall a. Ord a => Eq a
Evidence bound by a type signature of the constraint type Ord l
Instance of class: Ord of the constraint type forall l e. (Ord l, Ord e) => Ord (GenLocated l e)
Evidence bound by a type signature of the constraint type Ord e
Evidence bound by a type signature of the constraint type Ord l
Instance of class: Eq of the constraint type forall l e. (Eq l, Eq 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)
Evidence bound by a type signature of the constraint type Typeable t
External instance of the constraint type forall a. Data a => Typeable a
Evidence bound by a type signature of the constraint type Data l
External instance of the constraint type forall a. Data a => Typeable a
Evidence bound by a type signature of the constraint type Data l
External instance of the constraint type forall a. Data a => Typeable a
Evidence bound by a type signature of the constraint type Data e
External instance of the constraint type forall a. Data a => Typeable a
Evidence bound by a type signature of the constraint type Data e
External instance of the constraint type forall a. Data a => Typeable a
External instance of the constraint type forall a. Data a => Typeable a
Evidence bound by a type signature of the constraint type Data l
Evidence bound by a type signature of the constraint type Data e
Evidence bound by a type signature of the constraint type Data l
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)
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a type signature of the constraint type Applicative f
Evidence bound by a type signature of the constraint type Applicative f
Instance of class: Foldable of the constraint type forall l. Foldable (GenLocated l)
Instance of class: Functor of the constraint type forall l. Functor (GenLocated l)
Instance of class: Functor of the constraint type forall l. Functor (GenLocated l)
Instance of class: Foldable of the constraint type forall l. Foldable (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
Instance of class: Functor of the constraint type forall l. Functor (GenLocated l)
fmap
unLoc :: GenLocated l e -> e
unLoc :: GenLocated l e -> e
unLoc (L l
_ e
e) = e
e
getLoc :: GenLocated l e -> l
getLoc :: GenLocated l e -> l
getLoc (L l
l e
_) = l
l
noLoc :: e -> Located e
noLoc :: e -> Located e
noLoc e
e = SrcSpan -> e -> Located e
forall l e. l -> e -> GenLocated l e
L SrcSpan
noSrcSpan e
e
mkGeneralLocated :: String -> e -> Located e
mkGeneralLocated :: String -> e -> Located e
mkGeneralLocated String
s e
e = SrcSpan -> e -> Located e
forall l e. l -> e -> GenLocated l e
L (FastString -> SrcSpan
mkGeneralSrcSpan (String -> FastString
fsLit String
s)) e
e
combineLocs :: Located a -> Located b -> SrcSpan
combineLocs :: Located a -> Located b -> SrcSpan
combineLocs Located a
a Located b
b = SrcSpan -> SrcSpan -> SrcSpan
combineSrcSpans (Located a -> SrcSpan
forall l e. GenLocated l e -> l
getLoc Located a
a) (Located b -> SrcSpan
forall l e. GenLocated l e -> l
getLoc Located b
b)
addCLoc :: Located a -> Located b -> c -> Located c
addCLoc :: Located a -> Located b -> c -> Located c
addCLoc Located a
a Located b
b c
c = SrcSpan -> c -> Located c
forall l e. l -> e -> GenLocated l e
L (SrcSpan -> SrcSpan -> SrcSpan
combineSrcSpans (Located a -> SrcSpan
forall l e. GenLocated l e -> l
getLoc Located a
a) (Located b -> SrcSpan
forall l e. GenLocated l e -> l
getLoc Located b
b)) c
c
eqLocated :: Eq a => GenLocated l a -> GenLocated l a -> Bool
eqLocated :: GenLocated l a -> GenLocated l a -> Bool
eqLocated GenLocated l a
a GenLocated l a
b = GenLocated l a -> a
forall l e. GenLocated l e -> e
unLoc GenLocated l a
a a -> a -> Bool
forall a. Eq a => a -> a -> Bool
Evidence bound by a type signature of the constraint type Eq a
== GenLocated l a -> a
forall l e. GenLocated l e -> e
unLoc GenLocated l a
b
cmpLocated :: Ord a => GenLocated l a -> GenLocated l a -> Ordering
cmpLocated :: GenLocated l a -> GenLocated l a -> Ordering
cmpLocated GenLocated l a
a GenLocated l a
b = GenLocated l a -> a
forall l e. GenLocated l e -> e
unLoc GenLocated l a
a a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
Evidence bound by a type signature of the constraint type Ord a
`compare` GenLocated l a -> a
forall l e. GenLocated l e -> e
unLoc GenLocated l 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
Evidence bound by a type signature of the constraint type Outputable l
ppr l
l))
SDoc -> SDoc -> SDoc
$$ e -> SDoc
forall a. Outputable a => a -> SDoc
Evidence bound by a type signature of the constraint type Outputable e
ppr e
e
leftmost_smallest, leftmost_largest, rightmost_smallest :: SrcSpan -> SrcSpan -> Ordering
rightmost_smallest :: SrcSpan -> SrcSpan -> Ordering
rightmost_smallest = (RealSrcSpan -> RealSrcSpan -> Ordering)
-> SrcSpan -> SrcSpan -> Ordering
compareSrcSpanBy ((RealSrcSpan -> RealSrcSpan -> Ordering)
-> RealSrcSpan -> RealSrcSpan -> Ordering
forall a b c. (a -> b -> c) -> b -> a -> c
flip RealSrcSpan -> RealSrcSpan -> Ordering
forall a. Ord a => a -> a -> Ordering
Instance of class: Ord of the constraint type Ord RealSrcSpan
compare)
leftmost_smallest :: SrcSpan -> SrcSpan -> Ordering
leftmost_smallest = (RealSrcSpan -> RealSrcSpan -> Ordering)
-> SrcSpan -> SrcSpan -> Ordering
compareSrcSpanBy RealSrcSpan -> RealSrcSpan -> Ordering
forall a. Ord a => a -> a -> Ordering
Instance of class: Ord of the constraint type Ord RealSrcSpan
compare
leftmost_largest :: SrcSpan -> SrcSpan -> Ordering
leftmost_largest = (RealSrcSpan -> RealSrcSpan -> Ordering)
-> SrcSpan -> SrcSpan -> Ordering
compareSrcSpanBy ((RealSrcSpan -> RealSrcSpan -> Ordering)
-> SrcSpan -> SrcSpan -> Ordering)
-> (RealSrcSpan -> RealSrcSpan -> Ordering)
-> SrcSpan
-> SrcSpan
-> Ordering
forall a b. (a -> b) -> a -> b
$ \RealSrcSpan
a RealSrcSpan
b ->
(RealSrcSpan -> RealSrcLoc
realSrcSpanStart RealSrcSpan
a RealSrcLoc -> RealSrcLoc -> Ordering
forall a. Ord a => a -> a -> Ordering
Instance of class: Ord of the constraint type Ord RealSrcLoc
`compare` RealSrcSpan -> RealSrcLoc
realSrcSpanStart RealSrcSpan
b)
Ordering -> Ordering -> Ordering
`thenCmp`
(RealSrcSpan -> RealSrcLoc
realSrcSpanEnd RealSrcSpan
b RealSrcLoc -> RealSrcLoc -> Ordering
forall a. Ord a => a -> a -> Ordering
Instance of class: Ord of the constraint type Ord RealSrcLoc
`compare` RealSrcSpan -> RealSrcLoc
realSrcSpanEnd RealSrcSpan
a)
compareSrcSpanBy :: (RealSrcSpan -> RealSrcSpan -> Ordering) -> SrcSpan -> SrcSpan -> Ordering
compareSrcSpanBy :: (RealSrcSpan -> RealSrcSpan -> Ordering)
-> SrcSpan -> SrcSpan -> Ordering
compareSrcSpanBy RealSrcSpan -> RealSrcSpan -> Ordering
cmp (RealSrcSpan RealSrcSpan
a Maybe BufSpan
_) (RealSrcSpan RealSrcSpan
b Maybe BufSpan
_) = RealSrcSpan -> RealSrcSpan -> Ordering
cmp RealSrcSpan
a RealSrcSpan
b
compareSrcSpanBy RealSrcSpan -> RealSrcSpan -> Ordering
_ (RealSrcSpan RealSrcSpan
_ Maybe BufSpan
_) (UnhelpfulSpan FastString
_) = Ordering
LT
compareSrcSpanBy RealSrcSpan -> RealSrcSpan -> Ordering
_ (UnhelpfulSpan FastString
_) (RealSrcSpan RealSrcSpan
_ Maybe BufSpan
_) = Ordering
GT
compareSrcSpanBy RealSrcSpan -> RealSrcSpan -> Ordering
_ (UnhelpfulSpan FastString
_) (UnhelpfulSpan FastString
_) = Ordering
EQ
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 Maybe BufSpan
_) (Int
l,Int
c) = RealSrcSpan -> RealSrcLoc
realSrcSpanStart RealSrcSpan
span RealSrcLoc -> RealSrcLoc -> Bool
forall a. Ord a => a -> a -> Bool
Instance of class: Ord of the constraint type Ord RealSrcLoc
<= RealSrcLoc
loc Bool -> Bool -> Bool
&& RealSrcLoc
loc RealSrcLoc -> RealSrcLoc -> Bool
forall a. Ord a => a -> a -> Bool
Instance of class: Ord of the constraint type Ord RealSrcLoc
<= 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 (RealSrcSpan RealSrcSpan
src Maybe BufSpan
_) (RealSrcSpan RealSrcSpan
parent Maybe BufSpan
_) = RealSrcSpan -> RealSrcSpan -> Bool
isRealSubspanOf RealSrcSpan
src RealSrcSpan
parent
isSubspanOf SrcSpan
_ SrcSpan
_ = Bool
False
isRealSubspanOf :: RealSrcSpan
-> RealSrcSpan
-> Bool
isRealSubspanOf :: RealSrcSpan -> RealSrcSpan -> Bool
isRealSubspanOf RealSrcSpan
src RealSrcSpan
parent
| RealSrcSpan -> FastString
srcSpanFile RealSrcSpan
parent FastString -> FastString -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq FastString
/= RealSrcSpan -> FastString
srcSpanFile RealSrcSpan
src = Bool
False
| Bool
otherwise = RealSrcSpan -> RealSrcLoc
realSrcSpanStart RealSrcSpan
parent RealSrcLoc -> RealSrcLoc -> Bool
forall a. Ord a => a -> a -> Bool
Instance of class: Ord of the constraint type Ord RealSrcLoc
<= RealSrcSpan -> RealSrcLoc
realSrcSpanStart RealSrcSpan
src Bool -> Bool -> Bool
&&
RealSrcSpan -> RealSrcLoc
realSrcSpanEnd RealSrcSpan
parent RealSrcLoc -> RealSrcLoc -> Bool
forall a. Ord a => a -> a -> Bool
Instance of class: Ord of the constraint type Ord RealSrcLoc
>= RealSrcSpan -> RealSrcLoc
realSrcSpanEnd RealSrcSpan
src
liftL :: Monad m => (a -> m b) -> GenLocated l a -> m (GenLocated l b)
liftL :: (a -> m b) -> GenLocated l a -> m (GenLocated l b)
liftL a -> m b
f (L l
loc a
a) = do
b
a' <- a -> m b
f a
a
GenLocated l b -> m (GenLocated l b)
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a type signature of the constraint type Monad m
return (GenLocated l b -> m (GenLocated l b))
-> GenLocated l b -> m (GenLocated l b)
forall a b. (a -> b) -> a -> b
$ l -> b -> GenLocated l b
forall l e. l -> e -> GenLocated l e
L l
loc 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
data PsLoc
= PsLoc { PsLoc -> RealSrcLoc
psRealLoc :: !RealSrcLoc, PsLoc -> BufPos
psBufPos :: !BufPos }
deriving (PsLoc -> PsLoc -> Bool
(PsLoc -> PsLoc -> Bool) -> (PsLoc -> PsLoc -> Bool) -> Eq PsLoc
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PsLoc -> PsLoc -> Bool
$c/= :: PsLoc -> PsLoc -> Bool
== :: PsLoc -> PsLoc -> Bool
$c== :: PsLoc -> PsLoc -> Bool
Instance of class: Eq of the constraint type Eq BufPos
Instance of class: Eq of the constraint type Eq RealSrcLoc
Eq, Eq PsLoc
Eq PsLoc
-> (PsLoc -> PsLoc -> Ordering)
-> (PsLoc -> PsLoc -> Bool)
-> (PsLoc -> PsLoc -> Bool)
-> (PsLoc -> PsLoc -> Bool)
-> (PsLoc -> PsLoc -> Bool)
-> (PsLoc -> PsLoc -> PsLoc)
-> (PsLoc -> PsLoc -> PsLoc)
-> Ord PsLoc
PsLoc -> PsLoc -> Bool
PsLoc -> PsLoc -> Ordering
PsLoc -> PsLoc -> PsLoc
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 :: PsLoc -> PsLoc -> PsLoc
$cmin :: PsLoc -> PsLoc -> PsLoc
max :: PsLoc -> PsLoc -> PsLoc
$cmax :: PsLoc -> PsLoc -> PsLoc
>= :: PsLoc -> PsLoc -> Bool
$c>= :: PsLoc -> PsLoc -> Bool
> :: PsLoc -> PsLoc -> Bool
$c> :: PsLoc -> PsLoc -> Bool
<= :: PsLoc -> PsLoc -> Bool
$c<= :: PsLoc -> PsLoc -> Bool
< :: PsLoc -> PsLoc -> Bool
$c< :: PsLoc -> PsLoc -> Bool
compare :: PsLoc -> PsLoc -> Ordering
$ccompare :: PsLoc -> PsLoc -> Ordering
Instance of class: Eq of the constraint type Eq PsLoc
Instance of class: Ord of the constraint type Ord BufPos
Instance of class: Ord of the constraint type Ord RealSrcLoc
Instance of class: Ord of the constraint type Ord PsLoc
Instance of class: Eq of the constraint type Eq PsLoc
Ord, Int -> PsLoc -> ShowS
[PsLoc] -> ShowS
PsLoc -> String
(Int -> PsLoc -> ShowS)
-> (PsLoc -> String) -> ([PsLoc] -> ShowS) -> Show PsLoc
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PsLoc] -> ShowS
$cshowList :: [PsLoc] -> ShowS
show :: PsLoc -> String
$cshow :: PsLoc -> String
showsPrec :: Int -> PsLoc -> ShowS
$cshowsPrec :: Int -> PsLoc -> ShowS
External instance of the constraint type Ord Int
Instance of class: Show of the constraint type Show RealSrcLoc
Instance of class: Show of the constraint type Show BufPos
Show)
data PsSpan
= PsSpan { PsSpan -> RealSrcSpan
psRealSpan :: !RealSrcSpan, PsSpan -> BufSpan
psBufSpan :: !BufSpan }
deriving (PsSpan -> PsSpan -> Bool
(PsSpan -> PsSpan -> Bool)
-> (PsSpan -> PsSpan -> Bool) -> Eq PsSpan
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PsSpan -> PsSpan -> Bool
$c/= :: PsSpan -> PsSpan -> Bool
== :: PsSpan -> PsSpan -> Bool
$c== :: PsSpan -> PsSpan -> Bool
Instance of class: Eq of the constraint type Eq RealSrcSpan
Instance of class: Eq of the constraint type Eq BufSpan
Eq, Eq PsSpan
Eq PsSpan
-> (PsSpan -> PsSpan -> Ordering)
-> (PsSpan -> PsSpan -> Bool)
-> (PsSpan -> PsSpan -> Bool)
-> (PsSpan -> PsSpan -> Bool)
-> (PsSpan -> PsSpan -> Bool)
-> (PsSpan -> PsSpan -> PsSpan)
-> (PsSpan -> PsSpan -> PsSpan)
-> Ord PsSpan
PsSpan -> PsSpan -> Bool
PsSpan -> PsSpan -> Ordering
PsSpan -> PsSpan -> PsSpan
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 :: PsSpan -> PsSpan -> PsSpan
$cmin :: PsSpan -> PsSpan -> PsSpan
max :: PsSpan -> PsSpan -> PsSpan
$cmax :: PsSpan -> PsSpan -> PsSpan
>= :: PsSpan -> PsSpan -> Bool
$c>= :: PsSpan -> PsSpan -> Bool
> :: PsSpan -> PsSpan -> Bool
$c> :: PsSpan -> PsSpan -> Bool
<= :: PsSpan -> PsSpan -> Bool
$c<= :: PsSpan -> PsSpan -> Bool
< :: PsSpan -> PsSpan -> Bool
$c< :: PsSpan -> PsSpan -> Bool
compare :: PsSpan -> PsSpan -> Ordering
$ccompare :: PsSpan -> PsSpan -> Ordering
Instance of class: Eq of the constraint type Eq PsSpan
Instance of class: Ord of the constraint type Ord RealSrcSpan
Instance of class: Ord of the constraint type Ord BufSpan
Instance of class: Ord of the constraint type Ord PsSpan
Instance of class: Eq of the constraint type Eq PsSpan
Ord, Int -> PsSpan -> ShowS
[PsSpan] -> ShowS
PsSpan -> String
(Int -> PsSpan -> ShowS)
-> (PsSpan -> String) -> ([PsSpan] -> ShowS) -> Show PsSpan
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PsSpan] -> ShowS
$cshowList :: [PsSpan] -> ShowS
show :: PsSpan -> String
$cshow :: PsSpan -> String
showsPrec :: Int -> PsSpan -> ShowS
$cshowsPrec :: Int -> PsSpan -> ShowS
External instance of the constraint type Ord Int
Instance of class: Show of the constraint type Show RealSrcSpan
Instance of class: Show of the constraint type Show BufSpan
Show)
type PsLocated = GenLocated PsSpan
advancePsLoc :: PsLoc -> Char -> PsLoc
advancePsLoc :: PsLoc -> Char -> PsLoc
advancePsLoc (PsLoc RealSrcLoc
real_loc BufPos
buf_loc) Char
c =
RealSrcLoc -> BufPos -> PsLoc
PsLoc (RealSrcLoc -> Char -> RealSrcLoc
advanceSrcLoc RealSrcLoc
real_loc Char
c) (BufPos -> BufPos
advanceBufPos BufPos
buf_loc)
mkPsSpan :: PsLoc -> PsLoc -> PsSpan
mkPsSpan :: PsLoc -> PsLoc -> PsSpan
mkPsSpan (PsLoc RealSrcLoc
r1 BufPos
b1) (PsLoc RealSrcLoc
r2 BufPos
b2) = RealSrcSpan -> BufSpan -> PsSpan
PsSpan (RealSrcLoc -> RealSrcLoc -> RealSrcSpan
mkRealSrcSpan RealSrcLoc
r1 RealSrcLoc
r2) (BufPos -> BufPos -> BufSpan
BufSpan BufPos
b1 BufPos
b2)
psSpanStart :: PsSpan -> PsLoc
psSpanStart :: PsSpan -> PsLoc
psSpanStart (PsSpan RealSrcSpan
r BufSpan
b) = RealSrcLoc -> BufPos -> PsLoc
PsLoc (RealSrcSpan -> RealSrcLoc
realSrcSpanStart RealSrcSpan
r) (BufSpan -> BufPos
bufSpanStart BufSpan
b)
psSpanEnd :: PsSpan -> PsLoc
psSpanEnd :: PsSpan -> PsLoc
psSpanEnd (PsSpan RealSrcSpan
r BufSpan
b) = RealSrcLoc -> BufPos -> PsLoc
PsLoc (RealSrcSpan -> RealSrcLoc
realSrcSpanEnd RealSrcSpan
r) (BufSpan -> BufPos
bufSpanEnd BufSpan
b)
mkSrcSpanPs :: PsSpan -> SrcSpan
mkSrcSpanPs :: PsSpan -> SrcSpan
mkSrcSpanPs (PsSpan RealSrcSpan
r BufSpan
b) = RealSrcSpan -> Maybe BufSpan -> SrcSpan
RealSrcSpan RealSrcSpan
r (BufSpan -> Maybe BufSpan
forall a. a -> Maybe a
Just BufSpan
b)