text-printer-0.5.0.2: Abstract interface for text builders/printers.
Safe HaskellNone
LanguageHaskell2010

Text.Printer.Fractional

Description

Print fractions.

Synopsis

Positional numeral systems

class PositionalSystem s where Source #

Positional numeral system.

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

Instances details
PositionalSystem UpHex Source # 
Instance details

Defined in Text.Printer.Integral

PositionalSystem LowHex Source # 
Instance details

Defined in Text.Printer.Integral

PositionalSystem Hexadecimal Source # 
Instance details

Defined in Text.Printer.Integral

PositionalSystem Decimal Source # 
Instance details

Defined in Text.Printer.Integral

PositionalSystem Octal Source # 
Instance details

Defined in Text.Printer.Integral

PositionalSystem Binary Source # 
Instance details

Defined in Text.Printer.Integral

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

Instances details
BitSystem UpHex Source # 
Instance details

Defined in Text.Printer.Integral

Methods

digitBitsIn :: UpHex -> Int Source #

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

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

BitSystem LowHex Source # 
Instance details

Defined in Text.Printer.Integral

Methods

digitBitsIn :: LowHex -> Int Source #

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

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

BitSystem Hexadecimal Source # 
Instance details

Defined in Text.Printer.Integral

BitSystem Octal Source # 
Instance details

Defined in Text.Printer.Integral

Methods

digitBitsIn :: Octal -> Int Source #

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

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

BitSystem Binary Source # 
Instance details

Defined in Text.Printer.Integral

Methods

digitBitsIn :: Binary -> Int Source #

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

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

data Binary Source #

The binary numeral system.

Constructors

Binary 

Instances

Instances details
Eq Binary Source # 
Instance details

Defined in Text.Printer.Integral

Methods

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

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

Ord Binary Source # 
Instance details

Defined in Text.Printer.Integral

Read Binary Source # 
Instance details

Defined in Text.Printer.Integral

Show Binary Source # 
Instance details

Defined in Text.Printer.Integral

Generic Binary Source # 
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 #

BitSystem Binary Source # 
Instance details

Defined in Text.Printer.Integral

Methods

digitBitsIn :: Binary -> Int Source #

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

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

PositionalSystem Binary Source # 
Instance details

Defined in Text.Printer.Integral

type Rep Binary Source # 
Instance details

Defined in Text.Printer.Integral

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

data Octal Source #

The octal numeral system.

Constructors

Octal 

Instances

Instances details
Eq Octal Source # 
Instance details

Defined in Text.Printer.Integral

Methods

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

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

Ord Octal Source # 
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 Source # 
Instance details

Defined in Text.Printer.Integral

Show Octal Source # 
Instance details

Defined in Text.Printer.Integral

Methods

showsPrec :: Int -> Octal -> ShowS #

show :: Octal -> String #

showList :: [Octal] -> ShowS #

Generic Octal Source # 
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 #

BitSystem Octal Source # 
Instance details

Defined in Text.Printer.Integral

Methods

digitBitsIn :: Octal -> Int Source #

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

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

PositionalSystem Octal Source # 
Instance details

Defined in Text.Printer.Integral

type Rep Octal Source # 
Instance details

Defined in Text.Printer.Integral

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

data Decimal Source #

The decimal numeral system.

Constructors

Decimal 

Instances

Instances details
Eq Decimal Source # 
Instance details

Defined in Text.Printer.Integral

Methods

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

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

Ord Decimal Source # 
Instance details

Defined in Text.Printer.Integral

Read Decimal Source # 
Instance details

Defined in Text.Printer.Integral

Show Decimal Source # 
Instance details

Defined in Text.Printer.Integral

Generic Decimal Source # 
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 Source # 
Instance details

Defined in Text.Printer.Integral

type Rep Decimal Source # 
Instance details

Defined in Text.Printer.Integral

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

data Hexadecimal Source #

The hexadecimal numeral system.

Constructors

Hexadecimal 

Instances

Instances details
Eq Hexadecimal Source # 
Instance details

Defined in Text.Printer.Integral

Ord Hexadecimal Source # 
Instance details

Defined in Text.Printer.Integral

