| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Text.Printer.Integral
Description
Print integral numbers in common 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
- nonNegative :: (PositionalSystem s, Integral α, Printer p) => s -> α -> p
- nnBinary :: (Integral α, Printer p) => α -> p
- nnOctal :: (Integral α, Printer p) => α -> p
- nnDecimal :: (Integral α, Printer p) => α -> p
- nnLowHex :: (Integral α, Printer p) => α -> p
- nnUpHex :: (Integral α, Printer p) => α -> p
- nnBits :: (BitSystem s, Num α, Bits α, Printer p) => s -> α -> p
- nnBinaryBits :: (Num α, Bits α, Printer p) => α -> p
- nnOctalBits :: (Num α, Bits α, Printer p) => α -> p
- nnLowHexBits :: (Num α, Bits α, Printer p) => α -> p
- nnUpHexBits :: (Num α, Bits α, Printer p) => α -> p
- nonPositive :: (PositionalSystem s, Integral α, Printer p) => s -> α -> p
- npBinary :: (Integral α, Printer p) => α -> p
- npOctal :: (Integral α, Printer p) => α -> p
- npDecimal :: (Integral α, Printer p) => α -> p
- npLowHex :: (Integral α, Printer p) => α -> p
- npUpHex :: (Integral α, Printer p) => α -> p
- npBits :: (BitSystem s, Ord α, Num α, Bits α, Printer p) => s -> α -> p
- npBinaryBits :: (Ord α, Num α, Bits α, Printer p) => α -> p
- npOctalBits :: (Ord α, Num α, Bits α, Printer p) => α -> p
- npLowHexBits :: (Ord α, Num α, Bits α, Printer p) => α -> p
- npUpHexBits :: (Ord α, Num α, Bits α, Printer p) => α -> p
- number' :: (PositionalSystem s, Integral α, Printer p) => s -> p -> p -> p -> α -> p
- number :: (PositionalSystem s, Integral α, Printer p) => s -> α -> p
- binary' :: (Integral α, Printer p) => p -> p -> p -> α -> p
- binary :: (Integral α, Printer p) => α -> p
- octal' :: (Integral α, Printer p) => p -> p -> p -> α -> p
- octal :: (Integral α, Printer p) => α -> p
- decimal' :: (Integral α, Printer p) => p -> p -> p -> α -> p
- decimal :: (Integral α, Printer p) => α -> p
- lowHex' :: (Integral α, Printer p) => p -> p -> p -> α -> p
- lowHex :: (Integral α, Printer p) => α -> p
- upHex' :: (Integral α, Printer p) => p -> p -> p -> α -> p
- upHex :: (Integral α, Printer p) => α -> p
- bits' :: (BitSystem s, Ord α, Num α, Bits α, Printer p) => s -> p -> p -> p -> α -> p
- bits :: (BitSystem s, Ord α, Num α, Bits α, Printer p) => s -> α -> p
- binaryBits' :: (Ord α, Num α, Bits α, Printer p) => p -> p -> p -> α -> p
- binaryBits :: (Ord α, Num α, Bits α, Printer p) => α -> p
- octalBits' :: (Ord α, Num α, Bits α, Printer p) => p -> p -> p -> α -> p
- octalBits :: (Ord α, Num α, Bits α, Printer p) => α -> p
- lowHexBits' :: (Ord α, Num α, Bits α, Printer p) => p -> p -> p -> α -> p
- lowHexBits :: (Ord α, Num α, Bits α, Printer p) => α -> p
- upHexBits' :: (Ord α, Num α, Bits α, Printer p) => p -> p -> p -> α -> p
- upHexBits :: (Ord α, Num α, Bits α, Printer p) => α -> p
Positional systems
class PositionalSystem s where Source #
Positional numeral system.
Minimal complete definition
systemName, radixIn, isDigitIn, isNzDigitIn, fromDigitIn, fromNzDigitIn, unsafeFromDigitIn, intToDigitIn
Methods
systemName :: s -> String Source #
The name of the system (e.g. "binary", "decimal").
radixIn :: Num α => s -> α Source #
The radix of the system.
isDigitIn :: s -> Char -> Bool Source #
Test if a character is a digit.
isNzDigitIn :: s -> Char -> Bool Source #
Test if a character is a non-zero digit.
fromDigitIn :: Num α => s -> Char -> Maybe α Source #
Map digits to the corresponding numbers. Return Nothing on
   other inputs.
fromNzDigitIn :: Num α => s -> Char -> Maybe α Source #
Map non-zero digits to the corresponding numbers. Return Nothing on
   other inputs.
unsafeFromDigitIn :: Num α => s -> Char -> α Source #
Map digits to the corresponding numbers. No checks are performed.
intToDigitIn :: s -> Int -> Char Source #
Map Int values to the corresponding digits. Inputs must be
   non-negative and less than the radix.
