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

Safe HaskellNone

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

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.

data Binary

The binary numeral system.

Constructors

Binary 

data Octal

The octal numeral system.

Constructors

Octal 

data Decimal

The decimal numeral system.

Constructors

Decimal 

data Hexadecimal

The hexadecimal numeral system.

Constructors

Hexadecimal 

data LowHex

The hexadecimal numeral system, using lower case digits.

Constructors

LowHex 

data UpHex

The hexadecimal numeral system, using upper case digits.

Constructors

UpHex 

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 

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

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

optMinus :: CharParsing μ => μ SignSource

Optional minus sign.

optSign :: CharParsing μ => μ SignSource

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.