{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE Safe #-}
module Text.Megaparsec.Pos
  ( 
    Pos,
    mkPos,
    unPos,
    pos1,
    defaultTabWidth,
    InvalidPosException (..),
    
    SourcePos (..),
    initialPos,
    sourcePosPretty,
  )
where
import Control.DeepSeq
import Control.Exception
import Data.Data (Data)
import Data.Typeable (Typeable)
import GHC.Generics
newtype Pos = Pos Int
  deriving (Int -> Pos -> ShowS
[Pos] -> ShowS
Pos -> String
(Int -> Pos -> ShowS)
-> (Pos -> String) -> ([Pos] -> ShowS) -> Show Pos
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Pos -> ShowS
showsPrec :: Int -> Pos -> ShowS
$cshow :: Pos -> String
show :: Pos -> String
$cshowList :: [Pos] -> ShowS
showList :: [Pos] -> ShowS
Show, Pos -> Pos -> Bool
(Pos -> Pos -> Bool) -> (Pos -> Pos -> Bool) -> Eq Pos
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Pos -> Pos -> Bool
== :: Pos -> Pos -> Bool
$c/= :: Pos -> Pos -> Bool
/= :: Pos -> Pos -> Bool
Eq, Eq Pos
Eq Pos =>
(Pos -> Pos -> Ordering)
-> (Pos -> Pos -> Bool)
-> (Pos -> Pos -> Bool)
-> (Pos -> Pos -> Bool)
-> (Pos -> Pos -> Bool)
-> (Pos -> Pos -> Pos)
-> (Pos -> Pos -> Pos)
-> Ord Pos
Pos -> Pos -> Bool
Pos -> Pos -> Ordering
Pos -> Pos -> Pos
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
$ccompare :: Pos -> Pos -> Ordering
compare :: Pos -> Pos -> Ordering
$c< :: Pos -> Pos -> Bool
< :: Pos -> Pos -> Bool
$c<= :: Pos -> Pos -> Bool
<= :: Pos -> Pos -> Bool
$c> :: Pos -> Pos -> Bool
> :: Pos -> Pos -> Bool
$c>= :: Pos -> Pos -> Bool
>= :: Pos -> Pos -> Bool
$cmax :: Pos -> Pos -> Pos
max :: Pos -> Pos -> Pos
$cmin :: Pos -> Pos -> Pos
min :: Pos -> Pos -> Pos
Ord, Typeable Pos
Typeable Pos =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Pos -> c Pos)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Pos)
-> (Pos -> Constr)
-> (Pos -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Pos))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pos))
-> ((forall b. Data b => b -> b) -> Pos -> Pos)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pos -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pos -> r)
-> (forall u. (forall d. Data d => d -> u) -> Pos -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Pos -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Pos -> m Pos)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Pos -> m Pos)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Pos -> m Pos)
-> Data Pos
Pos -> Constr
Pos -> DataType
(forall b. Data b => b -> b) -> Pos -> Pos
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) -> Pos -> u
forall u. (forall d. Data d => d -> u) -> Pos -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pos -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pos -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Pos -> m Pos
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Pos -> m Pos
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Pos
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Pos -> c Pos
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Pos)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pos)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Pos -> c Pos
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Pos -> c Pos
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Pos
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Pos
$ctoConstr :: Pos -> Constr
toConstr :: Pos -> Constr
$cdataTypeOf :: Pos -> DataType
dataTypeOf :: Pos -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Pos)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Pos)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pos)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pos)
$cgmapT :: (forall b. Data b => b -> b) -> Pos -> Pos
gmapT :: (forall b. Data b => b -> b) -> Pos -> Pos
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pos -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pos -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pos -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pos -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Pos -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Pos -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Pos -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Pos -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Pos -> m Pos
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Pos -> m Pos
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Pos -> m Pos
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Pos -> m Pos
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Pos -> m Pos
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Pos -> m Pos
Data, (forall x. Pos -> Rep Pos x)
-> (forall x. Rep Pos x -> Pos) -> Generic Pos
forall x. Rep Pos x -> Pos
forall x. Pos -> Rep Pos x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Pos -> Rep Pos x
from :: forall x. Pos -> Rep Pos x
$cto :: forall x. Rep Pos x -> Pos
to :: forall x. Rep Pos x -> Pos
Generic, Typeable, Pos -> ()
(Pos -> ()) -> NFData Pos
forall a. (a -> ()) -> NFData a
$crnf :: Pos -> ()
rnf :: Pos -> ()
NFData)
mkPos :: Int -> Pos
mkPos :: Int -> Pos
mkPos Int
a =
  if Int
a Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0
    then InvalidPosException -> Pos
forall a e. Exception e => e -> a
throw (Int -> InvalidPosException
InvalidPosException Int
a)
    else Int -> Pos
Pos Int
a
{-# INLINE mkPos #-}
unPos :: Pos -> Int
unPos :: Pos -> Int
unPos (Pos Int
w) = Int
w
{-# INLINE unPos #-}
pos1 :: Pos
pos1 :: Pos
pos1 = Int -> Pos
mkPos Int
1
defaultTabWidth :: Pos
defaultTabWidth :: Pos
defaultTabWidth = Int -> Pos
mkPos Int
8
instance Semigroup Pos where
  (Pos Int
x) <> :: Pos -> Pos -> Pos
<> (Pos Int
y) = Int -> Pos
Pos (Int
x Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
y)
  {-# INLINE (<>) #-}
instance Read Pos where
  readsPrec :: Int -> ReadS Pos
readsPrec Int
d =
    Bool -> ReadS Pos -> ReadS Pos
forall a. Bool -> ReadS a -> ReadS a
readParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) (ReadS Pos -> ReadS Pos) -> ReadS Pos -> ReadS Pos
forall a b. (a -> b) -> a -> b
$ \String
r1 -> do
      (String
"Pos", String
r2) <- ReadS String
lex String
r1
      (Int
x, String
r3) <- Int -> ReadS Int
forall a. Read a => Int -> ReadS a
readsPrec Int
11 String
r2
      (Pos, String) -> [(Pos, String)]
forall a. a -> [a]
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> Pos
mkPos Int
x, String
r3)
newtype InvalidPosException
  = 
    InvalidPosException Int
  deriving (InvalidPosException -> InvalidPosException -> Bool
(InvalidPosException -> InvalidPosException -> Bool)
-> (InvalidPosException -> InvalidPosException -> Bool)
-> Eq InvalidPosException
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InvalidPosException -> InvalidPosException -> Bool
== :: InvalidPosException -> InvalidPosException -> Bool
$c/= :: InvalidPosException -> InvalidPosException -> Bool
/= :: InvalidPosException -> InvalidPosException -> Bool
Eq, Int -> InvalidPosException -> ShowS
[InvalidPosException] -> ShowS
InvalidPosException -> String
(Int -> InvalidPosException -> ShowS)
-> (InvalidPosException -> String)
-> ([InvalidPosException] -> ShowS)
-> Show InvalidPosException
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InvalidPosException -> ShowS
showsPrec :: Int -> InvalidPosException -> ShowS
$cshow :: InvalidPosException -> String
show :: InvalidPosException -> String
$cshowList :: [InvalidPosException] -> ShowS
showList :: [InvalidPosException] -> ShowS
Show, Typeable InvalidPosException
Typeable InvalidPosException =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g)
 -> InvalidPosException
 -> c InvalidPosException)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c InvalidPosException)
-> (InvalidPosException -> Constr)
-> (InvalidPosException -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c InvalidPosException))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c InvalidPosException))
-> ((forall b. Data b => b -> b)
    -> InvalidPosException -> InvalidPosException)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> InvalidPosException -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> InvalidPosException -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> InvalidPosException -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> InvalidPosException -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> InvalidPosException -> m InvalidPosException)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> InvalidPosException -> m InvalidPosException)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> InvalidPosException -> m InvalidPosException)
