{-# LANGUAGE UndecidableInstances #-}
module Symparsec.Run ( type Run, type RunTest ) where
import Symparsec.Parser
import Data.Type.Symbol qualified as Symbol
import DeFun.Core
import GHC.TypeLits ( type Symbol )
import GHC.TypeNats ( type Natural, type (+) )
import GHC.TypeError qualified as TE
import TypeLevelShow.Doc
import TypeLevelShow.Natural ( type ShowNatDec )
type Run :: PParser a -> Symbol -> Either TE.ErrorMessage (a, Symbol)
type Run p str = RunEnd str (p @@ StateInit str)
type RunEnd :: Symbol -> PReply a -> Either TE.ErrorMessage (a, Symbol)
type family RunEnd str rep where
RunEnd str ('Reply (OK a) ('State rem _len _idx)) =
Right '(a, rem)
RunEnd str ('Reply (Err e) ('State _rem _len idx)) =
Left (RenderPDoc (PrettyErrorTop idx str e))
type RunTest :: PParser a -> Symbol -> (a, Symbol)
type RunTest p str = FromRightTypeError (Run p str)
type FromRightTypeError :: Either TE.ErrorMessage a -> a
type family FromRightTypeError eea where
FromRightTypeError (Right a) = a
FromRightTypeError (Left e) = TE.TypeError e
type StateInit :: Symbol -> PState
type StateInit str = 'State str (Symbol.Length str) 0
type PrettyErrorTop :: Natural -> Symbol -> PError -> PDoc
type PrettyErrorTop idx str e =
Text "Symparsec parse error:"
:$$: Text "1:" :<>: Text (ShowNatDec (idx+1))
:$$: PrettyErrorPosition idx str
:$$: PrettyError e
type PrettyErrorPosition :: Natural -> Symbol -> PDoc
type PrettyErrorPosition idx str =
Text " |"
:$$: Text "1 | " :<>: Text str
:$$: Text " | " :<>: Text (Symbol.Replicate idx ' ') :<>: Text "^"
type PrettyError :: PError -> PDoc
type family PrettyError e where
PrettyError ('Error (str:strs)) = ConcatSymbol (Text str) strs
PrettyError ('Error '[]) = Text "<no detail>"
type ConcatSymbol :: PDoc -> [Symbol] -> PDoc
type family ConcatSymbol doc strs where
ConcatSymbol doc (str:strs) = ConcatSymbol (doc :$$: Text str) strs
ConcatSymbol doc '[] = doc