| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Data.Textual.Integral
Description
Parsers for integral numbers written in positional numeral systems.
Synopsis
- class PositionalSystem s where- systemName :: s -> String
- radixIn :: Num α => s -> α
- isDigitIn :: s -> Char -> Bool
- isNzDigitIn :: s -> Char -> Bool
- fromDigitIn :: Num α => s -> Char -> Maybe α
- fromNzDigitIn :: Num α => s -> Char -> Maybe α
- unsafeFromDigitIn :: Num α => s -> Char -> α
- intToDigitIn :: s -> Int -> Char
- printDigitIn :: Printer p => s -> Char -> p
- printZeroIn :: Printer p => s -> p
 
- class PositionalSystem s => BitSystem s where- digitBitsIn :: s -> Int
- digitMaskIn :: Num α => s -> α
- lastDigitIn :: Bits α => s -> α -> Int
 
- data Binary = Binary
- data Octal = Octal
- data Decimal = Decimal
- data Hexadecimal = Hexadecimal
- data LowHex = LowHex
- data UpHex = UpHex
- digitIn :: (PositionalSystem s, Num α, CharParsing μ) => s -> μ α
- nzDigitIn :: (PositionalSystem s, Num α, CharParsing μ) => s -> μ α
- binDigit :: (Num α, CharParsing μ) => μ α
- nzBinDigit :: (Num α, CharParsing μ) => μ α
- octDigit :: (Num α, CharParsing μ) => μ α
- nzOctDigit :: (Num α, CharParsing μ) => μ α
- decDigit :: (Num α, CharParsing μ) => μ α
- nzDecDigit :: (Num α, CharParsing μ) => μ α
- hexDigit :: (Num α, CharParsing μ) => μ α
- nzHexDigit :: (Num α, CharParsing μ) => μ α
- lowHexDigit :: (Num α, CharParsing μ) => μ α
- nzLowHexDigit :: (Num α, CharParsing μ) => μ α
- upHexDigit :: (Num α, CharParsing μ) => μ α
- nzUpHexDigit :: (Num α, CharParsing μ) => μ α
- nonNegative :: (PositionalSystem s, Num α, Monad μ, CharParsing μ) => s -> μ α
- nnCompact :: (PositionalSystem s, Num α, Monad μ, CharParsing μ) => s -> μ α
- nnUpTo :: (PositionalSystem s, Num α, Monad μ, CharParsing μ) => s -> Int -> μ α
- nncUpTo :: (PositionalSystem s, Num α, Monad μ, CharParsing μ) => s -> Int -> μ α
- nnBounded :: (PositionalSystem s, Ord α, Bounded α, Integral α, Monad μ, CharParsing μ) => s -> μ α
- nncBounded :: (PositionalSystem s, Ord α, Bounded α, Integral α, Monad μ, CharParsing μ) => s -> μ α
- nnBits :: (BitSystem s, Num α, Bits α, Monad μ, CharParsing μ) => s -> μ α
- nncBits :: (BitSystem s, Num α, Bits α, Monad μ, CharParsing μ) => s -> μ α
- nnBitsUpTo :: (BitSystem s, Num α, Bits α, Monad μ, CharParsing μ) => s -> Int -> μ α
- nncBitsUpTo :: (BitSystem s, Num α, Bits α, Monad μ, CharParsing μ) => s -> Int -> μ α
- nnbBits :: (BitSystem s, Ord α, Bounded α, Num α, Bits α, Monad μ, CharParsing μ) => s -> μ α
- nncbBits :: (BitSystem s, Ord α, Bounded α, Num α, Bits α, Monad μ, CharParsing μ) => s -> μ α
- nonPositive :: (PositionalSystem s, Num α, Monad μ, CharParsing μ) => s -> μ α
- npCompact :: (PositionalSystem s, Num α, Monad μ, CharParsing μ) => s -> μ α
- npUpTo :: (PositionalSystem s, Num α, Monad μ, CharParsing μ) => s -> Int -> μ α
- npcUpTo :: (PositionalSystem s, Num α, Monad μ, CharParsing μ) => s -> Int -> μ α
- npBounded :: (PositionalSystem s, Ord α, Bounded α, Integral α, Monad μ, CharParsing μ) => s -> μ α
- npcBounded :: (PositionalSystem s, Ord α, Bounded α, Integral α, Monad μ, CharParsing μ) => s -> μ α
- npBits :: (BitSystem s, Num α, Bits α, Monad μ, CharParsing μ) => s -> μ α
- npcBits :: (BitSystem s, Num α, Bits α, Monad μ, CharParsing μ) => s -> μ α
- npBitsUpTo :: (BitSystem s, Num α, Bits α, Monad μ, CharParsing μ) => s -> Int -> μ α
- npcBitsUpTo :: (BitSystem s, Num α, Bits α, Monad μ, CharParsing μ) => s -> Int -> μ α
- npbBits :: forall s μ α. (BitSystem s, Ord α, Bounded α, Num α, Bits α, Monad μ, CharParsing μ) => s -> μ α
- npcbBits :: forall s μ α. (BitSystem s, Ord α, Bounded α, Num α, Bits α, Monad μ, CharParsing μ) => s -> μ α
- data Sign
- applySign :: Num α => Sign -> α -> α
- optMinus :: CharParsing μ => μ Sign
- optSign :: CharParsing μ => μ Sign
- number' :: (PositionalSystem s, Num α, Monad μ, CharParsing μ) => μ Sign -> s -> μ α
- number :: (PositionalSystem s, Num α, Monad μ, CharParsing μ) => s -> μ α
- compact' :: (PositionalSystem s, Num α, Monad μ, CharParsing μ) => μ Sign -> s -> μ α
- compact :: (PositionalSystem s, Num α, Monad μ, CharParsing μ) => s -> μ α
- numberUpTo' :: (PositionalSystem s, Num α, Monad μ, CharParsing μ) => μ Sign -> s -> Int -> μ α
- numberUpTo :: (PositionalSystem s, Num α, Monad μ, CharParsing μ) => s -> Int -> μ α
- compactUpTo' :: (PositionalSystem s, Num α, Monad μ, CharParsing μ) => μ Sign -> s -> Int -> μ α
- compactUpTo :: (PositionalSystem s, Num α, Monad μ, CharParsing μ) => s -> Int -> μ α
- bounded' :: (PositionalSystem s, Ord α, Bounded α, Integral α, Monad μ, CharParsing μ) => μ Sign -> s -> μ α
- bounded :: (PositionalSystem s, Ord α, Bounded α, Integral α, Monad μ, CharParsing μ) => s -> μ α
- cBounded' :: (PositionalSystem s, Ord α, Bounded α, Integral α, Monad μ, CharParsing μ) => μ Sign -> s -> μ α
- cBounded :: (PositionalSystem s, Ord α, Bounded α, Integral α, Monad μ, CharParsing μ) => s -> μ α
- bits' :: (BitSystem s, Num α, Bits α, Monad μ, CharParsing μ) => μ Sign -> s -> μ α
- bits :: (BitSystem s, Num α, Bits α, Monad μ, CharParsing μ) => s -> μ α
- cBits' :: (BitSystem s, Num α, Bits α, Monad μ, CharParsing μ) => μ Sign -> s -> μ α
- cBits :: (BitSystem s, Num α, Bits α, Monad μ, CharParsing μ) => s -> μ α
- bitsUpTo' :: (BitSystem s, Num α, Bits α, Monad μ, CharParsing μ) => μ Sign -> s -> Int -> μ α
- bitsUpTo :: (BitSystem s, Num α, Bits α, Monad μ, CharParsing μ) => s -> Int -> μ α
- cBitsUpTo' :: (BitSystem s, Num α, Bits α, Monad μ, CharParsing μ) => μ Sign -> s -> Int -> μ α
- cBitsUpTo :: (BitSystem s, Num α, Bits α, Monad μ, CharParsing μ) => s -> Int -> μ α
- bBits' :: (BitSystem s, Ord α, Bounded α, Num α, Bits α, Monad μ, CharParsing μ) => μ Sign -> s -> μ α
- bBits :: (BitSystem s, Ord α, Bounded α, Num α, Bits α, Monad μ, CharParsing μ) => s -> μ α
- cbBits' :: (BitSystem s, Ord α, Bounded α, Num α, Bits α, Monad μ, CharParsing μ) => μ Sign -> s -> μ α
- cbBits :: (BitSystem s, Ord α, Bounded α, Num α, Bits α, Monad μ, CharParsing μ) => s -> μ α
Positional numeral systems
class PositionalSystem s where #
Positional numeral system.
Minimal complete definition
systemName, radixIn, isDigitIn, isNzDigitIn, fromDigitIn, fromNzDigitIn, unsafeFromDigitIn, intToDigitIn
Methods
systemName :: s -> String #
The name of the system (e.g. "binary", "decimal").
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
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 | |
| Defined in Text.Printer.Integral Methods digitBitsIn :: Binary -> Int # digitMaskIn :: Num α => Binary -> α # lastDigitIn :: Bits α => Binary -> α -> Int # | |
| BitSystem Octal | |
| Defined in Text.Printer.Integral Methods digitBitsIn :: Octal -> Int # digitMaskIn :: Num α => Octal -> α # lastDigitIn :: Bits α => Octal -> α -> Int # | |
| BitSystem Hexadecimal | |
| Defined in Text.Printer.Integral Methods digitBitsIn :: Hexadecimal -> Int # digitMaskIn :: Num α => Hexadecimal -> α # lastDigitIn :: Bits α => Hexadecimal -> α -> Int # | |
| BitSystem LowHex | |
| Defined in Text.Printer.Integral Methods digitBitsIn :: LowHex -> Int # digitMaskIn :: Num α => LowHex -> α # lastDigitIn :: Bits α => LowHex -> α -> Int # | |
| BitSystem UpHex | |
| Defined in Text.Printer.Integral Methods digitBitsIn :: UpHex -> Int # digitMaskIn :: Num α => UpHex -> α # lastDigitIn :: Bits α => UpHex -> α -> Int # | |
The binary numeral system.
Constructors
| Binary | 
Instances
| Eq Binary | |
| Ord Binary | |
| Read Binary | |
| Show Binary | |
| Generic Binary | |
| PositionalSystem Binary | |
| 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 | |
| Defined in Text.Printer.Integral Methods digitBitsIn :: Binary -> Int # digitMaskIn :: Num α => Binary -> α # lastDigitIn :: Bits α => Binary -> α -> Int # | |
| type Rep Binary | |
The octal numeral system.
Constructors
| Octal | 
Instances
| Eq Octal | |
| Ord Octal | |
| Read Octal | |
| Show Octal | |
| Generic Octal | |
| PositionalSystem Octal | |
| 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 | |
| Defined in Text.Printer.Integral Methods digitBitsIn :: Octal -> Int # digitMaskIn :: Num α => Octal -> α # lastDigitIn :: Bits α => Octal -> α -> Int # | |
| type Rep Octal | |
The decimal numeral system.
Constructors
| Decimal | 
Instances
| Eq Decimal | |
| Ord Decimal | |
| Defined in Text.Printer.Integral | |
| Read Decimal | |
| Show Decimal | |
| Generic Decimal | |
| PositionalSystem Decimal | |
| Defined in Text.Printer.Integral Methods systemName :: Decimal -> String # radixIn :: Num α => Decimal -> α # isDigitIn :: Decimal -> Char -> Bool # isNzDigitIn :: Decimal -> Char -> Bool # fromDigitIn :: Num α => Decimal -> Char -> Maybe α # fromNzDigitIn :: Num α => Decimal -> Char -> Maybe α # unsafeFromDigitIn :: Num α => Decimal -> Char -> α # intToDigitIn :: Decimal -> Int -> Char # printDigitIn :: Printer p => Decimal -> Char -> p # printZeroIn :: Printer p => Decimal -> p # | |
| type Rep Decimal | |
data Hexadecimal #
The hexadecimal numeral system.
Constructors
| Hexadecimal | 
Instances
The hexadecimal numeral system, using lower case digits.
Constructors
| LowHex | 
Instances
| Eq LowHex | |
| Ord LowHex | |
| Read LowHex | |
| Show LowHex | |
| Generic LowHex | |
| PositionalSystem LowHex | |
| 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 | |
| Defined in Text.Printer.Integral Methods digitBitsIn :: LowHex -> Int # digitMaskIn :: Num α => LowHex -> α # lastDigitIn :: Bits α => LowHex -> α -> Int # | |
| type Rep LowHex | |
The hexadecimal numeral system, using upper case digits.
Constructors
| UpHex | 
Instances
| Eq UpHex | |
| Ord UpHex | |
| Read UpHex | |
| Show UpHex | |
| Generic UpHex | |
| PositionalSystem UpHex | |
| 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 | |
| Defined in Text.Printer.Integral Methods digitBitsIn :: UpHex -> Int # digitMaskIn :: Num α => UpHex -> α # lastDigitIn :: Bits α => UpHex -> α -> Int # | |
| type Rep 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.
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 μ => μ 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 #
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 #
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 #
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 #
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.
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.
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.
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 #
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.