data-textual-0.3.0.3: Human-friendly textual representations.

Safe HaskellNone
LanguageHaskell2010

Data.Textual.Integral

Contents

Description

Parsers for integral numbers written in positional numeral systems.

Synopsis

Positional numeral systems

class PositionalSystem s where #

Positional numeral system.

Methods

systemName :: s -> String #

The name of the system (e.g. "binary", "decimal").

radixIn :: Num α => s -> α #

The radix of the system.

isDigitIn :: s -> Char -> Bool #

Test if a character is a digit.

isNzDigitIn :: s -> Char -> Bool #

Test if a character is a non-zero digit.

fromDigitIn :: Num α => s -> Char -> Maybe α #

Map digits to the corresponding numbers. Return Nothing on other inputs.

fromNzDigitIn :: Num α => s -> Char -> Maybe α #

Map non-zero digits to the corresponding numbers. Return Nothing on other inputs.

unsafeFromDigitIn :: Num α => s -> Char -> α #

Map digits to the corresponding numbers. No checks are performed.

intToDigitIn :: s -> Int -> Char #

Map Int values to the corresponding digits. Inputs must be non-negative and less than the radix.

printDigitIn :: Printer p => s -> Char -> p #

Print a digit.

printZeroIn :: Printer p => s -> p #

Instances
PositionalSystem Binary 
Instance details

Defined in Text.Printer.Integral

Methods

systemName :: Binary -> String #

radixIn :: Num α => Binary -> α #

isDigitIn :: Binary -> Char -> Bool #

isNzDigitIn :: Binary -> Char -> Bool #

fromDigitIn :: Num α => Binary -> Char -> Maybe α #

fromNzDigitIn :: Num α => Binary -> Char -> Maybe α #

unsafeFromDigitIn :: Num α => Binary -> Char -> α #

intToDigitIn :: Binary -> Int -> Char #

printDigitIn :: Printer p => Binary -> Char -> p #

printZeroIn :: Printer p => Binary -> p #

PositionalSystem Octal 
Instance details

Defined in Text.Printer.Integral

Methods

systemName :: Octal -> String #

radixIn :: Num α => Octal -> α #

isDigitIn :: Octal -> Char -> Bool #

isNzDigitIn :: Octal -> Char -> Bool #

fromDigitIn :: Num α => Octal -> Char -> Maybe α #

fromNzDigitIn :: Num α => Octal -> Char -> Maybe α #

unsafeFromDigitIn :: Num α => Octal -> Char -> α #

intToDigitIn :: Octal -> Int -> Char #

printDigitIn :: Printer p => Octal -> Char -> p #

printZeroIn :: Printer p => Octal -> p #

PositionalSystem Decimal 
Instance details

Defined in Text.Printer.Integral

PositionalSystem Hexadecimal 
Instance details

Defined in Text.Printer.Integral

PositionalSystem LowHex 
Instance details

Defined in Text.Printer.Integral

Methods

systemName :: LowHex -> String #

radixIn :: Num α => LowHex -> α #

isDigitIn :: LowHex -> Char -> Bool #

isNzDigitIn :: LowHex -> Char -> Bool #

fromDigitIn :: Num α => LowHex -> Char -> Maybe α #

fromNzDigitIn :: Num α => LowHex -> Char -> Maybe α #

unsafeFromDigitIn :: Num α => LowHex -> Char -> α #

intToDigitIn :: LowHex -> Int -> Char #

printDigitIn :: Printer p => LowHex -> Char -> p #

printZeroIn :: Printer p => LowHex -> p #

PositionalSystem UpHex 
Instance details

Defined in Text.Printer.Integral

Methods

systemName :: UpHex -> String #

radixIn :: Num α => UpHex -> α #

isDigitIn :: UpHex -> Char -> Bool #

isNzDigitIn :: UpHex -> Char -> Bool #

