{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE Safe #-}
module Text.Parsec.Pos
    ( SourceName, Line, Column
    , SourcePos
    , sourceLine, sourceColumn, sourceName
    , incSourceLine, incSourceColumn
    , setSourceLine, setSourceColumn, setSourceName
    , newPos, initialPos
    , updatePosChar, updatePosString
    ) where
import Data.Data (Data)
import Data.Typeable (Typeable)
type SourceName = String
type Line       = Int
type Column     = Int
data SourcePos  = SourcePos SourceName !Line !Column
    deriving ( 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.
    Line -> (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. Line -> (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. Line -> (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. Line -> (forall d. Data d => d -> u) -> SourcePos -> u
gmapQi :: forall u. Line -> (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)
newPos :: SourceName -> Line -> Column -> SourcePos
newPos :: SourceName -> Line -> Line -> SourcePos
newPos SourceName
name Line
line Line
column
    = SourceName -> Line -> Line -> SourcePos
SourcePos SourceName
name Line
line Line
column
initialPos :: SourceName -> SourcePos
initialPos :: SourceName -> SourcePos
initialPos SourceName
name
    = SourceName -> Line -> Line -> SourcePos
newPos SourceName
name Line
1 Line
1
sourceName :: SourcePos -> SourceName
sourceName :: SourcePos -> SourceName
sourceName (SourcePos SourceName
name Line
_line Line
_column) = SourceName
name
sourceLine :: SourcePos -> Line
sourceLine :: SourcePos -> Line
sourceLine (SourcePos SourceName
_name Line
line Line
_column) = Line
line
sourceColumn :: SourcePos -> Column
sourceColumn :: SourcePos -> Line
sourceColumn (SourcePos SourceName
_name Line
_line Line
column) = Line
column
incSourceLine :: SourcePos -> Line -> SourcePos
incSourceLine :: SourcePos -> Line -> SourcePos
incSourceLine (SourcePos SourceName
name Line
line Line
column) Line
n = SourceName -> Line -> Line -> SourcePos
SourcePos SourceName
name (Line
lineLine -> Line -> Line
forall a. Num a => a -> a -> a
+Line
n) Line
column
incSourceColumn :: SourcePos -> Column -> SourcePos
incSourceColumn :: SourcePos -> Line -> SourcePos
incSourceColumn (SourcePos SourceName
name Line
line Line
column) Line
n = SourceName -> Line -> Line -> SourcePos
SourcePos SourceName
name Line
line (Line
columnLine -> Line -> Line
forall a. Num a => a -> a -> a
+Line
n)
setSourceName :: SourcePos -> SourceName -> SourcePos
setSourceName :: SourcePos -> SourceName -> SourcePos
setSourceName (SourcePos SourceName
_name Line
line Line
column) SourceName
n = SourceName -> Line -> Line -> SourcePos
SourcePos SourceName
n Line
line Line
column
setSourceLine :: SourcePos -> Line -> SourcePos
setSourceLine :: SourcePos -> Line -> SourcePos
setSourceLine (SourcePos SourceName
name Line
_line Line
column) Line
n = SourceName -> Line -> Line -> SourcePos
SourcePos SourceName
name Line
n Line
column
setSourceColumn :: SourcePos -> Column -> SourcePos
setSourceColumn :: SourcePos -> Line -> SourcePos
setSourceColumn (SourcePos SourceName
name Line
line Line
_column) Line
n = SourceName -> Line -> Line -> SourcePos
SourcePos SourceName
name Line
line Line
n
updatePosString :: SourcePos -> String -> SourcePos
updatePosString :: SourcePos -> SourceName -> SourcePos
updatePosString SourcePos
pos SourceName
string
    = (SourcePos -> Char -> SourcePos)
-> SourcePos -> SourceName -> SourcePos
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl SourcePos -> Char -> SourcePos
updatePosChar SourcePos
pos SourceName
string
updatePosChar   :: SourcePos -> Char -> SourcePos
updatePosChar :: SourcePos -> Char -> SourcePos
updatePosChar (SourcePos SourceName
name Line
line Line
column) Char
c
    = case Char
c of
        Char
'\n' -> SourceName -> Line -> Line -> SourcePos
SourcePos SourceName
name (Line
lineLine -> Line -> Line
forall a. Num a => a -> a -> a
+Line
1) Line
1
        Char
'\t' -> SourceName -> Line -> Line -> SourcePos
SourcePos SourceName
name Line
line (Line
column Line -> Line -> Line
forall a. Num a => a -> a -> a
+ Line
8 Line -> Line -> Line
forall a. Num a => a -> a -> a
- ((Line
columnLine -> Line -> Line
forall a. Num a => a -> a -> a
-Line
1) Line -> Line -> Line
forall a. Integral a => a -> a -> a
`mod` Line
8))
        Char
_    -> SourceName -> Line -> Line -> SourcePos
SourcePos SourceName
name Line
line (Line
column Line -> Line -> Line
forall a. Num a => a -> a -> a
+ Line
1)
instance Show SourcePos where
  show :: SourcePos -> SourceName
show (SourcePos SourceName
name Line
line Line
column)
    | SourceName -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null SourceName
name = SourceName
showLineColumn
    | Bool
otherwise = SourceName
"\"" SourceName -> ShowS
forall a. [a] -> [a] -> [a]
++ SourceName
name SourceName -> ShowS
forall a. [a] -> [a] -> [a]
++ SourceName
"\" " SourceName -> ShowS
forall a. [a] -> [a] -> [a]
++ SourceName
showLineColumn
    where
      showLineColumn :: SourceName
showLineColumn    = SourceName
"(line " SourceName -> ShowS
forall a. [a] -> [a] -> [a]
++ Line -> SourceName
forall a. Show a => a -> SourceName
show Line
line SourceName -> ShowS
forall a. [a] -> [a] -> [a]
++
                          SourceName
", column " SourceName -> ShowS
forall a. [a] -> [a] -> [a]
++ Line -> SourceName
forall a. Show a => a -> SourceName
show Line
column SourceName -> ShowS
forall a. [a] -> [a] -> [a]
++
                          SourceName
")"