module Language.Haskell.Lexer.Position where

-- | The posisiotn within a file.
data Pos = Pos { Pos -> Int
char, Pos -> Int
line, Pos -> Int
column :: !Int } deriving (Int -> Pos -> ShowS
[Pos] -> ShowS
Pos -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Pos] -> ShowS
$cshowList :: [Pos] -> ShowS
show :: Pos -> String
$cshow :: Pos -> String
showsPrec :: Int -> Pos -> ShowS
$cshowsPrec :: Int -> Pos -> ShowS
Show)

-- | The line and column numbers of a position.
simpPos :: Pos -> (Int,Int)
simpPos :: Pos -> (Int, Int)
simpPos (Pos Int
_ Int
l Int
c) = (Int
l,Int
c)

-- Some functions still put fake char positions in Pos values, so...
instance Eq Pos where Pos
p1 == :: Pos -> Pos -> Bool
== Pos
p2 = Pos -> (Int, Int)
simpPos Pos
p1 forall a. Eq a => a -> a -> Bool
== Pos -> (Int, Int)
simpPos Pos
p2
instance Ord Pos where compare :: Pos -> Pos -> Ordering
compare Pos
p1 Pos
p2 = forall a. Ord a => a -> a -> Ordering
compare (Pos -> (Int, Int)
simpPos Pos
p1) (Pos -> (Int, Int)
simpPos Pos
p2)

-- | The first column is designated column 1, not 0.
startPos :: Pos
startPos :: Pos
startPos = Pos { char :: Int
char = Int
0, line :: Int
line = Int
1, column :: Int
column = Int
1 }

-- | Advance position by a string.
nextPos :: Pos -> String -> Pos
nextPos :: Pos -> String -> Pos
nextPos = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl Pos -> Char -> Pos
nextPos1

-- | Advance position by a single character.
nextPos1 :: Pos -> Char -> Pos
nextPos1 :: Pos -> Char -> Pos
nextPos1 (Pos Int
n Int
y Int
x) Char
c =
    case Char
c of
      -- The characters newline, return, linefeed, and formfeed, all start
      -- a new line.
      Char
'\CR' -> Int -> Int -> Int -> Pos
Pos (Int
nforall a. Num a => a -> a -> a
+Int
1) (Int
yforall a. Num a => a -> a -> a
+Int
1) Int
1
      Char
'\LF' -> Int -> Int -> Int -> Pos
Pos (Int
nforall a. Num a => a -> a -> a
+Int
1) (Int
yforall a. Num a => a -> a -> a
+Int
1) Int
1
      Char
'\FF' -> Int -> Int -> Int -> Pos
Pos (Int
nforall a. Num a => a -> a -> a
+Int
1) (Int
yforall a. Num a => a -> a -> a
+Int
1) Int
1
      -- Tab stops are 8 characters apart.
      -- A tab character causes the insertion of enough spaces to align the
      -- current position with the next tab stop.
      -- + (not in the report) the first tab stop is column 1.
      Char
'\t'  -> Int -> Int -> Int -> Pos
Pos (Int
nforall a. Num a => a -> a -> a
+Int
1) Int
y (Int
xforall a. Num a => a -> a -> a
+Int
8forall a. Num a => a -> a -> a
-(Int
xforall a. Num a => a -> a -> a
-Int
1) forall a. Integral a => a -> a -> a
`mod` Int
8)
      Char
_ -> Int -> Int -> Int -> Pos
Pos (Int
nforall a. Num a => a -> a -> a
+Int
1) Int
y (Int
xforall a. Num a => a -> a -> a
+Int
1)