fromDigitIn :: Num α => UpHex -> Char -> Maybe α #

fromNzDigitIn :: Num α => UpHex -> Char -> Maybe α #

unsafeFromDigitIn :: Num α => UpHex -> Char -> α #

intToDigitIn :: UpHex -> Int -> Char #

printDigitIn :: Printer p => UpHex -> Char -> p #

printZeroIn :: Printer p => UpHex -> p #

class PositionalSystem s => BitSystem s where #

Positonal numeral system with a power of two radix.

Methods

digitBitsIn :: s -> Int #

Numer of bits occupied by a digit.

digitMaskIn :: Num α => s -> α #

The number that has digitBitsIn least significant bits set to ones and all the other bits set to zeroes.

lastDigitIn :: Bits α => s -> α -> Int #

Map the last digit of a number to the corresponding Int value.

Instances
BitSystem Binary 
Instance details

Defined in Text.Printer.Integral

Methods

digitBitsIn :: Binary -> Int #

digitMaskIn :: Num α => Binary -> α #

lastDigitIn :: Bits α => Binary -> α -> Int #

BitSystem Octal 
Instance details

Defined in Text.Printer.Integral

Methods

digitBitsIn :: Octal -> Int #

digitMaskIn :: Num α => Octal -> α #

lastDigitIn :: Bits α => Octal -> α -> Int #

BitSystem Hexadecimal 
Instance details

Defined in Text.Printer.Integral

Methods

digitBitsIn :: Hexadecimal -> Int #

digitMaskIn :: Num α => Hexadecimal -> α #

lastDigitIn :: Bits α => Hexadecimal -> α -> Int #

BitSystem LowHex 
Instance details

Defined in Text.Printer.Integral

Methods

digitBitsIn :: LowHex -> Int #

digitMaskIn :: Num α => LowHex -> α #

lastDigitIn :: Bits α => LowHex -> α -> Int #

BitSystem UpHex 
Instance details

Defined in Text.Printer.Integral

Methods

digitBitsIn :: UpHex -> Int #

digitMaskIn :: Num α => UpHex -> α #

lastDigitIn :: Bits α => UpHex -> α -> Int #

data Binary #

The binary numeral system.

Constructors

Binary 
Instances
Eq Binary 
Instance details

Defined in Text.Printer.Integral

Methods

(==) :: Binary -> Binary -> Bool #

(/=) :: Binary -> Binary -> Bool #

Ord Binary 
Instance details

Defined in Text.Printer.Integral

Read Binary 
Instance details

Defined in Text.Printer.Integral

Show Binary 
Instance details

Defined in Text.Printer.Integral

Generic Binary 
Instance details

Defined in Text.Printer.Integral

Associated Types

type Rep Binary :: Type -> Type #

Methods

from :: Binary -> Rep Binary x #

to :: Rep Binary x -> Binary #

PositionalSystem Binary 
Instance details

Defined in Text.Printer.Integral

Methods

systemName :: Binary -> String #

radixIn :: Num α => Binary -> α #

isDigitIn :: Binary -> Char -> Bool #

isNzDigitIn :: Binary -> Char -> Bool #

fromDigitIn :: Num α => Binary -> Char -> Maybe α #

fromNzDigitIn :: Num α => Binary -> Char -> Maybe α #

unsafeFromDigitIn :: Num α => Binary -> Char -> α #

intToDigitIn :: Binary -> Int -> Char #

printDigitIn :: Printer p => Binary -> Char -> p #

printZeroIn :: Printer p => Binary -> p #

BitSystem Binary 
Instance details

Defined in Text.Printer.Integral

Methods

digitBitsIn :: Binary -> Int #

digitMaskIn :: Num α => Binary -> α #

lastDigitIn :: Bits α => Binary -> α -> Int #

type Rep Binary 
Instance details

Defined in Text.Printer.Integral