printDigitIn :: Printer p => s -> Char -> p Source #
Print a digit.
printZeroIn :: Printer p => s -> p Source #
Instances
class PositionalSystem s => BitSystem s where Source #
Positonal numeral system with a power of two radix.
Methods
digitBitsIn :: s -> Int Source #
Numer of bits occupied by a digit.
digitMaskIn :: Num α => s -> α Source #
The number that has digitBitsIn least significant bits set to ones
   and all the other bits set to zeroes.
lastDigitIn :: Bits α => s -> α -> Int Source #
Map the last digit of a number to the corresponding Int value.
Instances
| BitSystem UpHex Source # | |
| Defined in Text.Printer.Integral | |
| BitSystem LowHex Source # | |
| Defined in Text.Printer.Integral | |
| BitSystem Hexadecimal Source # | |
| Defined in Text.Printer.Integral Methods digitBitsIn :: Hexadecimal -> Int Source # digitMaskIn :: Num α => Hexadecimal -> α Source # lastDigitIn :: Bits α => Hexadecimal -> α -> Int Source # | |
| BitSystem Octal Source # | |
| Defined in Text.Printer.Integral | |
| BitSystem Binary Source # | |
| Defined in Text.Printer.Integral | |
The binary numeral system.
Constructors
| Binary | 
Instances
| Eq Binary Source # | |
| Ord Binary Source # | |
| Read Binary Source # | |
| Show Binary Source # | |
| Generic Binary Source # | |
| BitSystem Binary Source # | |
| Defined in Text.Printer.Integral | |
| PositionalSystem Binary Source # | |
| Defined in Text.Printer.Integral Methods systemName :: Binary -> String Source # radixIn :: Num α => Binary -> α Source # isDigitIn :: Binary -> Char -> Bool Source # isNzDigitIn :: Binary -> Char -> Bool Source # fromDigitIn :: Num α => Binary -> Char -> Maybe α Source # fromNzDigitIn :: Num α => Binary -> Char -> Maybe α Source # unsafeFromDigitIn :: Num α => Binary -> Char -> α Source # intToDigitIn :: Binary -> Int -> Char Source # printDigitIn :: Printer p => Binary -> Char -> p Source # printZeroIn :: Printer p => Binary -> p Source # | |
| type Rep Binary Source # | |
The octal numeral system.
Constructors
| Octal | 
Instances
| Eq Octal Source # | |
| Ord Octal Source # | |
| Read Octal Source # | |
| Show Octal Source # | |
| Generic Octal Source # | |
| BitSystem Octal Source # | |
| Defined in Text.Printer.Integral | |
| PositionalSystem Octal Source # | |
| Defined in Text.Printer.Integral Methods systemName :: Octal -> String Source # radixIn :: Num α => Octal -> α Source # isDigitIn :: Octal -> Char -> Bool Source # isNzDigitIn :: Octal -> Char -> Bool Source # fromDigitIn :: Num α => Octal -> Char -> Maybe α Source # fromNzDigitIn :: Num α => Octal -> Char -> Maybe α Source # unsafeFromDigitIn :: Num α => Octal -> Char -> α Source # intToDigitIn :: Octal -> Int -> Char Source # printDigitIn :: Printer p => Octal -> Char -> p Source # printZeroIn :: Printer p => Octal -> p Source # | |
| type Rep Octal Source # | |
The decimal numeral system.
Constructors
| Decimal | 
Instances
| Eq Decimal Source # | |
| Ord Decimal Source # | |
| Defined in Text.Printer.Integral | |
| Read Decimal Source # | |
| Show Decimal Source # | |
| Generic Decimal Source # | |
| PositionalSystem Decimal Source # | |
| Defined in Text.Printer.Integral Methods systemName :: Decimal -> String Source # radixIn :: Num α => Decimal -> α Source # isDigitIn :: Decimal -> Char -> Bool Source # isNzDigitIn :: Decimal -> Char -> Bool Source # fromDigitIn :: Num α => Decimal -> Char -> Maybe α Source # fromNzDigitIn :: Num α => Decimal -> Char -> Maybe α Source # unsafeFromDigitIn :: Num α => Decimal -> Char -> α Source # intToDigitIn :: Decimal -> Int -> Char Source # printDigitIn :: Printer p => Decimal -> Char -> p Source # printZeroIn :: Printer p => Decimal -> p Source # | |
| type Rep Decimal Source # | |
data Hexadecimal Source #
The hexadecimal numeral system.
Constructors
| Hexadecimal | 
Instances
The hexadecimal numeral system, using lower case digits.
Constructors
| LowHex | 
Instances
| Eq LowHex Source # | |
| Ord LowHex Source # | |
| Read LowHex Source # | |
| Show LowHex Source # | |
| Generic LowHex Source # | |
| BitSystem LowHex Source # | |
| Defined in Text.Printer.Integral | |
| PositionalSystem LowHex Source # | |
| Defined in Text.Printer.Integral Methods systemName :: LowHex -> String Source # radixIn :: Num α => LowHex -> α Source # isDigitIn :: LowHex -> Char -> Bool Source # isNzDigitIn :: LowHex -> Char -> Bool Source # fromDigitIn :: Num α => LowHex -> Char -> Maybe α Source # fromNzDigitIn :: Num α => LowHex -> Char -> Maybe α Source # unsafeFromDigitIn :: Num α => LowHex -> Char -> α Source # intToDigitIn :: LowHex -> Int -> Char Source # printDigitIn :: Printer p => LowHex -> Char -> p Source # printZeroIn :: Printer p => LowHex -> p Source # | |
| type Rep LowHex Source # | |
The hexadecimal numeral system, using upper case digits.
Constructors
| UpHex | 
Instances
| Eq UpHex Source # | |
| Ord UpHex Source # | |
| Read UpHex Source # | |
| Show UpHex Source # | |
| Generic UpHex Source # | |
| BitSystem UpHex Source # | |
| Defined in Text.Printer.Integral | |
| PositionalSystem UpHex Source # | |
| Defined in Text.Printer.Integral Methods systemName :: UpHex -> String Source # radixIn :: Num α => UpHex -> α Source # isDigitIn :: UpHex -> Char -> Bool Source # isNzDigitIn :: UpHex -> Char -> Bool Source # fromDigitIn :: Num α => UpHex -> Char -> Maybe α Source # fromNzDigitIn :: Num α => UpHex -> Char -> Maybe α Source # unsafeFromDigitIn :: Num α => UpHex -> Char -> α Source # intToDigitIn :: UpHex -> Int -> Char Source # printDigitIn :: Printer p => UpHex -> Char -> p Source # printZeroIn :: Printer p => UpHex -> p Source # | |
| type Rep UpHex Source # | |
Numeral printers
nonNegative :: (PositionalSystem s, Integral α, Printer p) => s -> α -> p Source #
Print a non-negative number in the specified positional numeral system.
nnBinary :: (Integral α, Printer p) => α -> p Source #
Print a non-negative number in the binary numeral system.
nnOctal :: (Integral α, Printer p) => α -> p Source #
Print a non-negative number in the octal numeral system.
nnDecimal :: (Integral α, Printer p) => α -> p Source #
Print a non-negative number in the decimal numeral system.
nnLowHex :: (Integral α, Printer p) => α -> p Source #
Print a non-negative number in the hexadecimal numeral system using lower case digits.
nnUpHex :: (Integral α, Printer p) => α -> p Source #
Print a non-negative number in the hexadecimal numeral system using upper case digits.
nnBits :: (BitSystem s, Num α, Bits α, Printer p) => s -> α -> p Source #
Print a non-negative binary number in the specified positional numeral system.
nnBinaryBits :: (Num α, Bits α, Printer p) => α -> p Source #
Print a non-negative binary number in the binary numeral system.
nnOctalBits :: (Num α, Bits α, Printer p) => α -> p Source #
Print a non-negative binary number in the octal numeral system.
nnLowHexBits :: (Num α, Bits α, Printer p) => α -> p Source #
Print a non-negative binary number in the hexadecimal numeral system using lower case digits.
nnUpHexBits :: (Num α, Bits α, Printer p) => α -> p Source #
Print a non-negative binary number in the hexadecimal numeral system using upper case digits.
nonPositive :: (PositionalSystem s, Integral α, Printer p) => s -> α -> p Source #
Print a non-positive number in the specified positional numeral system.
   For example, nonPositive Decimal (-123)
