-- (c) The University of Glasgow, 1992-2006

{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE DeriveFunctor      #-}
{-# LANGUAGE DeriveFoldable     #-}
{-# LANGUAGE DeriveTraversable  #-}
{-# LANGUAGE FlexibleInstances  #-}
{-# LANGUAGE RecordWildCards    #-}
{-# LANGUAGE TypeFamilies       #-}
{-# LANGUAGE ViewPatterns       #-}
{-# LANGUAGE FlexibleContexts   #-}
{-# LANGUAGE PatternSynonyms    #-}


-- | This module contains types that relate to the positions of things
-- in source files, and allow tagging of those things with locations
module GHC.Types.SrcLoc (
        -- * SrcLoc
        RealSrcLoc,             -- Abstract
        SrcLoc(..),

        -- ** Constructing SrcLoc
        mkSrcLoc, mkRealSrcLoc, mkGeneralSrcLoc,

        noSrcLoc,               -- "I'm sorry, I haven't a clue"
        generatedSrcLoc,        -- Code generated within the compiler
        interactiveSrcLoc,      -- Code from an interactive session

        advanceSrcLoc,
        advanceBufPos,

        -- ** Unsafely deconstructing SrcLoc
        -- These are dubious exports, because they crash on some inputs
        srcLocFile,             -- return the file name part
        srcLocLine,             -- return the line part
        srcLocCol,              -- return the column part

        -- * SrcSpan
        RealSrcSpan,            -- Abstract
        SrcSpan(..),
        UnhelpfulSpanReason(..),

        -- ** Constructing SrcSpan
        mkGeneralSrcSpan, mkSrcSpan, mkRealSrcSpan,
        noSrcSpan, generatedSrcSpan, isGeneratedSrcSpan,
        wiredInSrcSpan,         -- Something wired into the compiler
        interactiveSrcSpan,
        srcLocSpan, realSrcLocSpan,
        combineSrcSpans,
        srcSpanFirstCharacter,

        -- ** Deconstructing SrcSpan
        srcSpanStart, srcSpanEnd,
        realSrcSpanStart, realSrcSpanEnd,
        srcSpanFileName_maybe,
        pprUserRealSpan, pprUnhelpfulSpanReason,
        unhelpfulSpanFS,

        -- ** Unsafely deconstructing SrcSpan
        -- These are dubious exports, because they crash on some inputs
        srcSpanFile,
        srcSpanStartLine, srcSpanEndLine,
        srcSpanStartCol, srcSpanEndCol,

        -- ** Predicates on SrcSpan
        isGoodSrcSpan, isOneLineSpan,
        containsSpan,

        -- * StringBuffer locations
        BufPos(..),
        getBufPos,
        BufSpan(..),
        getBufSpan,

        -- * Located
        Located,
        RealLocated,
        GenLocated(..),

        -- ** Constructing Located
        noLoc,
        mkGeneralLocated,

        -- ** Deconstructing Located
        getLoc, unLoc,
        unRealSrcSpan, getRealSrcSpan,

        -- ** Modifying Located
        mapLoc,

        -- ** Combining and comparing Located values
        eqLocated, cmpLocated, cmpBufSpan,
        combineLocs, addCLoc,
        leftmost_smallest, leftmost_largest, rightmost_smallest,
        spans, isSubspanOf, isRealSubspanOf,
        sortLocated, sortRealLocated,
        lookupSrcLoc, lookupSrcSpan,

        liftL,

        -- * Parser locations
        PsLoc(..),
        PsSpan(..),
        PsLocated,
        advancePsLoc,
        mkPsSpan,
        psSpanStart,
        psSpanEnd,
        mkSrcSpanPs,

        -- * Layout information
        LayoutInfo(..),
        leftmostColumn

    ) 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
import qualified Data.Semigroup

{-
************************************************************************
*                                                                      *
\subsection[SrcLoc-SrcLocations]{Source-location information}
*                                                                      *
************************************************************************

We keep information about the {\em definition} point for each entity;
this is the obvious stuff:
-}

-- | Real Source Location
--
-- Represents a single point within a file
data RealSrcLoc
  = SrcLoc      FastString              -- A precise location (file name)
                {-# UNPACK #-} !Int     -- line number, begins at 1
                {-# UNPACK #-} !Int     -- column number, begins at 1
  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
Ord)

-- | 0-based offset identifying the raw location in the 'StringBuffer'.
--
-- The lexer increments the 'BufPos' every time a character (UTF-8 code point)
-- is read from the input buffer. As UTF-8 is a variable-length encoding and
-- 'StringBuffer' needs a byte offset for indexing, a 'BufPos' cannot be used
-- for indexing.
--
-- The parser guarantees that 'BufPos' are monotonic. See #17632. This means
-- that syntactic constructs that appear later in the 'StringBuffer' are guaranteed to
-- have a higher 'BufPos'. Constrast that with 'RealSrcLoc', which does *not* make the
-- analogous guarantee about higher line/column numbers.
--
-- This is due to #line and {-# LINE ... #-} pragmas that can arbitrarily
-- modify 'RealSrcLoc'. Notice how 'setSrcLoc' and 'resetAlrLastLoc' in
-- "GHC.Parser.Lexer" update 'PsLoc', modifying 'RealSrcLoc' but preserving
-- 'BufPos'.
--
-- Monotonicity makes 'BufPos' useful to determine the order in which syntactic
-- elements appear in the source. Consider this example (haddockA041 in the test suite):
--
--  haddockA041.hs
--      {-# LANGUAGE CPP #-}
--      -- | Module header documentation
--      module Comments_and_CPP_include where
--      #include "IncludeMe.hs"
--
--  IncludeMe.hs:
--      -- | Comment on T
--      data T = MkT -- ^ Comment on MkT
--
-- After the C preprocessor runs, the 'StringBuffer' will contain a program that
-- looks like this (unimportant lines at the beginning removed):
--
--    # 1 "haddockA041.hs"
--    {-# LANGUAGE CPP #-}
--    -- | Module header documentation
--    module Comments_and_CPP_include where
--    # 1 "IncludeMe.hs" 1
--    -- | Comment on T
--    data T = MkT -- ^ Comment on MkT
--    # 7 "haddockA041.hs" 2
--
-- The line pragmas inserted by CPP make the error messages more informative.
-- The downside is that we can't use RealSrcLoc to determine the ordering of
-- syntactic elements.
--
-- With RealSrcLoc, we have the following location information recorded in the AST:
--   * The module name is located at haddockA041.hs:3:8-31
--   * The Haddock comment "Comment on T" is located at IncludeMe:1:1-17
--   * The data declaration is located at IncludeMe.hs:2:1-32
--
-- Is the Haddock comment located between the module name and the data
-- declaration? This is impossible to tell because the locations are not
-- comparable; they even refer to different files.
--
-- On the other hand, with 'BufPos', we have the following location information:
--   * The module name is located at 846-870
--   * The Haddock comment "Comment on T" is located at 898-915
--   * The data declaration is located at 916-928
--
-- Aside:  if you're wondering why the numbers are so high, try running
--           @ghc -E haddockA041.hs@
--         and see the extra fluff that CPP inserts at the start of the file.
--
-- For error messages, 'BufPos' is not useful at all. On the other hand, this is
-- exactly what we need to determine the order of syntactic elements:
--    870 < 898, therefore the Haddock comment appears *after* the module name.
--    915 < 916, therefore the Haddock comment appears *before* the data declaration.
--
-- We use 'BufPos' in in GHC.Parser.PostProcess.Haddock to associate Haddock
-- comments with parts of the AST using location information (#17544).
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
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
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
Show)

-- | Source Location
data SrcLoc
  = RealSrcLoc !RealSrcLoc !(Maybe BufPos)  -- See Note [Why Maybe BufPos]
  | UnhelpfulLoc FastString     -- Just a general indication
  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, 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)

{-
************************************************************************
*                                                                      *
\subsection[SrcLoc-access-fns]{Access functions}
*                                                                      *
************************************************************************
-}

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

getBufPos :: SrcLoc -> Maybe BufPos
getBufPos :: SrcLoc -> Maybe BufPos
getBufPos (RealSrcLoc RealSrcLoc
_ Maybe BufPos
mbpos) = Maybe BufPos
mbpos
getBufPos (UnhelpfulLoc FastString
_) = Maybe BufPos
forall a. Maybe a
Nothing

-- | Built-in "bad" 'SrcLoc' values for particular locations
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>")

-- | Creates a "bad" 'SrcLoc' that has no detailed information about its location
mkGeneralSrcLoc :: FastString -> SrcLoc
mkGeneralSrcLoc :: FastString -> SrcLoc
mkGeneralSrcLoc = FastString -> SrcLoc
UnhelpfulLoc

-- | Gives the filename of the 'RealSrcLoc'
srcLocFile :: RealSrcLoc -> FastString
srcLocFile :: RealSrcLoc -> FastString
srcLocFile (SrcLoc FastString
fname Int
_ Int
_) = FastString
fname

-- | Raises an error when used on a "bad" 'SrcLoc'
srcLocLine :: RealSrcLoc -> Int
srcLocLine :: RealSrcLoc -> Int
srcLocLine (SrcLoc FastString
_ Int
l Int
_) = Int
l

-- | Raises an error when used on a "bad" 'SrcLoc'
srcLocCol :: RealSrcLoc -> Int
srcLocCol :: RealSrcLoc -> Int
srcLocCol (SrcLoc FastString
_ Int
_ Int
c) = Int
c

-- | Move the 'SrcLoc' down by one line if the character is a newline,
-- to the next 8-char tabstop if it is a tab, and across by one
-- character in any other case
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 -> 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
+ 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
- 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

advanceBufPos :: BufPos -> BufPos
advanceBufPos :: BufPos -> BufPos
advanceBufPos (BufPos Int
i) = Int -> BufPos
BufPos (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)

{-
************************************************************************
*                                                                      *
\subsection[SrcLoc-instances]{Instance declarations for various names}
*                                                                      *
************************************************************************
-}

sortLocated :: [Located a] -> [Located a]
sortLocated :: forall a. [Located a] -> [Located a]
sortLocated = (GenLocated SrcSpan a -> GenLocated SrcSpan a -> Ordering)
-> [GenLocated SrcSpan a] -> [GenLocated SrcSpan a]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (SrcSpan -> SrcSpan -> Ordering
leftmost_smallest (SrcSpan -> SrcSpan -> Ordering)
-> (GenLocated SrcSpan a -> SrcSpan)
-> GenLocated SrcSpan a
-> GenLocated SrcSpan a
-> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` GenLocated SrcSpan a -> SrcSpan
forall l e. GenLocated l e -> l
getLoc)

sortRealLocated :: [RealLocated a] -> [RealLocated a]
sortRealLocated :: forall a. [RealLocated a] -> [RealLocated a]
sortRealLocated = (GenLocated RealSrcSpan a -> GenLocated RealSrcSpan a -> Ordering)
-> [GenLocated RealSrcSpan a] -> [GenLocated RealSrcSpan a]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (RealSrcSpan -> RealSrcSpan -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (RealSrcSpan -> RealSrcSpan -> Ordering)
-> (GenLocated RealSrcSpan a -> RealSrcSpan)
-> GenLocated RealSrcSpan a
-> GenLocated RealSrcSpan a
-> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` GenLocated RealSrcSpan a -> RealSrcSpan
forall l e. GenLocated l e -> l
getLoc)

lookupSrcLoc :: SrcLoc -> Map.Map RealSrcLoc a -> Maybe a
lookupSrcLoc :: forall a. 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
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 :: forall a. 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
Map.lookup RealSrcSpan
l
lookupSrcSpan (UnhelpfulSpan UnhelpfulSpanReason
_) = 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 ]

-- I don't know why there is this style-based difference
--        if userStyle sty || debugStyle sty then
--            hcat [ pprFastFilePath src_path, char ':',
--                   int src_line,
--                   char ':', int src_col
--                 ]
--        else
--            hcat [text "{-# LINE ", int src_line, space,
--                  char '\"', pprFastFilePath src_path, text " #-}"]

instance Outputable SrcLoc where
    ppr :: SrcLoc -> SDoc
ppr (RealSrcLoc RealSrcLoc
l Maybe BufPos
_) = RealSrcLoc -> SDoc
forall a. Outputable a => a -> SDoc
ppr RealSrcLoc
l
    ppr (UnhelpfulLoc FastString
s)  = FastString -> SDoc
ftext FastString
s

instance Data RealSrcSpan where
  -- don't traverse?
  toConstr :: RealSrcSpan -> Constr
toConstr RealSrcSpan
_   = String -> Constr
abstractConstr String
"RealSrcSpan"
  gunfold :: forall (c :: * -> *).
(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
  -- don't traverse?
  toConstr :: SrcSpan -> Constr
toConstr SrcSpan
_   = String -> Constr
abstractConstr String
"SrcSpan"
  gunfold :: forall (c :: * -> *).
(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"

{-
************************************************************************
*                                                                      *
\subsection[SrcSpan]{Source Spans}
*                                                                      *
************************************************************************
-}

{- |
A 'RealSrcSpan' delimits a portion of a text file.  It could be represented
by a pair of (line,column) coordinates, but in fact we optimise
slightly by using more compact representations for single-line and
zero-length spans, both of which are quite common.

The end position is defined to be the column /after/ the end of the
span.  That is, a span of (1,1)-(1,2) is one character long, and a
span of (1,1)-(1,1) is zero characters long.
-}

-- | Real Source Span
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

-- | StringBuffer Source Span
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
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
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
Show)

instance Semigroup BufSpan where
  BufSpan BufPos
start1 BufPos
end1 <> :: BufSpan -> BufSpan -> BufSpan
<> BufSpan BufPos
start2 BufPos
end2 =
    BufPos -> BufPos -> BufSpan
BufSpan (BufPos -> BufPos -> BufPos
forall a. Ord a => a -> a -> a
min BufPos
start1 BufPos
start2) (BufPos -> BufPos -> BufPos
forall a. Ord a => a -> a -> a
max BufPos
end1 BufPos
end2)

-- | Source Span
--
-- A 'SrcSpan' identifies either a specific portion of a text file
-- or a human-readable description of a location.
data SrcSpan =
    RealSrcSpan !RealSrcSpan !(Maybe BufSpan)  -- See Note [Why Maybe BufPos]
  | UnhelpfulSpan !UnhelpfulSpanReason

  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, 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) -- Show is used by GHC.Parser.Lexer, because we
                      -- derive Show for Token

data UnhelpfulSpanReason
  = UnhelpfulNoLocationInfo
  | UnhelpfulWiredIn
  | UnhelpfulInteractive
  | UnhelpfulGenerated
  | UnhelpfulOther !FastString
  deriving (UnhelpfulSpanReason -> UnhelpfulSpanReason -> Bool
(UnhelpfulSpanReason -> UnhelpfulSpanReason -> Bool)
-> (UnhelpfulSpanReason -> UnhelpfulSpanReason -> Bool)
-> Eq UnhelpfulSpanReason
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UnhelpfulSpanReason -> UnhelpfulSpanReason -> Bool
$c/= :: UnhelpfulSpanReason -> UnhelpfulSpanReason -> Bool
== :: UnhelpfulSpanReason -> UnhelpfulSpanReason -> Bool
$c== :: UnhelpfulSpanReason -> UnhelpfulSpanReason -> Bool
Eq, Int -> UnhelpfulSpanReason -> ShowS
[UnhelpfulSpanReason] -> ShowS
UnhelpfulSpanReason -> String
(Int -> UnhelpfulSpanReason -> ShowS)
-> (UnhelpfulSpanReason -> String)
-> ([UnhelpfulSpanReason] -> ShowS)
-> Show UnhelpfulSpanReason
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UnhelpfulSpanReason] -> ShowS
$cshowList :: [UnhelpfulSpanReason] -> ShowS
show :: UnhelpfulSpanReason -> String
$cshow :: UnhelpfulSpanReason -> String
showsPrec :: Int -> UnhelpfulSpanReason -> ShowS
$cshowsPrec :: Int -> UnhelpfulSpanReason -> ShowS
Show)

{- Note [Why Maybe BufPos]
~~~~~~~~~~~~~~~~~~~~~~~~~~
In SrcLoc we store (Maybe BufPos); in SrcSpan we store (Maybe BufSpan).
Why the Maybe?

Surely, the lexer can always fill in the buffer position, and it guarantees to do so.
However, sometimes the SrcLoc/SrcSpan is constructed in a different context
where the buffer location is not available, and then we use Nothing instead of
a fake value like BufPos (-1).

Perhaps the compiler could be re-engineered to pass around BufPos more
carefully and never discard it, and this 'Maybe' could be removed. If you're
interested in doing so, you may find this ripgrep query useful:

  rg "RealSrc(Loc|Span).*?Nothing"

For example, it is not uncommon to whip up source locations for e.g. error
messages, constructing a SrcSpan without a BufSpan.
-}

instance ToJson SrcSpan where
  json :: SrcSpan -> JsonDoc
json (UnhelpfulSpan {} ) = JsonDoc
JSNull --JSObject [( "type", "unhelpful")]
  json (RealSrcSpan RealSrcSpan
rss Maybe BufSpan
_) = 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` ()

getBufSpan :: SrcSpan -> Maybe BufSpan
getBufSpan :: SrcSpan -> Maybe BufSpan
getBufSpan (RealSrcSpan RealSrcSpan
_ Maybe BufSpan
mbspan) = Maybe BufSpan
mbspan
getBufSpan (UnhelpfulSpan UnhelpfulSpanReason
_) = Maybe BufSpan
forall a. Maybe a
Nothing

-- | Built-in "bad" 'SrcSpan's for common sources of location uncertainty
noSrcSpan, generatedSrcSpan, wiredInSrcSpan, interactiveSrcSpan :: SrcSpan
noSrcSpan :: SrcSpan
noSrcSpan          = UnhelpfulSpanReason -> SrcSpan
UnhelpfulSpan UnhelpfulSpanReason
UnhelpfulNoLocationInfo
wiredInSrcSpan :: SrcSpan
wiredInSrcSpan     = UnhelpfulSpanReason -> SrcSpan
UnhelpfulSpan UnhelpfulSpanReason
UnhelpfulWiredIn
interactiveSrcSpan :: SrcSpan
interactiveSrcSpan = UnhelpfulSpanReason -> SrcSpan
UnhelpfulSpan UnhelpfulSpanReason
UnhelpfulInteractive
generatedSrcSpan :: SrcSpan
generatedSrcSpan   = UnhelpfulSpanReason -> SrcSpan
UnhelpfulSpan UnhelpfulSpanReason
UnhelpfulGenerated

isGeneratedSrcSpan :: SrcSpan -> Bool
isGeneratedSrcSpan :: SrcSpan -> Bool
isGeneratedSrcSpan (UnhelpfulSpan UnhelpfulSpanReason
UnhelpfulGenerated) = Bool
True
isGeneratedSrcSpan SrcSpan
_                                  = Bool
False

-- | Create a "bad" 'SrcSpan' that has not location information
mkGeneralSrcSpan :: FastString -> SrcSpan
mkGeneralSrcSpan :: FastString -> SrcSpan
mkGeneralSrcSpan = UnhelpfulSpanReason -> SrcSpan
UnhelpfulSpan (UnhelpfulSpanReason -> SrcSpan)
-> (FastString -> UnhelpfulSpanReason) -> FastString -> SrcSpan
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FastString -> UnhelpfulSpanReason
UnhelpfulOther

-- | Create a 'SrcSpan' corresponding to a single point
srcLocSpan :: SrcLoc -> SrcSpan
srcLocSpan :: SrcLoc -> SrcSpan
srcLocSpan (UnhelpfulLoc FastString
str) = UnhelpfulSpanReason -> SrcSpan
UnhelpfulSpan (FastString -> UnhelpfulSpanReason
UnhelpfulOther 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
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

-- | Create a 'SrcSpan' between two points in a file
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

-- | 'True' if the span is known to straddle only one line.
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

-- | 'True' if the span is a single point
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

-- | Create a 'SrcSpan' between two points in a file
mkSrcSpan :: SrcLoc -> SrcLoc -> SrcSpan
mkSrcSpan :: SrcLoc -> SrcLoc -> SrcSpan
mkSrcSpan (UnhelpfulLoc FastString
str) SrcLoc
_ = UnhelpfulSpanReason -> SrcSpan
UnhelpfulSpan (FastString -> UnhelpfulSpanReason
UnhelpfulOther FastString
str)
mkSrcSpan SrcLoc
_ (UnhelpfulLoc FastString
str) = UnhelpfulSpanReason -> SrcSpan
UnhelpfulSpan (FastString -> UnhelpfulSpanReason
UnhelpfulOther 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
liftA2 BufPos -> BufPos -> BufSpan
BufSpan Maybe BufPos
mbpos1 Maybe BufPos
mbpos2)

-- | Combines two 'SrcSpan' into one that spans at least all the characters
-- within both spans. Returns UnhelpfulSpan if the files differ.
combineSrcSpans :: SrcSpan -> SrcSpan -> SrcSpan
combineSrcSpans :: SrcSpan -> SrcSpan -> SrcSpan
combineSrcSpans (UnhelpfulSpan UnhelpfulSpanReason
_) SrcSpan
r = SrcSpan
r -- this seems more useful
combineSrcSpans SrcSpan
l (UnhelpfulSpan UnhelpfulSpanReason
_) = 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
== 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
liftA2 BufSpan -> BufSpan -> BufSpan
combineBufSpans Maybe BufSpan
mbspan1 Maybe BufSpan
mbspan2)
  | Bool
otherwise = UnhelpfulSpanReason -> SrcSpan
UnhelpfulSpan (UnhelpfulSpanReason -> SrcSpan) -> UnhelpfulSpanReason -> SrcSpan
forall a b. (a -> b) -> a -> b
$
      FastString -> UnhelpfulSpanReason
UnhelpfulOther (String -> FastString
fsLit String
"<combineSrcSpans: files differ>")

-- | Combines two 'SrcSpan' into one that spans at least all the characters
-- within both spans. Assumes the "file" part is the same in both inputs
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

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
min (BufSpan -> BufPos
bufSpanStart BufSpan
span1) (BufSpan -> BufPos
bufSpanStart BufSpan
span2)
    end :: BufPos
end   = BufPos -> BufPos -> BufPos
forall a. Ord a => a -> a -> a
max (BufSpan -> BufPos
bufSpanEnd   BufSpan
span1) (BufSpan -> BufPos
bufSpanEnd   BufSpan
span2)


-- | Convert a SrcSpan into one that represents only its first character
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
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
+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
+Int
1)
      in BufPos -> BufPos -> BufSpan
BufSpan BufPos
bpos1 BufPos
bpos2

{-
************************************************************************
*                                                                      *
\subsection[SrcSpan-predicates]{Predicates}
*                                                                      *
************************************************************************
-}

-- | Test if a 'SrcSpan' is "good", i.e. has precise location information
isGoodSrcSpan :: SrcSpan -> Bool
isGoodSrcSpan :: SrcSpan -> Bool
isGoodSrcSpan (RealSrcSpan RealSrcSpan
_ Maybe BufSpan
_) = Bool
True
isGoodSrcSpan (UnhelpfulSpan UnhelpfulSpanReason
_) = Bool
False

isOneLineSpan :: SrcSpan -> Bool
-- ^ True if the span is known to straddle only one line.
-- For "bad" 'SrcSpan', it returns False
isOneLineSpan :: SrcSpan -> Bool
isOneLineSpan (RealSrcSpan RealSrcSpan
s Maybe BufSpan
_) = RealSrcSpan -> Int
srcSpanStartLine RealSrcSpan
s Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== RealSrcSpan -> Int
srcSpanEndLine RealSrcSpan
s
isOneLineSpan (UnhelpfulSpan UnhelpfulSpanReason
_) = Bool
False

-- | Tests whether the first span "contains" the other span, meaning
-- that it covers at least as much source code. True where spans are equal.
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)
    -- We check file equality last because it is (presumably?) least
    -- likely to fail.
{-
%************************************************************************
%*                                                                      *
\subsection[SrcSpan-unsafe-access-fns]{Unsafe access functions}
*                                                                      *
************************************************************************
-}

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

{-
************************************************************************
*                                                                      *
\subsection[SrcSpan-access-fns]{Access functions}
*                                                                      *
************************************************************************
-}

-- | Returns the location at the start of the 'SrcSpan' or a "bad" 'SrcSpan' if that is unavailable
srcSpanStart :: SrcSpan -> SrcLoc
srcSpanStart :: SrcSpan -> SrcLoc
srcSpanStart (UnhelpfulSpan UnhelpfulSpanReason
r) = FastString -> SrcLoc
UnhelpfulLoc (UnhelpfulSpanReason -> FastString
unhelpfulSpanFS UnhelpfulSpanReason
r)
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
fmap BufSpan -> BufPos
bufSpanStart Maybe BufSpan
b)

-- | Returns the location at the end of the 'SrcSpan' or a "bad" 'SrcSpan' if that is unavailable
srcSpanEnd :: SrcSpan -> SrcLoc
srcSpanEnd :: SrcSpan -> SrcLoc
srcSpanEnd (UnhelpfulSpan UnhelpfulSpanReason
r) = FastString -> SrcLoc
UnhelpfulLoc (UnhelpfulSpanReason -> FastString
unhelpfulSpanFS UnhelpfulSpanReason
r)
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
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)

-- | Obtains the filename for a 'SrcSpan' if it is "good"
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 UnhelpfulSpanReason
_) = Maybe FastString
forall a. Maybe a
Nothing

{-
************************************************************************
*                                                                      *
\subsection[SrcSpan-instances]{Instances}
*                                                                      *
************************************************************************
-}

-- We want to order RealSrcSpans first by the start point, then by the
-- end point.
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

-- Show is used by GHC.Parser.Lexer, because we derive Show for Token
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

-- I don't know why there is this style-based difference
--      = getPprStyle $ \ sty ->
--        if userStyle sty || debugStyle sty then
--           text (showUserRealSpan True span)
--        else
--           hcat [text "{-# LINE ", int (srcSpanStartLine span), space,
--                 char '\"', pprFastFilePath $ srcSpanFile span, text " #-}"]

instance Outputable SrcSpan where
    ppr :: SrcSpan -> SDoc
ppr SrcSpan
span = Bool -> SrcSpan -> SDoc
pprUserSpan Bool
True SrcSpan
span

instance Outputable UnhelpfulSpanReason where
    ppr :: UnhelpfulSpanReason -> SDoc
ppr = UnhelpfulSpanReason -> SDoc
pprUnhelpfulSpanReason

-- I don't know why there is this style-based difference
--      = getPprStyle $ \ sty ->
--        if userStyle sty || debugStyle sty then
--           pprUserSpan True span
--        else
--           case span of
--           UnhelpfulSpan _ -> panic "Outputable UnhelpfulSpan"
--           RealSrcSpan s -> ppr s

unhelpfulSpanFS :: UnhelpfulSpanReason -> FastString
unhelpfulSpanFS :: UnhelpfulSpanReason -> FastString
unhelpfulSpanFS UnhelpfulSpanReason
r = case UnhelpfulSpanReason
r of
  UnhelpfulOther FastString
s        -> FastString
s
  UnhelpfulSpanReason
UnhelpfulNoLocationInfo -> String -> FastString
fsLit String
"<no location info>"
  UnhelpfulSpanReason
UnhelpfulWiredIn        -> String -> FastString
fsLit String
"<wired into compiler>"
  UnhelpfulSpanReason
UnhelpfulInteractive    -> String -> FastString
fsLit String
"<interactive>"
  UnhelpfulSpanReason
UnhelpfulGenerated      -> String -> FastString
fsLit String
"<generated>"

pprUnhelpfulSpanReason :: UnhelpfulSpanReason -> SDoc
pprUnhelpfulSpanReason :: UnhelpfulSpanReason -> SDoc
pprUnhelpfulSpanReason UnhelpfulSpanReason
r = FastString -> SDoc
ftext (UnhelpfulSpanReason -> FastString
unhelpfulSpanFS UnhelpfulSpanReason
r)

pprUserSpan :: Bool -> SrcSpan -> SDoc
pprUserSpan :: Bool -> SrcSpan -> SDoc
pprUserSpan Bool
_         (UnhelpfulSpan UnhelpfulSpanReason
r) = UnhelpfulSpanReason -> SDoc
pprUnhelpfulSpanReason UnhelpfulSpanReason
r
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
- 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)) ]
            -- For single-character or point spans, we just
            -- output the starting column number

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

{-
************************************************************************
*                                                                      *
\subsection[Located]{Attaching SrcSpans to things}
*                                                                      *
************************************************************************
-}

-- | We attach SrcSpans to lots of things, so let's have a datatype for it.
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
Ord, Typeable (GenLocated l e)
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 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))
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u.
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 u. (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 :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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)
Data, (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
<$ :: forall a b. a -> GenLocated l b -> GenLocated l a
$c<$ :: forall l a b. a -> GenLocated l b -> GenLocated l a
fmap :: forall a b. (a -> b) -> GenLocated l a -> GenLocated l b
$cfmap :: forall l a b. (a -> b) -> GenLocated l a -> GenLocated l b
Functor, (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 :: forall a. Num a => GenLocated l a -> a
$cproduct :: forall l a. Num a => GenLocated l a -> a
sum :: forall a. Num a => GenLocated l a -> a
$csum :: forall l a. Num a => GenLocated l a -> a
minimum :: forall a. Ord a => GenLocated l a -> a
$cminimum :: forall l a. Ord a => GenLocated l a -> a
maximum :: forall a. Ord a => GenLocated l a -> a
$cmaximum :: forall l a. Ord a => GenLocated l a -> a
elem :: forall a. Eq a => a -> GenLocated l a -> Bool
$celem :: forall l a. Eq a => a -> GenLocated l a -> Bool
length :: forall a. GenLocated l a -> Int
$clength :: forall l a. GenLocated l a -> Int
null :: forall a. GenLocated l a -> Bool
$cnull :: forall l a. GenLocated l a -> Bool
toList :: forall a. GenLocated l a -> [a]
$ctoList :: forall l a. GenLocated l a -> [a]
foldl1 :: forall a. (a -> a -> a) -> GenLocated l a -> a
$cfoldl1 :: forall l a. (a -> a -> a) -> GenLocated l a -> a
foldr1 :: forall a. (a -> a -> a) -> GenLocated l a -> a
$cfoldr1 :: forall l a. (a -> a -> a) -> GenLocated l a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> GenLocated l a -> b
$cfoldl' :: forall l b a. (b -> a -> b) -> b -> GenLocated l a -> b
foldl :: forall b a. (b -> a -> b) -> b -> GenLocated l a -> b
$cfoldl :: forall l b a. (b -> a -> b) -> b -> GenLocated l a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> GenLocated l a -> b
$cfoldr' :: forall l a b. (a -> b -> b) -> b -> GenLocated l a -> b
foldr :: forall a b. (a -> b -> b) -> b -> GenLocated l a -> b
$cfoldr :: forall l a b. (a -> b -> b) -> b -> GenLocated l a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> GenLocated l a -> m
$cfoldMap' :: forall l m a. Monoid m => (a -> m) -> GenLocated l a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> GenLocated l a -> m
$cfoldMap :: forall l m a. Monoid m => (a -> m) -> GenLocated l a -> m
fold :: forall m. Monoid m => 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)
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 :: forall (m :: * -> *) a.
Monad m =>
GenLocated l (m a) -> m (GenLocated l a)
$csequence :: forall l (m :: * -> *) a.
Monad m =>
GenLocated l (m a) -> m (GenLocated l a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(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 :: forall (f :: * -> *) a.
Applicative f =>
GenLocated l (f a) -> f (GenLocated l a)
$csequenceA :: forall l (f :: * -> *) a.
Applicative f =>
GenLocated l (f a) -> f (GenLocated l a)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(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)
Traversable)

type Located = GenLocated SrcSpan
type RealLocated = GenLocated RealSrcSpan

mapLoc :: (a -> b) -> GenLocated l a -> GenLocated l b
mapLoc :: forall a b l. (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 :: GenLocated l e -> e
unLoc :: forall l e. GenLocated l e -> e
unLoc (L l
_ e
e) = e
e

getLoc :: GenLocated l e -> l
getLoc :: forall l e. GenLocated l e -> l
getLoc (L l
l e
_) = l
l

noLoc :: e -> Located e
noLoc :: forall e. e -> Located e
noLoc e
e = SrcSpan -> e -> GenLocated SrcSpan e
forall l e. l -> e -> GenLocated l e
L SrcSpan
noSrcSpan e
e

mkGeneralLocated :: String -> e -> Located e
mkGeneralLocated :: forall e. String -> e -> Located e
mkGeneralLocated String
s e
e = SrcSpan -> e -> GenLocated SrcSpan 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 :: forall a b. 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)

-- | Combine locations from two 'Located' things and add them to a third thing
addCLoc :: Located a -> Located b -> c -> Located c
addCLoc :: forall a b c. Located a -> Located b -> c -> Located c
addCLoc Located a
a Located b
b c
c = SrcSpan -> c -> GenLocated SrcSpan 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

-- not clear whether to add a general Eq instance, but this is useful sometimes:

-- | Tests whether the two located things are equal
eqLocated :: Eq a => GenLocated l a -> GenLocated l a -> Bool
eqLocated :: forall a l. Eq a => 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
== GenLocated l a -> a
forall l e. GenLocated l e -> e
unLoc GenLocated l a
b

-- not clear whether to add a general Ord instance, but this is useful sometimes:

-- | Tests the ordering of the two located things
cmpLocated :: Ord a => GenLocated l a -> GenLocated l a -> Ordering
cmpLocated :: forall a l. Ord a => 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
`compare` GenLocated l a -> a
forall l e. GenLocated l e -> e
unLoc GenLocated l a
b

-- | Compare the 'BufSpan' of two located things.
--
-- Precondition: both operands have an associated 'BufSpan'.
cmpBufSpan :: HasDebugCallStack => Located a -> Located a -> Ordering
cmpBufSpan :: forall a. HasDebugCallStack => Located a -> Located a -> Ordering
cmpBufSpan (L SrcSpan
l1 a
_) (L SrcSpan
l2  a
_)
  | Just BufSpan
a <- SrcSpan -> Maybe BufSpan
getBufSpan SrcSpan
l1
  , Just BufSpan
b <- SrcSpan -> Maybe BufSpan
getBufSpan SrcSpan
l2
  = BufSpan -> BufSpan -> Ordering
forall a. Ord a => a -> a -> Ordering
compare BufSpan
a BufSpan
b

  | Bool
otherwise = String -> Ordering
forall a. String -> a
panic String
"cmpBufSpan: no BufSpan"

instance (Outputable l, Outputable e) => Outputable (GenLocated l e) where
  ppr :: GenLocated l e -> SDoc
ppr (L l
l e
e) = -- TODO: We can't do this since Located was refactored into
                -- GenLocated:
                -- Print spans without the file name etc
                -- ifPprDebug (braces (pprUserSpan False l))
                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

{-
************************************************************************
*                                                                      *
\subsection{Ordering SrcSpans for InteractiveUI}
*                                                                      *
************************************************************************
-}

-- | Strategies for ordering 'SrcSpan's
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
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
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
`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
`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 UnhelpfulSpanReason
_) = Ordering
LT
compareSrcSpanBy RealSrcSpan -> RealSrcSpan -> Ordering
_   (UnhelpfulSpan UnhelpfulSpanReason
_) (RealSrcSpan RealSrcSpan
_ Maybe BufSpan
_) = Ordering
GT
compareSrcSpanBy RealSrcSpan -> RealSrcSpan -> Ordering
_   (UnhelpfulSpan UnhelpfulSpanReason
_) (UnhelpfulSpan UnhelpfulSpanReason
_) = Ordering
EQ

-- | Determines whether a span encloses a given line and column index
spans :: SrcSpan -> (Int, Int) -> Bool
spans :: SrcSpan -> (Int, Int) -> Bool
spans (UnhelpfulSpan UnhelpfulSpanReason
_) (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
<= 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

-- | Determines whether a span is enclosed by another one
isSubspanOf :: SrcSpan -- ^ The span that may be enclosed by the other
            -> SrcSpan -- ^ The span it may be enclosed by
            -> 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

-- | Determines whether a span is enclosed by another one
isRealSubspanOf :: RealSrcSpan -- ^ The span that may be enclosed by the other
                -> RealSrcSpan -- ^ The span it may be enclosed by
                -> 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
/= RealSrcSpan -> FastString
srcSpanFile RealSrcSpan
src = Bool
False
    | Bool
otherwise = RealSrcSpan -> RealSrcLoc
realSrcSpanStart RealSrcSpan
parent RealSrcLoc -> RealSrcLoc -> Bool
forall a. Ord a => a -> a -> Bool
<= RealSrcSpan -> RealSrcLoc
realSrcSpanStart RealSrcSpan
src Bool -> Bool -> Bool
&&
                  RealSrcSpan -> RealSrcLoc
realSrcSpanEnd RealSrcSpan
parent   RealSrcLoc -> RealSrcLoc -> Bool
forall a. Ord a => a -> a -> Bool
>= RealSrcSpan -> RealSrcLoc
realSrcSpanEnd RealSrcSpan
src

liftL :: Monad m => (a -> m b) -> GenLocated l a -> m (GenLocated l b)
liftL :: forall (m :: * -> *) a b l.
Monad m =>
(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
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 :: forall a. RealLocated a -> RealSrcSpan
getRealSrcSpan (L RealSrcSpan
l a
_) = RealSrcSpan
l

unRealSrcSpan :: RealLocated a -> a
unRealSrcSpan :: forall a. RealLocated a -> a
unRealSrcSpan  (L RealSrcSpan
_ a
e) = a
e


-- | A location as produced by the parser. Consists of two components:
--
-- * The location in the file, adjusted for #line and {-# LINE ... #-} pragmas (RealSrcLoc)
-- * The location in the string buffer (BufPos) with monotonicity guarantees (see #17632)
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
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
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
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
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
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
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)

-- | Layout information for declarations.
data LayoutInfo =

    -- | Explicit braces written by the user.
    --
    -- @
    -- class C a where { foo :: a; bar :: a }
    -- @
    ExplicitBraces
  |
    -- | Virtual braces inserted by the layout algorithm.
    --
    -- @
    -- class C a where
    --   foo :: a
    --   bar :: a
    -- @
    VirtualBraces
      !Int -- ^ Layout column (indentation level, begins at 1)
  |
    -- | Empty or compiler-generated blocks do not have layout information
    -- associated with them.
    NoLayoutInfo

  deriving (LayoutInfo -> LayoutInfo -> Bool
(LayoutInfo -> LayoutInfo -> Bool)
-> (LayoutInfo -> LayoutInfo -> Bool) -> Eq LayoutInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LayoutInfo -> LayoutInfo -> Bool
$c/= :: LayoutInfo -> LayoutInfo -> Bool
== :: LayoutInfo -> LayoutInfo -> Bool
$c== :: LayoutInfo -> LayoutInfo -> Bool
Eq, Eq LayoutInfo
Eq LayoutInfo
-> (LayoutInfo -> LayoutInfo -> Ordering)
-> (LayoutInfo -> LayoutInfo -> Bool)
-> (LayoutInfo -> LayoutInfo -> Bool)
-> (LayoutInfo -> LayoutInfo -> Bool)
-> (LayoutInfo -> LayoutInfo -> Bool)
-> (LayoutInfo -> LayoutInfo -> LayoutInfo)
-> (LayoutInfo -> LayoutInfo -> LayoutInfo)
-> Ord LayoutInfo
LayoutInfo -> LayoutInfo -> Bool
LayoutInfo -> LayoutInfo -> Ordering
LayoutInfo -> LayoutInfo -> LayoutInfo
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 :: LayoutInfo -> LayoutInfo -> LayoutInfo
$cmin :: LayoutInfo -> LayoutInfo -> LayoutInfo
max :: LayoutInfo -> LayoutInfo -> LayoutInfo
$cmax :: LayoutInfo -> LayoutInfo -> LayoutInfo
>= :: LayoutInfo -> LayoutInfo -> Bool
$c>= :: LayoutInfo -> LayoutInfo -> Bool
> :: LayoutInfo -> LayoutInfo -> Bool
$c> :: LayoutInfo -> LayoutInfo -> Bool
<= :: LayoutInfo -> LayoutInfo -> Bool
$c<= :: LayoutInfo -> LayoutInfo -> Bool
< :: LayoutInfo -> LayoutInfo -> Bool
$c< :: LayoutInfo -> LayoutInfo -> Bool
compare :: LayoutInfo -> LayoutInfo -> Ordering
$ccompare :: LayoutInfo -> LayoutInfo -> Ordering
Ord, Int -> LayoutInfo -> ShowS
[LayoutInfo] -> ShowS
LayoutInfo -> String
(Int -> LayoutInfo -> ShowS)
-> (LayoutInfo -> String)
-> ([LayoutInfo] -> ShowS)
-> Show LayoutInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LayoutInfo] -> ShowS
$cshowList :: [LayoutInfo] -> ShowS
show :: LayoutInfo -> String
$cshow :: LayoutInfo -> String
showsPrec :: Int -> LayoutInfo -> ShowS
$cshowsPrec :: Int -> LayoutInfo -> ShowS
Show, Typeable LayoutInfo
Typeable LayoutInfo
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> LayoutInfo -> c LayoutInfo)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c LayoutInfo)
-> (LayoutInfo -> Constr)
-> (LayoutInfo -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c LayoutInfo))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c LayoutInfo))
-> ((forall b. Data b => b -> b) -> LayoutInfo -> LayoutInfo)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> LayoutInfo -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> LayoutInfo -> r)
-> (forall u. (forall d. Data d => d -> u) -> LayoutInfo -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> LayoutInfo -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> LayoutInfo -> m LayoutInfo)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> LayoutInfo -> m LayoutInfo)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> LayoutInfo -> m LayoutInfo)
-> Data LayoutInfo
LayoutInfo -> DataType
LayoutInfo -> Constr
(forall b. Data b => b -> b) -> LayoutInfo -> LayoutInfo
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) -> LayoutInfo -> u
forall u. (forall d. Data d => d -> u) -> LayoutInfo -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LayoutInfo -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> LayoutInfo -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> LayoutInfo -> m LayoutInfo
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> LayoutInfo -> m LayoutInfo
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c LayoutInfo
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LayoutInfo -> c LayoutInfo
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c LayoutInfo)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LayoutInfo)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> LayoutInfo -> m LayoutInfo
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> LayoutInfo -> m LayoutInfo
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> LayoutInfo -> m LayoutInfo
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> LayoutInfo -> m LayoutInfo
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> LayoutInfo -> m LayoutInfo
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> LayoutInfo -> m LayoutInfo
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> LayoutInfo -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> LayoutInfo -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> LayoutInfo -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> LayoutInfo -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> LayoutInfo -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> LayoutInfo -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LayoutInfo -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LayoutInfo -> r
gmapT :: (forall b. Data b => b -> b) -> LayoutInfo -> LayoutInfo
$cgmapT :: (forall b. Data b => b -> b) -> LayoutInfo -> LayoutInfo
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LayoutInfo)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LayoutInfo)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c LayoutInfo)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c LayoutInfo)
dataTypeOf :: LayoutInfo -> DataType
$cdataTypeOf :: LayoutInfo -> DataType
toConstr :: LayoutInfo -> Constr
$ctoConstr :: LayoutInfo -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c LayoutInfo
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c LayoutInfo
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LayoutInfo -> c LayoutInfo
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LayoutInfo -> c LayoutInfo
Data)

-- | Indentation level is 1-indexed, so the leftmost column is 1.
leftmostColumn :: Int
leftmostColumn :: Int
leftmostColumn = Int
1