type Rep Binary = D1 (MetaData "Binary" "Text.Printer.Integral" "text-printer-0.5.0.1-DETqKuZOYTb54wMfYuJ3EI" False) (C1 (MetaCons "Binary" PrefixI False) (U1 :: Type -> Type))

data Octal #

The octal numeral system.

Constructors

Octal 
Instances
Eq Octal 
Instance details

Defined in Text.Printer.Integral

Methods

(==) :: Octal -> Octal -> Bool #

(/=) :: Octal -> Octal -> Bool #

Ord Octal 
Instance details

Defined in Text.Printer.Integral

Methods

compare :: Octal -> Octal -> Ordering #

(<) :: Octal -> Octal -> Bool #

(<=) :: Octal -> Octal -> Bool #

(>) :: Octal -> Octal -> Bool #

(>=) :: Octal -> Octal -> Bool #

max :: Octal -> Octal -> Octal #

min :: Octal -> Octal -> Octal #

Read Octal 
Instance details

Defined in Text.Printer.Integral

Show Octal 
Instance details

Defined in Text.Printer.Integral

Methods

showsPrec :: Int -> Octal -> ShowS #

show :: Octal -> String #

showList :: [Octal] -> ShowS #

Generic Octal 
Instance details

Defined in Text.Printer.Integral

Associated Types

type Rep Octal :: Type -> Type #

Methods

from :: Octal -> Rep Octal x #

to :: Rep Octal x -> Octal #

PositionalSystem Octal 
Instance details

Defined in Text.Printer.Integral

Methods

systemName :: Octal -> String #

radixIn :: Num α => Octal -> α #

isDigitIn :: Octal -> Char -> Bool #

isNzDigitIn :: Octal -> Char -> Bool #

fromDigitIn :: Num α => Octal -> Char -> Maybe α #

fromNzDigitIn :: Num α => Octal -> Char -> Maybe α #

unsafeFromDigitIn :: Num α => Octal -> Char -> α #

intToDigitIn :: Octal -> Int -> Char #

printDigitIn :: Printer p => Octal -> Char -> p #

printZeroIn :: Printer p => Octal -> p #

BitSystem Octal 
Instance details

Defined in Text.Printer.Integral

Methods

digitBitsIn :: Octal -> Int #

digitMaskIn :: Num α => Octal -> α #

lastDigitIn :: Bits α => Octal -> α -> Int #

type Rep Octal 
Instance details

Defined in Text.Printer.Integral

type Rep Octal = D1 (MetaData "Octal" "Text.Printer.Integral" "text-printer-0.5.0.1-DETqKuZOYTb54wMfYuJ3EI" False) (C1 (MetaCons "Octal" PrefixI False) (U1 :: Type -> Type))

data Decimal #

The decimal numeral system.

Constructors

Decimal 
Instances
Eq Decimal 
Instance details

Defined in Text.Printer.Integral

Methods

(==) :: Decimal -> Decimal -> Bool #

(/=) :: Decimal -> Decimal -> Bool #

Ord Decimal 
Instance details

Defined in Text.Printer.Integral

Read Decimal 
Instance details

Defined in Text.Printer.Integral

Show Decimal 
Instance details

Defined in Text.Printer.Integral

Generic Decimal 
Instance details

Defined in Text.Printer.Integral

Associated Types

type Rep Decimal :: Type -> Type #

Methods

from :: Decimal -> Rep Decimal x #

to :: Rep Decimal x -> Decimal #

PositionalSystem Decimal 
Instance details

Defined in Text.Printer.Integral

type Rep Decimal 
Instance details

Defined in Text.Printer.Integral

type Rep Decimal = D1 (MetaData "Decimal" "Text.Printer.Integral" "text-printer-0.5.0.1-DETqKuZOYTb54wMfYuJ3EI" False) (C1 (MetaCons "Decimal" PrefixI False) (U1 :: Type -> Type))

data Hexadecimal #

The hexadecimal numeral system.

