Safe Haskell | None |
---|---|
Language | Haskell2010 |
Print fractions.
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
- data Optional
- isOptional :: Optional -> Bool
- isRequired :: Optional -> Bool
- fraction' :: (PositionalSystem s, Real α, Printer p) => s -> p -> p -> p -> p -> Optional -> α -> p
- fraction :: (Real α, Printer p) => α -> p
Positional numeral systems
class PositionalSystem s where Source #
Positional numeral system.
systemName, radixIn, isDigitIn, isNzDigitIn, fromDigitIn, fromNzDigitIn, unsafeFromDigitIn, intToDigitIn
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.
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 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.
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 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.
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 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.
Instances
Eq Decimal Source # | |
Ord Decimal Source # | |
Read Decimal Source # | |
Show Decimal Source # | |
Generic Decimal Source # | |
PositionalSystem Decimal Source # | |
Defined in Text.Printer.Integral 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.
Instances
The hexadecimal numeral system, using lower case digits.
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 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.
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 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 # | |
Optionality characteristic
Optionality characteristic.
Instances
Bounded Optional Source # | |
Enum Optional Source # | |
Eq Optional Source # | |
Ord Optional Source # | |
Defined in Text.Printer.Fractional | |
Read Optional Source # | |
Show Optional Source # | |
Ix Optional Source # | |
Defined in Text.Printer.Fractional | |
Generic Optional Source # | |
type Rep Optional Source # | |
Fraction printers
:: (PositionalSystem s, Real α, Printer p) | |
=> s | |
-> p | Prefix for negative values |
-> p | Zero printer |
-> p | Prefix for positive values |
-> p | Numerator/denominator separator |
-> Optional | Whether to print invisible denominators |
-> α | |
-> p |
Print a fraction, writing the numerator and the denominator in the specified positional numeral system.