{-# LANGUAGE OverloadedStrings #-}
module Text.Parser.Input.Position (Position, fromStart, fromEnd,
offset, context, lineAndColumn) where
import Data.Char (isSpace)
import Data.String (IsString(fromString))
import qualified Data.Monoid.Factorial as Factorial
import qualified Data.Monoid.Textual as Textual
import Data.Monoid.Factorial (FactorialMonoid)
import Data.Monoid.Textual (TextualMonoid)
data Position = PositionFromStart !Int
| PositionFromEnd Int
deriving (Eq, Read, Show)
fromStart :: Int -> Position
fromStart = PositionFromStart
fromEnd :: Int -> Position
fromEnd = PositionFromEnd
offset :: FactorialMonoid s => s -> Position -> Int
offset wholeInput (PositionFromStart offset) = offset
offset wholeInput (PositionFromEnd remainderLength) = Factorial.length wholeInput - remainderLength
{-# INLINE offset #-}
context :: (Eq s, TextualMonoid s) => s -> Position -> Int -> s
context input pos contextLineCount =
foldMap (<> "\n") prevLines <> lastLinePadding
<> "at line " <> fromString (show $ length allPrevLines) <> ", column " <> fromString (show $ column+1) <> "\n"
where (allPrevLines, column) = lineAndColumn input pos
lastLinePadding
| (lastLine:_) <- allPrevLines, paddingPrefix <- Textual.takeWhile_ False isSpace lastLine =
Factorial.take column (paddingPrefix <> fromString (replicate column ' ')) <> "^\n"
| otherwise = ""
prevLines = reverse (take contextLineCount allPrevLines)
lineAndColumn :: (Eq s, IsString s, FactorialMonoid s) => s -> Position -> ([s], Int)
lineAndColumn input pos = context [] (offset input pos) (Factorial.split (== "\n") input)
where context revLines restCount []
| restCount > 0 = (["Error: the offset is beyond the input length"], -1)
| otherwise = (revLines, restCount)
context revLines restCount (next:rest)
| restCount' < 0 = (next:revLines, restCount)
| otherwise = context (next:revLines) restCount' rest
where nextLength = Factorial.length next
restCount' = restCount - nextLength - 1