{-# LANGUAGE FlexibleContexts, KindSignatures, OverloadedStrings, RankNTypes, ScopedTypeVariables #-}
module Text.Grampa (
MultiParsing(..),
offsetContext, offsetLineAndColumn, positionOffset, failureDescription, simply,
Grammar, GrammarBuilder, ParseResults, ParseFailure(..), Ambiguous(..), Position,
GrammarParsing(..), MonoidParsing(..), AmbiguousParsing(..), Lexical(..),
module Text.Parser.Char,
module Text.Parser.Combinators,
module Text.Parser.LookAhead)
where
import Data.List (intersperse)
import Data.Monoid ((<>))
import qualified Data.Monoid.Factorial as Factorial
import Data.Monoid.Factorial (FactorialMonoid)
import Data.String (IsString(fromString))
import Text.Parser.Char (CharParsing(char, notChar, anyChar))
import Text.Parser.Combinators (Parsing((<?>), notFollowedBy, skipMany, skipSome, unexpected))
import Text.Parser.LookAhead (LookAheadParsing(lookAhead))
import qualified Rank2
import Text.Grampa.Class (Lexical(..), MultiParsing(..), GrammarParsing(..), MonoidParsing(..), AmbiguousParsing(..),
Ambiguous(..), ParseResults, ParseFailure(..), Position, positionOffset)
type Grammar (g :: (* -> *) -> *) p s = g (p g s)
type GrammarBuilder (g :: (* -> *) -> *)
(g' :: (* -> *) -> *)
(p :: ((* -> *) -> *) -> * -> * -> *)
(s :: *)
= g (p g' s) -> g (p g' s)
simply :: (Rank2.Only r (p (Rank2.Only r) s) -> s -> Rank2.Only r f) -> p (Rank2.Only r) s r -> s -> f r
simply parseGrammar p input = Rank2.fromOnly (parseGrammar (Rank2.Only p) input)
failureDescription :: forall s. (Eq s, IsString s, FactorialMonoid s) => s -> ParseFailure -> Int -> s
failureDescription input (ParseFailure pos expected) contextLineCount =
offsetContext input pos contextLineCount
<> "expected " <> oxfordComma (fromString <$> expected)
where oxfordComma :: [s] -> s
oxfordComma [] = ""
oxfordComma [x] = x
oxfordComma [x, y] = x <> " or " <> y
oxfordComma (x:y:rest) = mconcat (intersperse ", " (x : y : onLast ("or " <>) rest))
onLast _ [] = []
onLast f [x] = [f x]
onLast f (x:xs) = x : onLast f xs
offsetContext :: (Eq s, IsString s, FactorialMonoid s) => s -> Int -> Int -> s
offsetContext input offset contextLineCount =
foldMap (<> "\n") prevLines <> fromString (replicate column ' ') <> "^\n"
<> "at line " <> fromString (show $ length allPrevLines) <> ", column " <> fromString (show $ column+1) <> "\n"
where (allPrevLines, column) = offsetLineAndColumn input offset
prevLines = reverse (take contextLineCount allPrevLines)
offsetLineAndColumn :: (Eq s, IsString s, FactorialMonoid s) => s -> Int -> ([s], Int)
offsetLineAndColumn input pos = context [] 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