Constructors

Hexadecimal 
Instances
Eq Hexadecimal 
Instance details

Defined in Text.Printer.Integral

Ord Hexadecimal 
Instance details

Defined in Text.Printer.Integral

Read Hexadecimal 
Instance details

Defined in Text.Printer.Integral

Show Hexadecimal 
Instance details

Defined in Text.Printer.Integral

Generic Hexadecimal 
Instance details

Defined in Text.Printer.Integral

Associated Types

type Rep Hexadecimal :: Type -> Type #

PositionalSystem Hexadecimal 
Instance details

Defined in Text.Printer.Integral

BitSystem Hexadecimal 
Instance details

Defined in Text.Printer.Integral

Methods

digitBitsIn :: Hexadecimal -> Int #

digitMaskIn :: Num α => Hexadecimal -> α #

lastDigitIn :: Bits α => Hexadecimal -> α -> Int #

type Rep Hexadecimal 
Instance details

Defined in Text.Printer.Integral

type Rep Hexadecimal = D1 (MetaData "Hexadecimal" "Text.Printer.Integral" "text-printer-0.5.0.1-DETqKuZOYTb54wMfYuJ3EI" False) (C1 (MetaCons "Hexadecimal" PrefixI False) (U1 :: Type -> Type))

data LowHex #

The hexadecimal numeral system, using lower case digits.

Constructors

LowHex 
Instances
Eq LowHex 
Instance details

Defined in Text.Printer.Integral

Methods

(==) :: LowHex -> LowHex -> Bool #

(/=) :: LowHex -> LowHex -> Bool #

Ord LowHex 
Instance details

Defined in Text.Printer.Integral

Read LowHex 
Instance details

Defined in Text.Printer.Integral

Show LowHex 
Instance details

Defined in Text.Printer.Integral

Generic LowHex 
Instance details

Defined in Text.Printer.Integral

Associated Types

type Rep LowHex :: Type -> Type #

Methods

from :: LowHex -> Rep LowHex x #

to :: Rep LowHex x -> LowHex #

PositionalSystem LowHex 
Instance details

Defined in Text.Printer.Integral

Methods

systemName :: LowHex -> String #

radixIn :: Num α => LowHex -> α #

isDigitIn :: LowHex -> Char -> Bool #

isNzDigitIn :: LowHex -> Char -> Bool #

fromDigitIn :: Num α => LowHex -> Char -> Maybe α #

fromNzDigitIn :: Num α => LowHex -> Char -> Maybe α #

unsafeFromDigitIn :: Num α => LowHex -> Char -> α #

intToDigitIn :: LowHex -> Int -> Char #

printDigitIn :: Printer p => LowHex -> Char -> p #

printZeroIn :: Printer p => LowHex -> p #

BitSystem LowHex 
Instance details

Defined in Text.Printer.Integral

Methods

digitBitsIn :: LowHex -> Int #

digitMaskIn :: Num α => LowHex -> α #

lastDigitIn :: Bits α => LowHex -> α -> Int #

type Rep LowHex 
Instance details

Defined in Text.Printer.Integral

type Rep LowHex = D1 (MetaData "LowHex" "Text.Printer.Integral" "text-printer-0.5.0.1-DETqKuZOYTb54wMfYuJ3EI" False) (C1 (MetaCons "LowHex" PrefixI False) (U1 :: Type -> Type))

data UpHex #

The hexadecimal numeral system, using upper case digits.

Constructors

UpHex 
Instances
Eq UpHex 
Instance details

Defined in Text.Printer.Integral

Methods

(==) :: UpHex -> UpHex -> Bool #

(/=) :: UpHex -> UpHex -> Bool #

Ord UpHex 
Instance details

Defined in Text.Printer.Integral

Methods

compare :: UpHex -> UpHex -> Ordering #

(<) :: UpHex -> UpHex -> Bool #