npBinary :: (Integral α, Printer p) => α -> p Source #
Print a non-positive number in the binary numeral system.
npOctal :: (Integral α, Printer p) => α -> p Source #
Print a non-positive number in the octal numeral system.
npDecimal :: (Integral α, Printer p) => α -> p Source #
Print a non-positive number in the decimal numeral system.
npLowHex :: (Integral α, Printer p) => α -> p Source #
Print a non-positive number in the hexadecimal numeral system using lower case digits.
npUpHex :: (Integral α, Printer p) => α -> p Source #
Print a non-positive number in the hexadecimal numeral system using upper case digits.
npBinaryBits :: (Ord α, Num α, Bits α, Printer p) => α -> p Source #
Print a non-positive binary number in the binary numeral system.
npOctalBits :: (Ord α, Num α, Bits α, Printer p) => α -> p Source #
Print a non-positive binary number in the octal numeral system.
npLowHexBits :: (Ord α, Num α, Bits α, Printer p) => α -> p Source #
Print a non-positive binary number in the hexadecimal numeral system using lower case digits.
npUpHexBits :: (Ord α, Num α, Bits α, Printer p) => α -> p Source #
Print a non-positive binary number in the hexadecimal numeral system using upper case digits.
Arguments
| :: (PositionalSystem s, Integral α, Printer p) | |
| => s | |
| -> p | Prefix for negative values | 
| -> p | Zero printer | 
| -> p | Prefix for positive values | 
| -> α | |
| -> p | 
Print a number in the specified positional numeral system.
number :: (PositionalSystem s, Integral α, Printer p) => s -> α -> p Source #
Print a number in the specified positional numeral system. Negative values are prefixed with a minus sign.
Arguments
| :: (Integral α, Printer p) | |
| => p | Prefix for negative values | 
| -> p | Zero printer | 
| -> p | Prefix for positive values | 
| -> α | |
| -> p | 
Print a number in the binary numeral system.
binary :: (Integral α, Printer p) => α -> p Source #
Print a number in the binary numeral system. Negative values are prefixed with a minus sign.
Arguments
| :: (Integral α, Printer p) | |
| => p | Prefix for negative values | 
| -> p | Zero printer | 
| -> p | Prefix for positive values | 
| -> α | |
| -> p | 
Print a number in the octal numeral system.
octal :: (Integral α, Printer p) => α -> p Source #
Print a number in the octal numeral system. Negative values are prefixed with a minus sign.
Arguments
| :: (Integral α, Printer p) | |
| => p | Prefix for negative values | 
| -> p | Zero printer | 
| -> p | Prefix for positive values | 
| -> α | |
| -> p | 
Print a number in the decimal numeral system.
decimal :: (Integral α, Printer p) => α -> p Source #
Print a number in the decimal numeral system. Negative values are prefixed with a minus sign.
Arguments
| :: (Integral α, Printer p) | |
| => p | Prefix for negative values | 
| -> p | Zero printer | 
| -> p | Prefix for positive values | 
| -> α | |
| -> p | 
Print a number in the hexadecimal numeral system using lower case digits.
lowHex :: (Integral α, Printer p) => α -> p Source #
Print a number in the hexadecimal numeral system using lower case digits. Negative values are prefixed with a minus sign.
Arguments
| :: (Integral α, Printer p) | |
| => p | Prefix for negative values | 
| -> p | Zero printer | 
| -> p | Prefix for positive values | 
| -> α | |
| -> p | 
Print a number in the hexadecimal numeral system using upper case digits.
upHex :: (Integral α, Printer p) => α -> p Source #
Print a number in the hexadecimal numeral system using upper case digits. Negative values are prefixed with a minus sign.
Arguments
| :: (BitSystem s, Ord α, Num α, Bits α, Printer p) | |
| => s | |
| -> p | Prefix for negative values | 
| -> p | Zero printer | 
| -> p | Prefix for positive values | 
| -> α | |
| -> p | 
Print a binary number in the specified positional numeral system.
bits :: (BitSystem s, Ord α, Num α, Bits α, Printer p) => s -> α -> p Source #
Print a binary number in the specified positional numeral system. Negative values are prefixed with a minus sign.
Arguments
| :: (Ord α, Num α, Bits α, Printer p) | |
| => p | Prefix for negative values | 
| -> p | Zero printer | 
| -> p | Prefix for positive values | 
| -> α | |
| -> p | 
Print a binary number in the binary numeral system.
binaryBits :: (Ord α, Num α, Bits α, Printer p) => α -> p Source #
Print a binary number in the binary numeral system. Negative values are prefixed with a minus sign.
Arguments
| :: (Ord α, Num α, Bits α, Printer p) | |
| => p | Prefix for negative values | 
| -> p | Zero printer | 
| -> p | Prefix for positive values | 
| -> α | |
| -> p | 
Print a binary number in the octal numeral system.
octalBits :: (Ord α, Num α, Bits α, Printer p) => α -> p Source #
Print a binary number in the octal numeral system. Negative values are prefixed with a minus sign.
Arguments
| :: (Ord α, Num α, Bits α, Printer p) | |
| => p | Prefix for negative values | 
| -> p | Zero printer | 
| -> p | Prefix for positive values | 
| -> α | |
| -> p | 
Print a binary number in the hexadecimal numeral system using lower case digits.
lowHexBits :: (Ord α, Num α, Bits α, Printer p) => α -> p Source #
Print a binary number in the hexadecimal numeral system using lower case digits. Negative values are prefixed with a minus sign.