symparsec
Safe HaskellNone
LanguageGHC2021

Symparsec.Parser.Natural

Synopsis

Documentation

data NatBase (base :: Natural) (parseDigit :: Char ~> Maybe Natural) (s :: FunKind PState (PReply Natural)) Source #

Parse a non-empty Natural using the given base and digit parser.

Only permits parsing numbers with digits exactly one Char long.

Returns an error if it parses zero digits, or if any character fails to parse.

Instances

Instances details
type App (NatBase base parseDigit :: FunKind PState (PReply Natural) -> Type) (s :: PState) Source # 
Instance details

Defined in Symparsec.Parser.Natural

type App (NatBase base parseDigit :: FunKind PState (PReply Natural) -> Type) (s :: PState)

data NatBase1 (base :: Natural) (parseDigit :: Char ~> Maybe Natural) (digit :: Natural) (s :: FunKind PState (PReply Natural)) Source #

Parse a Natural with the given starting value.

Skips some extra work. May be handy for hand-written parsers.

Instances

Instances details
type App (NatBase1 base parseDigit digit :: FunKind PState (PReply Natural) -> Type) (s :: PState) Source # 
Instance details

Defined in Symparsec.Parser.Natural

type App (NatBase1 base parseDigit digit :: FunKind PState (PReply Natural) -> Type) (s :: PState)

type NatDec = NatBase 10 ParseDigitDecSym Source #

Parse a decimal (base 10) Natural.

type NatHex = NatBase 16 ParseDigitHexSym Source #

Parse a hexadecimal (base 16) Natural. Permits mixed-case (0-9A-Fa-f).

type NatBin = NatBase 2 ParseDigitBinSym Source #

Parse a binary (base 2) Natural.

type NatOct = NatBase 8 ParseDigitOctSym Source #

Parse an octal (base 8) Natural.

data NatBaseWhile (base :: Natural) (parseDigit :: Char ~> Maybe Natural) (s :: FunKind PState (PReply Natural)) Source #

Parse a non-empty Natural using the given base and digit parser.

Only permits parsing numbers with digits exactly one Char long.

Returns an error if it parses zero digits, or if the first digit fails to parse. Returns success on parsing up to EOF, or just before the first failed character parse. (Should match the behaviour of Megaparsec's number parsers.)

Instances

Instances details
type App (NatBaseWhile base parseDigit :: FunKind PState (PReply Natural) -> Type) (s :: PState) Source # 
Instance details

Defined in Symparsec.Parser.Natural

type App (NatBaseWhile base parseDigit :: FunKind PState (PReply Natural) -> Type) (s :: PState)