(<=) :: UpHex -> UpHex -> Bool #

(>) :: UpHex -> UpHex -> Bool #

(>=) :: UpHex -> UpHex -> Bool #

max :: UpHex -> UpHex -> UpHex #

min :: UpHex -> UpHex -> UpHex #

Read UpHex 
Instance details

Defined in Text.Printer.Integral

Show UpHex 
Instance details

Defined in Text.Printer.Integral

Methods

showsPrec :: Int -> UpHex -> ShowS #

show :: UpHex -> String #

showList :: [UpHex] -> ShowS #

Generic UpHex 
Instance details

Defined in Text.Printer.Integral

Associated Types

type Rep UpHex :: Type -> Type #

Methods

from :: UpHex -> Rep UpHex x #

to :: Rep UpHex x -> UpHex #

PositionalSystem UpHex 
Instance details

Defined in Text.Printer.Integral

Methods

systemName :: UpHex -> String #

radixIn :: Num α => UpHex -> α #

isDigitIn :: UpHex -> Char -> Bool #

isNzDigitIn :: UpHex -> Char -> Bool #

fromDigitIn :: Num α => UpHex -> Char -> Maybe α #

fromNzDigitIn :: Num α => UpHex -> Char -> Maybe α #

unsafeFromDigitIn :: Num α => UpHex -> Char -> α #

intToDigitIn :: UpHex -> Int -> Char #

printDigitIn :: Printer p => UpHex -> Char -> p #

printZeroIn :: Printer p => UpHex -> p #

BitSystem UpHex 
Instance details

Defined in Text.Printer.Integral

Methods

digitBitsIn :: UpHex -> Int #

digitMaskIn :: Num α => UpHex -> α #

lastDigitIn :: Bits α => UpHex -> α -> Int #

type Rep UpHex 
Instance details

Defined in Text.Printer.Integral

type Rep UpHex = D1 (MetaData "UpHex" "Text.Printer.Integral" "text-printer-0.5.0.1-DETqKuZOYTb54wMfYuJ3EI" False) (C1 (MetaCons "UpHex" PrefixI False) (U1 :: Type -> Type))

Single digits

digitIn :: (PositionalSystem s, Num α, CharParsing μ) => s -> μ α Source #

Parse a digit of the specified positional numeral system.

nzDigitIn :: (PositionalSystem s, Num α, CharParsing μ) => s -> μ α Source #

Parse a non-zero digit of the specified positional numeral system.

binDigit :: (Num α, CharParsing μ) => μ α Source #

Parse a binary digit.

nzBinDigit :: (Num α, CharParsing μ) => μ α Source #

Parse a non-zero binary digit ('1').

octDigit :: (Num α, CharParsing μ) => μ α Source #

Parse an octal digit.

nzOctDigit :: (Num α, CharParsing μ) => μ α Source #

Parse a non-zero octal digit.

decDigit :: (Num α, CharParsing μ) => μ α Source #

Parse a decimal digit.

nzDecDigit :: (Num α, CharParsing μ) => μ α Source #

Parse a non-zero decimal digit.

hexDigit :: (Num α, CharParsing μ) => μ α Source #

Parse a hexadecimal digit.

nzHexDigit :: (Num α, CharParsing μ) => μ α Source #

Parse a non-zero hexadecimal digit.

lowHexDigit :: (Num α, CharParsing μ) => μ α Source #

Parse a lower case hexadecimal digit.

nzLowHexDigit :: (Num α, CharParsing μ) => μ α Source #

Parse a non-zero lower case hexadecimal digit.

upHexDigit :: (Num α, CharParsing μ) => μ α Source #

Parse an upper case hexadecimal digit.

nzUpHexDigit :: (Num α, CharParsing μ) => μ α Source #

Parse a non-zero upper case hexadecimal digit.

Numbers

nonNegative :: (PositionalSystem s, Num α, Monad μ, CharParsing μ) => s -> μ α Source #