Read Hexadecimal Source # 
Instance details

Defined in Text.Printer.Integral

Show Hexadecimal Source # 
Instance details

Defined in Text.Printer.Integral

Generic Hexadecimal Source # 
Instance details

Defined in Text.Printer.Integral

Associated Types

type Rep Hexadecimal :: Type -> Type #

BitSystem Hexadecimal Source # 
Instance details

Defined in Text.Printer.Integral

PositionalSystem Hexadecimal Source # 
Instance details

Defined in Text.Printer.Integral

type Rep Hexadecimal Source # 
Instance details

Defined in Text.Printer.Integral

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

data LowHex Source #

The hexadecimal numeral system, using lower case digits.

Constructors

LowHex 

Instances

Instances details
Eq LowHex Source # 
Instance details

Defined in Text.Printer.Integral

Methods

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

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

Ord LowHex Source # 
Instance details

Defined in Text.Printer.Integral

Read LowHex Source # 
Instance details

Defined in Text.Printer.Integral

Show LowHex Source # 
Instance details

Defined in Text.Printer.Integral

Generic LowHex Source # 
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 #

BitSystem LowHex Source # 
Instance details

Defined in Text.Printer.Integral

Methods

digitBitsIn :: LowHex -> Int Source #

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

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

PositionalSystem LowHex Source # 
Instance details

Defined in Text.Printer.Integral

type Rep LowHex Source # 
Instance details

Defined in Text.Printer.Integral

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

data UpHex Source #

The hexadecimal numeral system, using upper case digits.

Constructors

UpHex 

Instances

Instances details
Eq UpHex Source # 
Instance details

Defined in Text.Printer.Integral

Methods

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

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

Ord UpHex Source # 
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 Source # 
Instance details

Defined in Text.Printer.Integral

Show UpHex Source # 
Instance details

Defined in Text.Printer.Integral

Methods

showsPrec :: Int -> UpHex -> ShowS #

show :: UpHex -> String #

showList :: [UpHex] -> ShowS #

Generic UpHex Source # 
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 #

BitSystem UpHex Source # 
Instance details

Defined in Text.Printer.Integral

Methods

digitBitsIn :: UpHex -> Int Source #

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

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

PositionalSystem UpHex Source # 
Instance details

Defined in Text.Printer.Integral

type Rep UpHex Source # 
Instance details

Defined in Text.Printer.Integral

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

Optionality characteristic

data Optional Source #

Optionality characteristic.

Constructors

Optional 
Required 

Instances

Instances details
Bounded Optional Source # 
Instance details

Defined in Text.Printer.Fractional

Enum Optional Source # 
Instance details

Defined in Text.Printer.Fractional

Eq Optional Source # 
Instance details

Defined in Text.Printer.Fractional

Ord Optional Source # 
Instance details

Defined in Text.Printer.Fractional

Read Optional Source # 
Instance details

Defined in Text.Printer.Fractional

Show Optional Source # 
Instance details

Defined in Text.Printer.Fractional

Ix Optional Source # 
Instance details

Defined in Text.Printer.Fractional

Generic Optional Source # 
Instance details

Defined in Text.Printer.Fractional

Associated Types

type Rep Optional :: Type -> Type #

Methods

from :: Optional -> Rep Optional x #

to :: Rep Optional x -> Optional #

type Rep Optional Source # 
Instance details

Defined in Text.Printer.Fractional

type Rep Optional = D1 ('MetaData "Optional" "Text.Printer.Fractional" "text-printer-0.5.0.2-FlLDfrY0w204KWMtyVLEfo" 'False) (C1 ('MetaCons "Optional" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Required" 'PrefixI 'False) (U1 :: Type -> Type))

isOptional :: Optional -> Bool Source #

True if the supplied value is Optional and false otherwise.

isRequired :: Optional -> Bool Source #

True if the supplied value is Required and false otherwise.

Fraction printers

fraction' Source #

Arguments

:: (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.

fraction :: (Real α, Printer p) => α -> p Source #

Print a fraction. The numerator and the denominator are written in the decimal numeral system and separated by a slash. Negative values are prefixed with a minus sign. Invisible denominators are omitted.