{-# LANGUAGE UndecidableInstances #-}
module Symparsec.Parser.Common
(
type UnconsState
, type Error1
, type EStrInputTooShort, type EStrWrongChar
, type Impossible
, module Symparsec.Parser
, Doc(..), type (++)
, type App
, type Symbol, type UnconsSymbol, ConsSymbol
, type Natural, type (+), type (-), type (*)
, type ShowNatDec, type ShowChar
, type (@@), type (~>)
) where
import Symparsec.Parser
import DeFun.Core
import GHC.TypeLits ( type Symbol, type UnconsSymbol, type ConsSymbol )
import GHC.TypeNats ( type Natural, type (+), type (-), type (*) )
import TypeLevelShow.Doc
import TypeLevelShow.Natural ( type ShowNatDec )
import TypeLevelShow.Utils ( type ShowChar, type (++) )
import GHC.TypeError qualified as TE
type UnconsState :: PState -> (Maybe Char, PState)
type family UnconsState s where
UnconsState ('State rem 0 idx) = '(Nothing, 'State rem 0 idx)
UnconsState ('State rem len idx) = UnconsState' (UnconsSymbol rem) len idx
type UnconsState'
:: Maybe (Char, Symbol) -> Natural -> Natural -> (Maybe Char, PState)
type family UnconsState' mstr len idx where
UnconsState' (Just '(ch, rem)) len idx =
'(Just ch, 'State rem (len-1) (idx+1))
UnconsState' Nothing len idx =
TE.TypeError (TE.Text "unrecoverable parser error: got to end of input string before len=0")
type Error1 str = 'Error '[str]
type EStrInputTooShort :: Natural -> Natural -> Symbol
type EStrInputTooShort nNeed nGot =
"needed " ++ ShowNatDec nNeed
++ " chars, but only " ++ ShowNatDec nGot ++ " remain"
type EStrWrongChar :: Char -> Char -> Symbol
type EStrWrongChar chExpect chGot =
"expected '" ++ ShowChar chExpect
++ "', got '" ++ ShowChar chGot ++ "'"
type Impossible = TE.TypeError (TE.Text "impossible parser state")