Parse a non-negative number written in the specified positional numeral system.

nnCompact :: (PositionalSystem s, Num α, Monad μ, CharParsing μ) => s -> μ α Source #

Parse a non-negative number written in the specified positional numeral system. Leading zeroes are not allowed.

nnUpTo :: (PositionalSystem s, Num α, Monad μ, CharParsing μ) => s -> Int -> μ α Source #

Parse a non-negative number written in the specified positional numeral system (up to n digits).

nncUpTo :: (PositionalSystem s, Num α, Monad μ, CharParsing μ) => s -> Int -> μ α Source #

Parse a non-negative number written in the specified positional numeral system (up to n digits). Leading zeroes are not allowed.

nnBounded :: (PositionalSystem s, Ord α, Bounded α, Integral α, Monad μ, CharParsing μ) => s -> μ α Source #

Parse a non-negative number written in the specified positional numeral system, failing on overflow.

nncBounded :: (PositionalSystem s, Ord α, Bounded α, Integral α, Monad μ, CharParsing μ) => s -> μ α Source #

Parse a non-negative number written in the specified positional numeral system, failing on overflow. Leading zeroes are not allowed.

nnBits :: (BitSystem s, Num α, Bits α, Monad μ, CharParsing μ) => s -> μ α Source #

Parse a non-negative binary number written in the specified positional numeral system.

nncBits :: (BitSystem s, Num α, Bits α, Monad μ, CharParsing μ) => s -> μ α Source #

Parse a non-negative binary number written in the specified positional numeral system. Leading zeroes are not allowed.

nnBitsUpTo :: (BitSystem s, Num α, Bits α, Monad μ, CharParsing μ) => s -> Int -> μ α Source #

Parse a non-negative binary number written in the specified positional numeral system (up to n digits).

nncBitsUpTo :: (BitSystem s, Num α, Bits α, Monad μ, CharParsing μ) => s -> Int -> μ α Source #

Parse a non-negative binary number written in the specified positional numeral system (up to n digits). Leading zeroes are not allowed.

nnbBits :: (BitSystem s, Ord α, Bounded α, Num α, Bits α, Monad μ, CharParsing μ) => s -> μ α Source #

Parse a non-negative binary number written in the specified positional numeral system, failing on overflow.

nncbBits :: (BitSystem s, Ord α, Bounded α, Num α, Bits α, Monad μ, CharParsing μ) => s -> μ α Source #

Parse a non-negative binary number written in the specified positional numeral system, failing on overflow. Leading zeroes are not allowed.

nonPositive :: (PositionalSystem s, Num α, Monad μ, CharParsing μ) => s -> μ α Source #

Parse a non-positive number written in the specified positional numeral system. For example, parsing "123" as a decimal would produce -123, not 123.

npCompact :: (PositionalSystem s, Num α, Monad μ, CharParsing μ) => s -> μ α Source #

Parse a non-positive number written in the specified positional numeral system. Leading zeroes are not allowed.

npUpTo :: (PositionalSystem s, Num α, Monad μ, CharParsing μ) => s -> Int -> μ α Source #

Parse a non-positive number written in the specified positional numeral system (up to n digits).

npcUpTo :: (PositionalSystem s, Num α, Monad μ, CharParsing μ) => s -> Int -> μ α Source #

Parse a non-positive number written in the specified positional numeral system (up to n digits). Leading zeroes are not allowed.

npBounded :: (PositionalSystem s, Ord α, Bounded α, Integral α, Monad μ, CharParsing μ) => s -> μ α Source #

Parse a non-positive number written in the specified positional numeral system, failing on overflow.

npcBounded :: (PositionalSystem s, Ord α, Bounded α, Integral α, Monad μ, CharParsing μ) => s -> μ α Source #

Parse a non-positive number written in the specified positional numeral system, failing on overflow. Leading zeroes are not allowed.

