{-|
Module      : Toml.Syntax.Position
Description : File position representation
Copyright   : (c) Eric Mertens, 2023
License     : ISC
Maintainer  : emertens@gmail.com

This module provides the 'Position' type for tracking locations
in files while doing lexing and parsing for providing more useful
error messages.

This module assumes 8 column wide tab stops.

-}
module Toml.Syntax.Position (
    Located(..),
    Position(..),
    startPos,
    move,
    ) where

-- | A value annotated with its text file position
data Located a = Located
    { forall a. Located a -> Position
locPosition :: {-# UNPACK #-} !Position -- ^ position
    , forall a. Located a -> a
locThing    :: !a -- ^ thing at position
    }
    deriving (
        ReadPrec [Located a]
ReadPrec (Located a)
Int -> ReadS (Located a)
ReadS [Located a]
(Int -> ReadS (Located a))
-> ReadS [Located a]
-> ReadPrec (Located a)
-> ReadPrec [Located a]
-> Read (Located a)
forall a. Read a => ReadPrec [Located a]
forall a. Read a => ReadPrec (Located a)
forall a. Read a => Int -> ReadS (Located a)
forall a. Read a => ReadS [Located a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: forall a. Read a => Int -> ReadS (Located a)
readsPrec :: Int -> ReadS (Located a)
$creadList :: forall a. Read a => ReadS [Located a]
readList :: ReadS [Located a]
$creadPrec :: forall a. Read a => ReadPrec (Located a)
readPrec :: ReadPrec (Located a)
$creadListPrec :: forall a. Read a => ReadPrec [Located a]
readListPrec :: ReadPrec [Located a]
Read        {- ^ Default instance -},
        Int -> Located a -> ShowS
[Located a] -> ShowS
Located a -> String
(Int -> Located a -> ShowS)
-> (Located a -> String)
-> ([Located a] -> ShowS)
-> Show (Located a)
forall a. Show a => Int -> Located a -> ShowS
forall a. Show a => [Located a] -> ShowS
forall a. Show a => Located a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> Located a -> ShowS
showsPrec :: Int -> Located a -> ShowS
$cshow :: forall a. Show a => Located a -> String
show :: Located a -> String
$cshowList :: forall a. Show a => [Located a] -> ShowS
showList :: [Located a] -> ShowS
Show        {- ^ Default instance -},
        (forall a b. (a -> b) -> Located a -> Located b)
-> (forall a b. a -> Located b -> Located a) -> Functor Located
forall a b. a -> Located b -> Located a
forall a b. (a -> b) -> Located a -> Located b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> Located a -> Located b
fmap :: forall a b. (a -> b) -> Located a -> Located b
$c<$ :: forall a b. a -> Located b -> Located a
<$ :: forall a b. a -> Located b -> Located a
Functor     {- ^ Default instance -},
        (forall m. Monoid m => Located m -> m)
-> (forall m a. Monoid m => (a -> m) -> Located a -> m)
-> (forall m a. Monoid m => (a -> m) -> Located a -> m)
-> (forall a b. (a -> b -> b) -> b -> Located a -> b)
-> (forall a b. (a -> b -> b) -> b -> Located a -> b)
-> (forall b a. (b -> a -> b) -> b -> Located a -> b)
-> (forall b a. (b -> a -> b) -> b -> Located a -> b)
-> (forall a. (a -> a -> a) -> Located a -> a)
-> (forall a. (a -> a -> a) -> Located a -> a)
-> (forall a. Located a -> [a])
-> (forall a. Located a -> Bool)
-> (forall a. Located a -> Int)
-> (forall a. Eq a => a -> Located a -> Bool)
-> (forall a. Ord a => Located a -> a)
-> (forall a. Ord a => Located a -> a)
-> (forall a. Num a => Located a -> a)
-> (forall a. Num a => Located a -> a)
-> Foldable Located
forall a. Eq a => a -> Located a -> Bool
forall a. Num a => Located a -> a
forall a. Ord a => Located a -> a
forall m. Monoid m => Located m -> m
forall a. Located a -> Bool
forall a. Located a -> Int
forall a. Located a -> [a]
forall a. (a -> a -> a) -> Located a -> a
forall m a. Monoid m => (a -> m) -> Located a -> m
forall b a. (b -> a -> b) -> b -> Located a -> b
forall a b. (a -> b -> b) -> b -> Located 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
$cfold :: forall m. Monoid m => Located m -> m
fold :: forall m. Monoid m => Located m -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> Located a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> Located a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> Located a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> Located a -> m
$cfoldr :: forall a b. (a -> b -> b) -> b -> Located a -> b
foldr :: forall a b. (a -> b -> b) -> b -> Located a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> Located a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> Located a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> Located a -> b
foldl :: forall b a. (b -> a -> b) -> b -> Located a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> Located a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> Located a -> b
$cfoldr1 :: forall a. (a -> a -> a) -> Located a -> a
foldr1 :: forall a. (a -> a -> a) -> Located a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> Located a -> a
foldl1 :: forall a. (a -> a -> a) -> Located a -> a
$ctoList :: forall a. Located a -> [a]
toList :: forall a. Located a -> [a]
$cnull :: forall a. Located a -> Bool
null :: forall a. Located a -> Bool
$clength :: forall a. Located a -> Int
length :: forall a. Located a -> Int
$celem :: forall a. Eq a => a -> Located a -> Bool
elem :: forall a. Eq a => a -> Located a -> Bool
$cmaximum :: forall a. Ord a => Located a -> a
maximum :: forall a. Ord a => Located a -> a
$cminimum :: forall a. Ord a => Located a -> a
minimum :: forall a. Ord a => Located a -> a
$csum :: forall a. Num a => Located a -> a
sum :: forall a. Num a => Located a -> a
$cproduct :: forall a. Num a => Located a -> a
product :: forall a. Num a => Located a -> a
Foldable    {- ^ Default instance -},
        Functor Located
Foldable Located
(Functor Located, Foldable Located) =>
(forall (f :: * -> *) a b.
 Applicative f =>
 (a -> f b) -> Located a -> f (Located b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    Located (f a) -> f (Located a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> Located a -> m (Located b))
-> (forall (m :: * -> *) a.
    Monad m =>
    Located (m a) -> m (Located a))
-> Traversable Located
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 => Located (m a) -> m (Located a)
forall (f :: * -> *) a.
Applicative f =>
Located (f a) -> f (Located a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Located a -> m (Located b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Located a -> f (Located b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Located a -> f (Located b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Located a -> f (Located b)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
Located (f a) -> f (Located a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
Located (f a) -> f (Located a)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Located a -> m (Located b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Located a -> m (Located b)
$csequence :: forall (m :: * -> *) a. Monad m => Located (m a) -> m (Located a)
sequence :: forall (m :: * -> *) a. Monad m => Located (m a) -> m (Located a)
Traversable {- ^ Default instance -})

-- | A position in a text file
data Position = Position {
    Position -> Int
posIndex  :: {-# UNPACK #-} !Int, -- ^ code-point index (zero-based)
    Position -> Int
posLine   :: {-# UNPACK #-} !Int, -- ^ line index (one-based)
    Position -> Int
posColumn :: {-# UNPACK #-} !Int  -- ^ column index (one-based)
    } deriving (
        ReadPrec [Position]
ReadPrec Position
Int -> ReadS Position
ReadS [Position]
(Int -> ReadS Position)
-> ReadS [Position]
-> ReadPrec Position
-> ReadPrec [Position]
-> Read Position
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Position
readsPrec :: Int -> ReadS Position
$creadList :: ReadS [Position]
readList :: ReadS [Position]
$creadPrec :: ReadPrec Position
readPrec :: ReadPrec Position
$creadListPrec :: ReadPrec [Position]
readListPrec :: ReadPrec [Position]
Read    {- ^ Default instance -},
        Int -> Position -> ShowS
[Position] -> ShowS
Position -> String
(Int -> Position -> ShowS)
-> (Position -> String) -> ([Position] -> ShowS) -> Show Position
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Position -> ShowS
showsPrec :: Int -> Position -> ShowS
$cshow :: Position -> String
show :: Position -> String
$cshowList :: [Position] -> ShowS
showList :: [Position] -> ShowS
Show    {- ^ Default instance -},
        Eq Position
Eq Position =>
(Position -> Position -> Ordering)
-> (Position -> Position -> Bool)
-> (Position -> Position -> Bool)
-> (Position -> Position -> Bool)
-> (Position -> Position -> Bool)
-> (Position -> Position -> Position)
-> (Position -> Position -> Position)
-> Ord Position
Position -> Position -> Bool
Position -> Position -> Ordering
Position -> Position -> Position
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 :: Position -> Position -> Ordering
compare :: Position -> Position -> Ordering
$c< :: Position -> Position -> Bool
< :: Position -> Position -> Bool
$c<= :: Position -> Position -> Bool
<= :: Position -> Position -> Bool
$c> :: Position -> Position -> Bool
> :: Position -> Position -> Bool
$c>= :: Position -> Position -> Bool
>= :: Position -> Position -> Bool
$cmax :: Position -> Position -> Position
max :: Position -> Position -> Position
$cmin :: Position -> Position -> Position
min :: Position -> Position -> Position
Ord     {- ^ Default instance -},
        Position -> Position -> Bool
(Position -> Position -> Bool)
-> (Position -> Position -> Bool) -> Eq Position
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Position -> Position -> Bool
== :: Position -> Position -> Bool
$c/= :: Position -> Position -> Bool
/= :: Position -> Position -> Bool
Eq      {- ^ Default instance -})

-- | The initial 'Position' for the start of a file
startPos :: Position
startPos :: Position
startPos = Position { posIndex :: Int
posIndex = Int
0, posLine :: Int
posLine = Int
1, posColumn :: Int
posColumn = Int
1 }

-- | Adjust a file position given a single character handling
-- newlines and tabs. All other characters are considered to fill
-- exactly one column.
move :: Char -> Position -> Position
move :: Char -> Position -> Position
move Char
x Position{ posIndex :: Position -> Int
posIndex = Int
i, posLine :: Position -> Int
posLine = Int
l, posColumn :: Position -> Int
posColumn = Int
c} =
    case Char
x of
        Char
'\n' -> Position{ posIndex :: Int
posIndex = Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1, posLine :: Int
posLine = Int
lInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1, posColumn :: Int
posColumn = Int
1 }
        Char
'\t' -> Position{ posIndex :: Int
posIndex = Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1, posLine :: Int
posLine = Int
l, posColumn :: Int
posColumn = (Int
c Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
7) Int -> Int -> Int
forall a. Integral a => a -> a -> a
`quot` Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1 }
        Char
_    -> Position{ posIndex :: Int
posIndex = Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1, posLine :: Int
posLine = Int
l, posColumn :: Int
posColumn = Int
cInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1 }