-> Data InvalidPosException
InvalidPosException -> Constr
InvalidPosException -> DataType
(forall b. Data b => b -> b)
-> InvalidPosException -> InvalidPosException
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) -> InvalidPosException -> u
forall u.
(forall d. Data d => d -> u) -> InvalidPosException -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> InvalidPosException -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> InvalidPosException -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> InvalidPosException -> m InvalidPosException
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> InvalidPosException -> m InvalidPosException
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c InvalidPosException
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> InvalidPosException
-> c InvalidPosException
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c InvalidPosException)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c InvalidPosException)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> InvalidPosException
-> c InvalidPosException
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> InvalidPosException
-> c InvalidPosException
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c InvalidPosException
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c InvalidPosException
$ctoConstr :: InvalidPosException -> Constr
toConstr :: InvalidPosException -> Constr
$cdataTypeOf :: InvalidPosException -> DataType
dataTypeOf :: InvalidPosException -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c InvalidPosException)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c InvalidPosException)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c InvalidPosException)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c InvalidPosException)
$cgmapT :: (forall b. Data b => b -> b)
-> InvalidPosException -> InvalidPosException
gmapT :: (forall b. Data b => b -> b)
-> InvalidPosException -> InvalidPosException
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> InvalidPosException -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> InvalidPosException -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> InvalidPosException -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> InvalidPosException -> r
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> InvalidPosException -> [u]
gmapQ :: forall u.
(forall d. Data d => d -> u) -> InvalidPosException -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> InvalidPosException -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> InvalidPosException -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> InvalidPosException -> m InvalidPosException
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> InvalidPosException -> m InvalidPosException
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> InvalidPosException -> m InvalidPosException
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> InvalidPosException -> m InvalidPosException
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> InvalidPosException -> m InvalidPosException
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> InvalidPosException -> m InvalidPosException
Data, Typeable, (forall x. InvalidPosException -> Rep InvalidPosException x)
-> (forall x. Rep InvalidPosException x -> InvalidPosException)
-> Generic InvalidPosException
forall x. Rep InvalidPosException x -> InvalidPosException
forall x. InvalidPosException -> Rep InvalidPosException x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. InvalidPosException -> Rep InvalidPosException x
from :: forall x. InvalidPosException -> Rep InvalidPosException x
$cto :: forall x. Rep InvalidPosException x -> InvalidPosException
to :: forall x. Rep InvalidPosException x -> InvalidPosException
Generic)
instance Exception InvalidPosException
instance NFData InvalidPosException
data SourcePos = SourcePos
  { 
    SourcePos -> String
sourceName :: FilePath,
    
    SourcePos -> Pos
sourceLine :: !Pos,
    
    SourcePos -> Pos
sourceColumn :: !Pos
  }
  deriving (Int -> SourcePos -> ShowS
[SourcePos] -> ShowS
SourcePos -> String
(Int -> SourcePos -> ShowS)
-> (SourcePos -> String)
-> ([SourcePos] -> ShowS)
-> Show SourcePos
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SourcePos -> ShowS
showsPrec :: Int -> SourcePos -> ShowS
$cshow :: SourcePos -> String
show :: SourcePos -> String
$cshowList :: [SourcePos] -> ShowS
showList :: [SourcePos] -> ShowS
Show, ReadPrec [SourcePos]
ReadPrec SourcePos
Int -> ReadS SourcePos
ReadS [SourcePos]
(Int -> ReadS SourcePos)
-> ReadS [SourcePos]
-> ReadPrec SourcePos
-> ReadPrec [SourcePos]
-> Read SourcePos
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS SourcePos
readsPrec :: Int -> ReadS SourcePos
$creadList :: ReadS [SourcePos]
readList :: ReadS [SourcePos]
$creadPrec :: ReadPrec SourcePos
readPrec :: ReadPrec SourcePos
$creadListPrec :: ReadPrec [SourcePos]
readListPrec :: ReadPrec [SourcePos]
Read, SourcePos -> SourcePos -> Bool
(SourcePos -> SourcePos -> Bool)
-> (SourcePos -> SourcePos -> Bool) -> Eq SourcePos
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SourcePos -> SourcePos -> Bool
== :: SourcePos -> SourcePos -> Bool
$c/= :: SourcePos -> SourcePos -> Bool
/= :: SourcePos -> SourcePos -> Bool
Eq, Eq SourcePos
Eq SourcePos =>
(SourcePos -> SourcePos -> Ordering)
-> (SourcePos -> SourcePos -> Bool)
-> (SourcePos -> SourcePos -> Bool)
-> (SourcePos -> SourcePos -> Bool)
-> (SourcePos -> SourcePos -> Bool)
-> (SourcePos -> SourcePos -> SourcePos)
-> (SourcePos -> SourcePos -> SourcePos)
-> Ord SourcePos
SourcePos -> SourcePos -> Bool
SourcePos -> SourcePos -> Ordering
SourcePos -> SourcePos -> SourcePos
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
$ccompare :: SourcePos -> SourcePos -> Ordering
compare :: SourcePos -> SourcePos -> Ordering
$c< :: SourcePos -> SourcePos -> Bool
< :: SourcePos -> SourcePos -> Bool
$c<= :: SourcePos -> SourcePos -> Bool
<= :: SourcePos -> SourcePos -> Bool
$c> :: SourcePos -> SourcePos -> Bool
> :: SourcePos -> SourcePos -> Bool
$c>= :: SourcePos -> SourcePos -> Bool
>= :: SourcePos -> SourcePos -> Bool
$cmax :: SourcePos -> SourcePos -> SourcePos
max :: SourcePos -> SourcePos -> SourcePos
$cmin :: SourcePos -> SourcePos -> SourcePos
min :: SourcePos -> SourcePos -> SourcePos
Ord, Typeable SourcePos
Typeable SourcePos =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> SourcePos -> c SourcePos)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c SourcePos)
-> (SourcePos -> Constr)
-> (SourcePos -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c SourcePos))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SourcePos))
-> ((forall b. Data b => b -> b) -> SourcePos -> SourcePos)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> SourcePos -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> SourcePos -> r)
-> (forall u. (forall d. Data d => d -> u) -> SourcePos -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> SourcePos -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> SourcePos -> m SourcePos)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> SourcePos -> m SourcePos)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> SourcePos -> m SourcePos)
-> Data SourcePos
SourcePos -> Constr
SourcePos -> DataType
(forall b. Data b => b -> b) -> SourcePos -> SourcePos
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) -> SourcePos -> u
forall u. (forall d. Data d => d -> u) -> SourcePos -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SourcePos -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SourcePos -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SourcePos -> m SourcePos
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SourcePos -> m SourcePos
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SourcePos
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SourcePos -> c SourcePos
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SourcePos)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SourcePos)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SourcePos -> c SourcePos
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SourcePos -> c SourcePos
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SourcePos
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SourcePos
$ctoConstr :: SourcePos -> Constr
toConstr :: SourcePos -> Constr
$cdataTypeOf :: SourcePos -> DataType
dataTypeOf :: SourcePos -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SourcePos)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SourcePos)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SourcePos)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SourcePos)
$cgmapT :: (forall b. Data b => b -> b) -> SourcePos -> SourcePos
gmapT :: (forall b. Data b => b -> b) -> SourcePos -> SourcePos
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SourcePos -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SourcePos -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SourcePos -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SourcePos -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> SourcePos -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> SourcePos -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> SourcePos -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> SourcePos -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SourcePos -> m SourcePos
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SourcePos -> m SourcePos
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SourcePos -> m SourcePos
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SourcePos -> m SourcePos
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SourcePos -> m SourcePos
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SourcePos -> m SourcePos
Data, Typeable, (forall x. SourcePos -> Rep SourcePos x)
-> (forall x. Rep SourcePos x -> SourcePos) -> Generic SourcePos
forall x. Rep SourcePos x -> SourcePos
forall x. SourcePos -> Rep SourcePos x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SourcePos -> Rep SourcePos x
from :: forall x. SourcePos -> Rep SourcePos x
$cto :: forall x. Rep SourcePos x -> SourcePos
to :: forall x. Rep SourcePos x -> SourcePos
Generic)
instance NFData SourcePos
initialPos :: FilePath -> SourcePos
initialPos :: String -> SourcePos
initialPos String
n = String -> Pos -> Pos -> SourcePos
SourcePos String
n Pos
pos1 Pos
pos1
sourcePosPretty :: SourcePos -> String
sourcePosPretty :: SourcePos -> String
sourcePosPretty (SourcePos String
n Pos
l Pos
c)
  | String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
n = String
showLC
  | Bool
otherwise = String
n String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
":" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
showLC
  where
    showLC :: String
showLC = Int -> String
forall a. Show a => a -> String
show (Pos -> Int
unPos Pos
l) String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
":" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Int -> String
forall a. Show a => a -> String
show (Pos -> Int
unPos Pos
c)