npBits :: (BitSystem s, Num α, Bits α, Monad μ, CharParsing μ) => s -> μ α Source #

Parse a non-positive two's complement binary number written in the specified positional numeral system.

npcBits :: (BitSystem s, Num α, Bits α, Monad μ, CharParsing μ) => s -> μ α Source #

Parse a non-positive two's complement binary number written in the specified positional numeral system. Leading zeroes are not allowed.

npBitsUpTo :: (BitSystem s, Num α, Bits α, Monad μ, CharParsing μ) => s -> Int -> μ α Source #

Parse a non-positive two's complement binary number written in the specified positional numeral system (up to n digits).

npcBitsUpTo :: (BitSystem s, Num α, Bits α, Monad μ, CharParsing μ) => s -> Int -> μ α Source #

Parse a non-positive two's complement binary number written in the specified positional numeral system (up to n digits). Leading zeroes are not allowed.

npbBits :: forall s μ α. (BitSystem s, Ord α, Bounded α, Num α, Bits α, Monad μ, CharParsing μ) => s -> μ α Source #

Parse a non-positive two's complement binary number written in the specified positional numeral system, failing on overflow.

npcbBits :: forall s μ α. (BitSystem s, Ord α, Bounded α, Num α, Bits α, Monad μ, CharParsing μ) => s -> μ α Source #

Parse a non-positive two's complement binary number written in the specified positional numeral system, failing on overflow. Leading zeroes are not allowed.

data Sign Source #

Sign of a number.

Constructors

NonNegative 
NonPositive 
Instances
Eq Sign Source # 
Instance details

Defined in Data.Textual.Integral

Methods

(==) :: Sign -> Sign -> Bool #

(/=) :: Sign -> Sign -> Bool #

Read Sign Source # 
Instance details

Defined in Data.Textual.Integral

Show Sign Source # 
Instance details

Defined in Data.Textual.Integral

Methods

showsPrec :: Int -> Sign -> ShowS #

show :: Sign -> String #

showList :: [Sign] -> ShowS #

applySign :: Num α => Sign -> α -> α Source #

Negate the supplied value if the sign is NonPositive and return it as it is otherwise.

optMinus :: CharParsing μ => μ Sign Source #

Optional minus sign.

optSign :: CharParsing μ => μ Sign Source #

Optional minus or plus sign.

number' :: (PositionalSystem s, Num α, Monad μ, CharParsing μ) => μ Sign -> s -> μ α Source #

Parse a number written in the specified positional numeral system. The supplied parser is used to determine the sign of the number.

number :: (PositionalSystem s, Num α, Monad μ, CharParsing μ) => s -> μ α Source #

A shorthand for number' optMinus.

compact' :: (PositionalSystem s, Num α, Monad μ, CharParsing μ) => μ Sign -> s -> μ α Source #

Parse a number written in the specified positional numeral system. The supplied parser is used to determine the sign of the number. Leading zeroes are not allowed.

compact :: (PositionalSystem s, Num α, Monad μ, CharParsing μ) => s -> μ α Source #

A shorthand for compact' optMinus.

numberUpTo' :: (PositionalSystem s, Num α, Monad μ, CharParsing μ) => μ Sign -> s -> Int -> μ α Source #

Parse a number written in the specified positional numeral system (up to n digits). The supplied parser is used to determine the sign of the number.

numberUpTo :: (PositionalSystem s, Num α, Monad μ, CharParsing μ) => s -> Int -> μ α Source #

A shorthand for numberUpTo' optMinus.

compactUpTo' :: (PositionalSystem s, Num α, Monad μ, CharParsing μ) => μ Sign -> s -> Int -> μ α Source #

Parse a number written in the specified positional numeral system (up to n digits). The supplied parser is used to determine the sign of the number. Leading zeroes are not allowed.

compactUpTo :: (PositionalSystem s, Num α, Monad μ, CharParsing μ) => s -> Int -> μ α Source #

