Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Symparsec.Parser.Count
Documentation
type Count' n pCh pEnd s0 = 'PParser (CountChSym pCh s0) (CountEndSym pEnd s0) '(n, '[], s0) Source #
sCount :: SNat n -> SParser ss sr ('PParser pCh pEnd s0) -> SParser (SCountS ss sr) (SList sr) (Count' n pCh pEnd s0) Source #
sCountChSym :: SParserChSym ss sr pCh -> ss s0 -> SParserChSym (SCountS ss sr) (SList sr) (CountChSym pCh s0) Source #
sCountCh' :: SParserChSym ss sr pCh -> ss s0 -> SChar ch -> SNat n -> SList sr rs -> ss s -> SResult (SCountS ss sr) (SList sr) (CountCh' pCh s0 ch n rs s) Source #
sCountChN :: SParserChSym ss sr pCh -> SChar ch -> SNat n -> SList sr rs -> ss s0 -> SResult ss sr res -> SResult (SCountS ss sr) (SList sr) (CountChN pCh ch n rs s0 res) Source #
data CountChSym pCh s0 f Source #
Instances
(p ~ 'PParser pCh pEnd s0, SingParser p, KnownNat n) => SingParser (Count' n pCh pEnd s0 :: PParser (CountS k r) [r]) Source # | |
type App (CountChSym pCh s0 :: FunKind Char (CountS s r ~> PResult (CountS s r) [r]) -> Type) (f :: Char) Source # | |
Defined in Symparsec.Parser.Count | |
type PS (Count' n pCh pEnd s0 :: PParser (CountS k r) [r]) Source # | |
type PR (Count' n pCh pEnd s0 :: PParser (CountS k r) [r]) Source # | |
data CountChSym1 pCh s0 ch s Source #
Instances
sCountEnd' :: SParserEndSym ss sr pEnd -> ss s0 -> SNat n -> SList sr rs -> ss s -> SResultEnd (SList sr) (CountEnd' pEnd s0 n rs s) Source #
sCountEndN :: SParserEndSym ss sr pEnd -> ss s0 -> SNat n -> SList sr rs -> SResultEnd sr res -> SResultEnd (SList sr) (CountEndN pEnd s0 n rs res) Source #
data CountEndSym pEnd s0 s Source #
Instances
(p ~ 'PParser pCh pEnd s0, SingParser p, KnownNat n) => SingParser (Count' n pCh pEnd s0 :: PParser (CountS k r) [r]) Source # | |
type PS (Count' n pCh pEnd s0 :: PParser (CountS k r) [r]) Source # | |
type App (CountEndSym pEnd s0 :: FunKind (CountS a k) (PResultEnd [k]) -> Type) (s :: CountS a k) Source # | |
Defined in Symparsec.Parser.Count type App (CountEndSym pEnd s0 :: FunKind (CountS a k) (PResultEnd [k]) -> Type) (s :: CountS a k) = CountEnd pEnd s0 s | |
type PR (Count' n pCh pEnd s0 :: PParser (CountS k r) [r]) Source # | |
sCountEndSym :: SParserEndSym ss sr pEnd -> ss s0 -> SParserEndSym (SCountS ss sr) (SList sr) (CountEndSym pEnd s0) Source #