A shorthand for compactUpTo' optMinus.

bounded' :: (PositionalSystem s, Ord α, Bounded α, Integral α, Monad μ, CharParsing μ) => μ Sign -> s -> μ α Source #

Parse a number written in the specified positional numeral system, failing on overflow. The supplied parser is used to determine the sign of the number.

bounded :: (PositionalSystem s, Ord α, Bounded α, Integral α, Monad μ, CharParsing μ) => s -> μ α Source #

A shorthand for bounded' optMinus.

cBounded' :: (PositionalSystem s, Ord α, Bounded α, Integral α, Monad μ, CharParsing μ) => μ Sign -> s -> μ α Source #

Parse a number written in the specified positional numeral system, failing on overflow. The supplied parser is used to determine the sign of the number. Leading zeroes are not allowed.

cBounded :: (PositionalSystem s, Ord α, Bounded α, Integral α, Monad μ, CharParsing μ) => s -> μ α Source #

A shorthand for cBounded' optMinus.

bits' :: (BitSystem s, Num α, Bits α, Monad μ, CharParsing μ) => μ Sign -> s -> μ α Source #

Parse a (two's complement) binary number written in the specified positional numeral system. The supplied parser is used to determine the sign of the number.

bits :: (BitSystem s, Num α, Bits α, Monad μ, CharParsing μ) => s -> μ α Source #

A shorthand for bits' optMinus.

cBits' :: (BitSystem s, Num α, Bits α, Monad μ, CharParsing μ) => μ Sign -> s -> μ α Source #

Parse a (two's complement) binary number written in the specified positional numeral system. The supplied parser is used to determine the sign of the number. Leading zeroes are not allowed.

cBits :: (BitSystem s, Num α, Bits α, Monad μ, CharParsing μ) => s -> μ α Source #

A shorthand for cBits' optMinus.

bitsUpTo' :: (BitSystem s, Num α, Bits α, Monad μ, CharParsing μ) => μ Sign -> s -> Int -> μ α Source #

Parse a (two's complement) binary number written in the specified positional numeral system (up to n digits). The supplied parser is used to determine the sign of the number.

bitsUpTo :: (BitSystem s, Num α, Bits α, Monad μ, CharParsing μ) => s -> Int -> μ α Source #

A shorthand for bitsUpTo' optMinus.

cBitsUpTo' :: (BitSystem s, Num α, Bits α, Monad μ, CharParsing μ) => μ Sign -> s -> Int -> μ α Source #

Parse a (two's complement) binary number written in the specified positional numeral system (up to n digits). The supplied parser is used to determine the sign of the number. Leading zeroes are not allowed.

cBitsUpTo :: (BitSystem s, Num α, Bits α, Monad μ, CharParsing μ) => s -> Int -> μ α Source #

A shorthand for cBitsUpTo' optMinus.

bBits' :: (BitSystem s, Ord α, Bounded α, Num α, Bits α, Monad μ, CharParsing μ) => μ Sign -> s -> μ α Source #

Parse a (two's complement) binary number written in the specified positional numeral system, failing on overflow. The supplied parser is used to determine the sign of the number.

bBits :: (BitSystem s, Ord α, Bounded α, Num α, Bits α, Monad μ, CharParsing μ) => s -> μ α Source #

A shorthand for bBits' optMinus.

cbBits' :: (BitSystem s, Ord α, Bounded α, Num α, Bits α, Monad μ, CharParsing μ) => μ Sign -> s -> μ α Source #

Parse a (two's complement) binary number written in the specified positional numeral system, failing on overflow. The supplied parser is used to determine the sign of the number. Leading zeroes are not allowed.

cbBits :: (BitSystem s, Ord α, Bounded α, Num α, Bits α, Monad μ, CharParsing μ) => s -> μ α Source #

A shorthand for cbBits' optMinus.