{-# LANGUAGE CPP #-}
{-# LANGUAGE UnicodeSyntax #-}
{-# LANGUAGE DeriveDataTypeable #-}
#if __GLASGOW_HASKELL__ >= 706
{-# LANGUAGE DeriveGeneric #-}
#endif
{-# LANGUAGE BangPatterns #-}

-- | Print integral numbers in common positional numeral systems. 
module Text.Printer.Integral
  (
  -- * Positional systems
    PositionalSystem(..)
  , BitSystem(..)
  , Binary(..)
  , Octal(..)
  , Decimal(..)
  , Hexadecimal(..)
  , LowHex(..)
  , UpHex(..)
  -- * Numeral printers
  , nonNegative
  , nnBinary
  , nnOctal
  , nnDecimal
  , nnLowHex
  , nnUpHex
  , nnBits
  , nnBinaryBits
  , nnOctalBits
  , nnLowHexBits
  , nnUpHexBits
  , nonPositive
  , npBinary
  , npOctal
  , npDecimal
  , npLowHex
  , npUpHex
  , npBits
  , npBinaryBits
  , npOctalBits
  , npLowHexBits
  , npUpHexBits
  , number'
  , number
  , binary'
  , binary
  , octal'
  , octal
  , decimal'
  , decimal
  , lowHex'
  , lowHex
  , upHex'
  , upHex
  , bits'
  , bits
  , binaryBits'
  , binaryBits
  , octalBits'
  , octalBits
  , lowHexBits'
  , lowHexBits
  , upHexBits'
  , upHexBits
  ) where

#if __GLASGOW_HASKELL__ >= 706
import GHC.Generics (Generic)
#endif
import Data.Typeable (Typeable)
import Data.Char (chr, ord)
import Data.Int
import Data.Word
import Data.Bits (Bits(..))
import Data.Monoid (mempty)
import qualified Text.Ascii as A
import Text.Printer

-- | Positional numeral system.
class PositionalSystem s where
  -- | The name of the system (e.g. \"binary\", \"decimal\").
  systemName  s  String
  -- | The radix of the system.
  radixIn  Num α  s  α
  -- | Test if a character is a digit.
  isDigitIn  s  Char  Bool
  -- | Test if a character is a non-zero digit.
  isNzDigitIn  s  Char  Bool
  -- | Map digits to the corresponding numbers. Return 'Nothing' on
  --   other inputs.
  fromDigitIn  Num α  s  Char  Maybe α
  -- | Map non-zero digits to the corresponding numbers. Return 'Nothing' on
  --   other inputs.
  fromNzDigitIn  Num α  s  Char  Maybe α
  -- | Map digits to the corresponding numbers. No checks are performed.
  unsafeFromDigitIn  Num α  s  Char  α
  -- | Map 'Int' values to the corresponding digits. Inputs /must/ be
  --   non-negative and less than the radix.
  intToDigitIn  s  Int  Char
  -- | Print a digit.
  printDigitIn  Printer p  s  Char  p
  printDigitIn s
_ = Char -> p
forall p. Printer p => Char -> p
char7
  {-# INLINE printDigitIn #-}
  printZeroIn  Printer p  s  p
  printZeroIn s
s = s -> Char -> p
forall s p. (PositionalSystem s, Printer p) => s -> Char -> p
printDigitIn s
s (Char -> p) -> Char -> p
forall a b. (a -> b) -> a -> b
$! s -> Int -> Char
forall s. PositionalSystem s => s -> Int -> Char
intToDigitIn s
s Int
0
  {-# INLINE printZeroIn #-}

-- | Positonal numeral system with a power of two radix.
class PositionalSystem s  BitSystem s where
  -- | Numer of bits occupied by a digit.
  digitBitsIn  s  Int
  -- | The number that has 'digitBitsIn' least significant bits set to ones
  --   and all the other bits set to zeroes.
  digitMaskIn  Num α  s  α
  -- | Map the last digit of a number to the corresponding 'Int' value.
  lastDigitIn  Bits α  s  α  Int

-- | The binary numeral system.
data Binary = Binary deriving ( Typeable
#if __GLASGOW_HASKELL__ >= 706
                              , (forall x. Binary -> Rep Binary x)
-> (forall x. Rep Binary x -> Binary) -> Generic Binary
forall x. Rep Binary x -> Binary
forall x. Binary -> Rep Binary x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Binary x -> Binary
$cfrom :: forall x. Binary -> Rep Binary x
Generic
#endif
                              , Binary -> Binary -> Bool
(Binary -> Binary -> Bool)
-> (Binary -> Binary -> Bool) -> Eq Binary
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Binary -> Binary -> Bool
$c/= :: Binary -> Binary -> Bool
== :: Binary -> Binary -> Bool
$c== :: Binary -> Binary -> Bool
Eq, Eq Binary
Eq Binary
-> (Binary -> Binary -> Ordering)
-> (Binary -> Binary -> Bool)
-> (Binary -> Binary -> Bool)
-> (Binary -> Binary -> Bool)
-> (Binary -> Binary -> Bool)
-> (Binary -> Binary -> Binary)
-> (Binary -> Binary -> Binary)
-> Ord Binary
Binary -> Binary -> Bool
Binary -> Binary -> Ordering
Binary -> Binary -> Binary
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Binary -> Binary -> Binary
$cmin :: Binary -> Binary -> Binary
max :: Binary -> Binary -> Binary
$cmax :: Binary -> Binary -> Binary
>= :: Binary -> Binary -> Bool
$c>= :: Binary -> Binary -> Bool
> :: Binary -> Binary -> Bool
$c> :: Binary -> Binary -> Bool
<= :: Binary -> Binary -> Bool
$c<= :: Binary -> Binary -> Bool
< :: Binary -> Binary -> Bool
$c< :: Binary -> Binary -> Bool
compare :: Binary -> Binary -> Ordering
$ccompare :: Binary -> Binary -> Ordering
$cp1Ord :: Eq Binary
Ord, Int -> Binary -> ShowS
[Binary] -> ShowS
Binary -> String
(Int -> Binary -> ShowS)
-> (Binary -> String) -> ([Binary] -> ShowS) -> Show Binary
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Binary] -> ShowS
$cshowList :: [Binary] -> ShowS
show :: Binary -> String
$cshow :: Binary -> String
showsPrec :: Int -> Binary -> ShowS
$cshowsPrec :: Int -> Binary -> ShowS
Show, ReadPrec [Binary]
ReadPrec Binary
Int -> ReadS Binary
ReadS [Binary]
(Int -> ReadS Binary)
-> ReadS [Binary]
-> ReadPrec Binary
-> ReadPrec [Binary]
-> Read Binary
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Binary]
$creadListPrec :: ReadPrec [Binary]
readPrec :: ReadPrec Binary
$creadPrec :: ReadPrec Binary
readList :: ReadS [Binary]
$creadList :: ReadS [Binary]
readsPrec :: Int -> ReadS Binary
$creadsPrec :: Int -> ReadS Binary
Read )

instance PositionalSystem Binary where
  systemName :: Binary -> String
systemName Binary
_ = String
"binary"
  {-# INLINE systemName #-}
  radixIn :: Binary -> α
radixIn Binary
_ = α
2
  {-# INLINE radixIn #-}
  isDigitIn :: Binary -> Char -> Bool
isDigitIn Binary
_ = Char -> Bool
A.isBinDigit
  {-# INLINE isDigitIn #-}
  isNzDigitIn :: Binary -> Char -> Bool
isNzDigitIn Binary
_ = Char -> Bool
A.isNzBinDigit
  {-# INLINE isNzDigitIn #-}
  fromDigitIn :: Binary -> Char -> Maybe α
fromDigitIn Binary
_ = Char -> Maybe α
forall a. Num a => Char -> Maybe a
A.fromBinDigit
  {-# INLINE fromDigitIn #-}
  fromNzDigitIn :: Binary -> Char -> Maybe α
fromNzDigitIn Binary
_ = Char -> Maybe α
forall a. Num a => Char -> Maybe a
A.fromNzBinDigit
  {-# INLINE fromNzDigitIn #-}
  unsafeFromDigitIn :: Binary -> Char -> α
unsafeFromDigitIn Binary
_ = Char -> α
forall a. Num a => Char -> a
A.unsafeFromBinDigit
  {-# INLINE unsafeFromDigitIn #-}
  intToDigitIn :: Binary -> Int -> Char
intToDigitIn Binary
_ Int
i = Int -> Char
chr (Int -> Char) -> Int -> Char
forall a b. (a -> b) -> a -> b
$! Char -> Int
ord Char
'0' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
i
  {-# INLINE intToDigitIn #-}
  printZeroIn :: Binary -> p
printZeroIn Binary
_ = Char -> p
forall p. Printer p => Char -> p
char7 Char
'0'
  {-# INLINE printZeroIn #-}

instance BitSystem Binary where
  digitBitsIn :: Binary -> Int
digitBitsIn Binary
_ = Int
1
  {-# INLINE digitBitsIn #-}
  digitMaskIn :: Binary -> α
digitMaskIn Binary
_ = α
1
  {-# INLINE digitMaskIn #-}
  lastDigitIn :: Binary -> α -> Int
lastDigitIn Binary
_ α
n = if α -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit α
n Int
0 then Int
1 else Int
0
  {-# INLINE lastDigitIn #-}

-- | The octal numeral system.
data Octal = Octal deriving ( Typeable
#if __GLASGOW_HASKELL__ >= 706
                            , (forall x. Octal -> Rep Octal x)
-> (forall x. Rep Octal x -> Octal) -> Generic Octal
forall x. Rep Octal x -> Octal
forall x. Octal -> Rep Octal x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Octal x -> Octal
$cfrom :: forall x. Octal -> Rep Octal x
Generic
#endif
                            , Octal -> Octal -> Bool
(Octal -> Octal -> Bool) -> (Octal -> Octal -> Bool) -> Eq Octal
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Octal -> Octal -> Bool
$c/= :: Octal -> Octal -> Bool
== :: Octal -> Octal -> Bool
$c== :: Octal -> Octal -> Bool
Eq, Eq Octal
Eq Octal
-> (Octal -> Octal -> Ordering)
-> (Octal -> Octal -> Bool)
-> (Octal -> Octal -> Bool)
-> (Octal -> Octal -> Bool)
-> (Octal -> Octal -> Bool)
-> (Octal -> Octal -> Octal)
-> (Octal -> Octal -> Octal)
-> Ord Octal
Octal -> Octal -> Bool
Octal -> Octal -> Ordering
Octal -> Octal -> Octal
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Octal -> Octal -> Octal
$cmin :: Octal -> Octal -> Octal
max :: Octal -> Octal -> Octal
$cmax :: Octal -> Octal -> Octal
>= :: Octal -> Octal -> Bool
$c>= :: Octal -> Octal -> Bool
> :: Octal -> Octal -> Bool
$c> :: Octal -> Octal -> Bool
<= :: Octal -> Octal -> Bool
$c<= :: Octal -> Octal -> Bool
< :: Octal -> Octal -> Bool
$c< :: Octal -> Octal -> Bool
compare :: Octal -> Octal -> Ordering
$ccompare :: Octal -> Octal -> Ordering
$cp1Ord :: Eq Octal
Ord, Int -> Octal -> ShowS
[Octal] -> ShowS
Octal -> String
(Int -> Octal -> ShowS)
-> (Octal -> String) -> ([Octal] -> ShowS) -> Show Octal
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Octal] -> ShowS
$cshowList :: [Octal] -> ShowS
show :: Octal -> String
$cshow :: Octal -> String
showsPrec :: Int -> Octal -> ShowS
$cshowsPrec :: Int -> Octal -> ShowS
Show, ReadPrec [Octal]
ReadPrec Octal
Int -> ReadS Octal
ReadS [Octal]
(Int -> ReadS Octal)
-> ReadS [Octal]
-> ReadPrec Octal
-> ReadPrec [Octal]
-> Read Octal
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Octal]
$creadListPrec :: ReadPrec [Octal]
readPrec :: ReadPrec Octal
$creadPrec :: ReadPrec Octal
readList :: ReadS [Octal]
$creadList :: ReadS [Octal]
readsPrec :: Int -> ReadS Octal
$creadsPrec :: Int -> ReadS Octal
Read )

instance PositionalSystem Octal where
  systemName :: Octal -> String
systemName Octal
_ = String
"octal"
  {-# INLINE systemName #-}
  radixIn :: Octal -> α
radixIn Octal
_ = α
8
  {-# INLINE radixIn #-}
  isDigitIn :: Octal -> Char -> Bool
isDigitIn Octal
_ = Char -> Bool
A.isOctDigit
  {-# INLINE isDigitIn #-}
  isNzDigitIn :: Octal -> Char -> Bool
isNzDigitIn Octal
_ = Char -> Bool
A.isNzOctDigit
  {-# INLINE isNzDigitIn #-}
  fromDigitIn :: Octal -> Char -> Maybe α
fromDigitIn Octal
_ = Char -> Maybe α
forall a. Num a => Char -> Maybe a
A.fromOctDigit
  {-# INLINE fromDigitIn #-}
  fromNzDigitIn :: Octal -> Char -> Maybe α
fromNzDigitIn Octal
_ = Char -> Maybe α
forall a. Num a => Char -> Maybe a
A.fromNzOctDigit
  {-# INLINE fromNzDigitIn #-}
  unsafeFromDigitIn :: Octal -> Char -> α
unsafeFromDigitIn Octal
_ = Char -> α
forall a. Num a => Char -> a
A.unsafeFromOctDigit
  {-# INLINE unsafeFromDigitIn #-}
  intToDigitIn :: Octal -> Int -> Char
intToDigitIn Octal
_ Int
i = Int -> Char
chr (Int -> Char) -> Int -> Char
forall a b. (a -> b) -> a -> b
$! Char -> Int
ord Char
'0' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
i
  {-# INLINE intToDigitIn #-}
  printZeroIn :: Octal -> p
printZeroIn Octal
_ = Char -> p
forall p. Printer p => Char -> p
char7 Char
'0'
  {-# INLINE printZeroIn #-}

instance BitSystem Octal where
  digitBitsIn :: Octal -> Int
digitBitsIn Octal
_ = Int
3
  {-# INLINE digitBitsIn #-}
  digitMaskIn :: Octal -> α
digitMaskIn Octal
_ = α
7
  {-# INLINE digitMaskIn #-}
  lastDigitIn :: Octal -> α -> Int
lastDigitIn Octal
_ α
n = (if α -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit α
n Int
0 then Int
1 else Int
0)
                  Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (if α -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit α
n Int
1 then Int
2 else Int
0)
                  Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (if α -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit α
n Int
2 then Int
4 else Int
0)
  {-# INLINE lastDigitIn #-}

-- | The decimal numeral system.
data Decimal = Decimal deriving ( Typeable
#if __GLASGOW_HASKELL__ >= 706
                                , (forall x. Decimal -> Rep Decimal x)
-> (forall x. Rep Decimal x -> Decimal) -> Generic Decimal
forall x. Rep Decimal x -> Decimal
forall x. Decimal -> Rep Decimal x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Decimal x -> Decimal
$cfrom :: forall x. Decimal -> Rep Decimal x
Generic
#endif
                                , Decimal -> Decimal -> Bool
(Decimal -> Decimal -> Bool)
-> (Decimal -> Decimal -> Bool) -> Eq Decimal
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Decimal -> Decimal -> Bool
$c/= :: Decimal -> Decimal -> Bool
== :: Decimal -> Decimal -> Bool
$c== :: Decimal -> Decimal -> Bool
Eq, Eq Decimal
Eq Decimal
-> (Decimal -> Decimal -> Ordering)
-> (Decimal -> Decimal -> Bool)
-> (Decimal -> Decimal -> Bool)
-> (Decimal -> Decimal -> Bool)
-> (Decimal -> Decimal -> Bool)
-> (Decimal -> Decimal -> Decimal)
-> (Decimal -> Decimal -> Decimal)
-> Ord Decimal
Decimal -> Decimal -> Bool
Decimal -> Decimal -> Ordering
Decimal -> Decimal -> Decimal
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Decimal -> Decimal -> Decimal
$cmin :: Decimal -> Decimal -> Decimal
max :: Decimal -> Decimal -> Decimal
$cmax :: Decimal -> Decimal -> Decimal
>= :: Decimal -> Decimal -> Bool
$c>= :: Decimal -> Decimal -> Bool
> :: Decimal -> Decimal -> Bool
$c> :: Decimal -> Decimal -> Bool
<= :: Decimal -> Decimal -> Bool
$c<= :: Decimal -> Decimal -> Bool
< :: Decimal -> Decimal -> Bool
$c< :: Decimal -> Decimal -> Bool
compare :: Decimal -> Decimal -> Ordering
$ccompare :: Decimal -> Decimal -> Ordering
$cp1Ord :: Eq Decimal
Ord, Int -> Decimal -> ShowS
[Decimal] -> ShowS
Decimal -> String
(Int -> Decimal -> ShowS)
-> (Decimal -> String) -> ([Decimal] -> ShowS) -> Show Decimal
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Decimal] -> ShowS
$cshowList :: [Decimal] -> ShowS
show :: Decimal -> String
$cshow :: Decimal -> String
showsPrec :: Int -> Decimal -> ShowS
$cshowsPrec :: Int -> Decimal -> ShowS
Show, ReadPrec [Decimal]
ReadPrec Decimal
Int -> ReadS Decimal
ReadS [Decimal]
(Int -> ReadS Decimal)
-> ReadS [Decimal]
-> ReadPrec Decimal
-> ReadPrec [Decimal]
-> Read Decimal
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Decimal]
$creadListPrec :: ReadPrec [Decimal]
readPrec :: ReadPrec Decimal
$creadPrec :: ReadPrec Decimal
readList :: ReadS [Decimal]
$creadList :: ReadS [Decimal]
readsPrec :: Int -> ReadS Decimal
$creadsPrec :: Int -> ReadS Decimal
Read )

instance PositionalSystem Decimal where
  systemName :: Decimal -> String
systemName Decimal
_ = String
"decimal"
  {-# INLINE systemName #-}
  radixIn :: Decimal -> α
radixIn Decimal
_ = α
10
  {-# INLINE radixIn #-}
  isDigitIn :: Decimal -> Char -> Bool
isDigitIn Decimal
_ = Char -> Bool
A.isDecDigit
  {-# INLINE isDigitIn #-}
  isNzDigitIn :: Decimal -> Char -> Bool
isNzDigitIn Decimal
_ = Char -> Bool
A.isNzDecDigit
  {-# INLINE isNzDigitIn #-}
  fromDigitIn :: Decimal -> Char -> Maybe α
fromDigitIn Decimal
_ = Char -> Maybe α
forall a. Num a => Char -> Maybe a
A.fromDecDigit
  {-# INLINE fromDigitIn #-}
  fromNzDigitIn :: Decimal -> Char -> Maybe α
fromNzDigitIn Decimal
_ = Char -> Maybe α
forall a. Num a => Char -> Maybe a
A.fromNzDecDigit
  {-# INLINE fromNzDigitIn #-}
  unsafeFromDigitIn :: Decimal -> Char -> α
unsafeFromDigitIn Decimal
_ = Char -> α
forall a. Num a => Char -> a
A.unsafeFromDecDigit
  {-# INLINE unsafeFromDigitIn #-}
  intToDigitIn :: Decimal -> Int -> Char
intToDigitIn Decimal
_ Int
i = Int -> Char
chr (Int -> Char) -> Int -> Char
forall a b. (a -> b) -> a -> b
$! Char -> Int
ord Char
'0' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
i
  {-# INLINE intToDigitIn #-}
  printZeroIn :: Decimal -> p
printZeroIn Decimal
_ = Char -> p
forall p. Printer p => Char -> p
char7 Char
'0'
  {-# INLINE printZeroIn #-}

-- | The hexadecimal numeral system.
data Hexadecimal = Hexadecimal deriving ( Typeable
#if __GLASGOW_HASKELL__ >= 706
                                        , (forall x. Hexadecimal -> Rep Hexadecimal x)
-> (forall x. Rep Hexadecimal x -> Hexadecimal)
-> Generic Hexadecimal
forall x. Rep Hexadecimal x -> Hexadecimal
forall x. Hexadecimal -> Rep Hexadecimal x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Hexadecimal x -> Hexadecimal
$cfrom :: forall x. Hexadecimal -> Rep Hexadecimal x
Generic
#endif
                                        , Hexadecimal -> Hexadecimal -> Bool
(Hexadecimal -> Hexadecimal -> Bool)
-> (Hexadecimal -> Hexadecimal -> Bool) -> Eq Hexadecimal
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Hexadecimal -> Hexadecimal -> Bool
$c/= :: Hexadecimal -> Hexadecimal -> Bool
== :: Hexadecimal -> Hexadecimal -> Bool
$c== :: Hexadecimal -> Hexadecimal -> Bool
Eq, Eq Hexadecimal
Eq Hexadecimal
-> (Hexadecimal -> Hexadecimal -> Ordering)
-> (Hexadecimal -> Hexadecimal -> Bool)
-> (Hexadecimal -> Hexadecimal -> Bool)
-> (Hexadecimal -> Hexadecimal -> Bool)
-> (Hexadecimal -> Hexadecimal -> Bool)
-> (Hexadecimal -> Hexadecimal -> Hexadecimal)
-> (Hexadecimal -> Hexadecimal -> Hexadecimal)
-> Ord Hexadecimal
Hexadecimal -> Hexadecimal -> Bool
Hexadecimal -> Hexadecimal -> Ordering
Hexadecimal -> Hexadecimal -> Hexadecimal
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Hexadecimal -> Hexadecimal -> Hexadecimal
$cmin :: Hexadecimal -> Hexadecimal -> Hexadecimal
max :: Hexadecimal -> Hexadecimal -> Hexadecimal
$cmax :: Hexadecimal -> Hexadecimal -> Hexadecimal
>= :: Hexadecimal -> Hexadecimal -> Bool
$c>= :: Hexadecimal -> Hexadecimal -> Bool
> :: Hexadecimal -> Hexadecimal -> Bool
$c> :: Hexadecimal -> Hexadecimal -> Bool
<= :: Hexadecimal -> Hexadecimal -> Bool
$c<= :: Hexadecimal -> Hexadecimal -> Bool
< :: Hexadecimal -> Hexadecimal -> Bool
$c< :: Hexadecimal -> Hexadecimal -> Bool
compare :: Hexadecimal -> Hexadecimal -> Ordering
$ccompare :: Hexadecimal -> Hexadecimal -> Ordering
$cp1Ord :: Eq Hexadecimal
Ord, Int -> Hexadecimal -> ShowS
[Hexadecimal] -> ShowS
Hexadecimal -> String
(Int -> Hexadecimal -> ShowS)
-> (Hexadecimal -> String)
-> ([Hexadecimal] -> ShowS)
-> Show Hexadecimal
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Hexadecimal] -> ShowS
$cshowList :: [Hexadecimal] -> ShowS
show :: Hexadecimal -> String
$cshow :: Hexadecimal -> String
showsPrec :: Int -> Hexadecimal -> ShowS
$cshowsPrec :: Int -> Hexadecimal -> ShowS
Show, ReadPrec [Hexadecimal]
ReadPrec Hexadecimal
Int -> ReadS Hexadecimal
ReadS [Hexadecimal]
(Int -> ReadS Hexadecimal)
-> ReadS [Hexadecimal]
-> ReadPrec Hexadecimal
-> ReadPrec [Hexadecimal]
-> Read Hexadecimal
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Hexadecimal]
$creadListPrec :: ReadPrec [Hexadecimal]
readPrec :: ReadPrec Hexadecimal
$creadPrec :: ReadPrec Hexadecimal
readList :: ReadS [Hexadecimal]
$creadList :: ReadS [Hexadecimal]
readsPrec :: Int -> ReadS Hexadecimal
$creadsPrec :: Int -> ReadS Hexadecimal
Read )

instance PositionalSystem Hexadecimal where
  systemName :: Hexadecimal -> String
systemName Hexadecimal
_ = String
"hexadecimal"
  {-# INLINE systemName #-}
  radixIn :: Hexadecimal -> α
radixIn Hexadecimal
_ = α
16
  {-# INLINE radixIn #-}
  isDigitIn :: Hexadecimal -> Char -> Bool
isDigitIn Hexadecimal
_ = Char -> Bool
A.isHexDigit
  {-# INLINE isDigitIn #-}
  isNzDigitIn :: Hexadecimal -> Char -> Bool
isNzDigitIn Hexadecimal
_ = Char -> Bool
A.isNzHexDigit
  {-# INLINE isNzDigitIn #-}
  fromDigitIn :: Hexadecimal -> Char -> Maybe α
fromDigitIn Hexadecimal
_ = Char -> Maybe α
forall a. Num a => Char -> Maybe a
A.fromHexDigit
  {-# INLINE fromDigitIn #-}
  fromNzDigitIn :: Hexadecimal -> Char -> Maybe α
fromNzDigitIn Hexadecimal
_ = Char -> Maybe α
forall a. Num a => Char -> Maybe a
A.fromNzHexDigit
  {-# INLINE fromNzDigitIn #-}
  unsafeFromDigitIn :: Hexadecimal -> Char -> α
unsafeFromDigitIn Hexadecimal
_ = Char -> α
forall a. Num a => Char -> a
A.unsafeFromHexDigit
  {-# INLINE unsafeFromDigitIn #-}
  intToDigitIn :: Hexadecimal -> Int -> Char
intToDigitIn Hexadecimal
_ Int
i | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
10    = Int -> Char
chr (Int -> Char) -> Int -> Char
forall a b. (a -> b) -> a -> b
$! Char -> Int
ord Char
'0' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
i
                   | Bool
otherwise = Int -> Char
chr (Int -> Char) -> Int -> Char
forall a b. (a -> b) -> a -> b
$! Char -> Int
ord Char
'A' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
10) 
  {-# INLINE intToDigitIn #-}
  printZeroIn :: Hexadecimal -> p
printZeroIn Hexadecimal
_ = Char -> p
forall p. Printer p => Char -> p
char7 Char
'0'
  {-# INLINE printZeroIn #-}

instance BitSystem Hexadecimal where
  digitBitsIn :: Hexadecimal -> Int
digitBitsIn Hexadecimal
_ = Int
4
  {-# INLINE digitBitsIn #-}
  digitMaskIn :: Hexadecimal -> α
digitMaskIn Hexadecimal
_ = α
15
  {-# INLINE digitMaskIn #-}
  lastDigitIn :: Hexadecimal -> α -> Int
lastDigitIn Hexadecimal
_ α
n = (if α -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit α
n Int
0 then Int
1 else Int
0)
                  Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (if α -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit α
n Int
1 then Int
2 else Int
0)
                  Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (if α -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit α
n Int
2 then Int
4 else Int
0)
                  Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (if α -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit α
n Int
3 then Int
8 else Int
0)
  {-# INLINABLE lastDigitIn #-}

-- | The hexadecimal numeral system, using lower case digits.
data LowHex = LowHex deriving ( Typeable
#if __GLASGOW_HASKELL__ >= 706
                              , (forall x. LowHex -> Rep LowHex x)
-> (forall x. Rep LowHex x -> LowHex) -> Generic LowHex
forall x. Rep LowHex x -> LowHex
forall x. LowHex -> Rep LowHex x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LowHex x -> LowHex
$cfrom :: forall x. LowHex -> Rep LowHex x
Generic
#endif
                              , LowHex -> LowHex -> Bool
(LowHex -> LowHex -> Bool)
-> (LowHex -> LowHex -> Bool) -> Eq LowHex
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LowHex -> LowHex -> Bool
$c/= :: LowHex -> LowHex -> Bool
== :: LowHex -> LowHex -> Bool
$c== :: LowHex -> LowHex -> Bool
Eq, Eq LowHex
Eq LowHex
-> (LowHex -> LowHex -> Ordering)
-> (LowHex -> LowHex -> Bool)
-> (LowHex -> LowHex -> Bool)
-> (LowHex -> LowHex -> Bool)
-> (LowHex -> LowHex -> Bool)
-> (LowHex -> LowHex -> LowHex)
-> (LowHex -> LowHex -> LowHex)
-> Ord LowHex
LowHex -> LowHex -> Bool
LowHex -> LowHex -> Ordering
LowHex -> LowHex -> LowHex
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: LowHex -> LowHex -> LowHex
$cmin :: LowHex -> LowHex -> LowHex
max :: LowHex -> LowHex -> LowHex
$cmax :: LowHex -> LowHex -> LowHex
>= :: LowHex -> LowHex -> Bool
$c>= :: LowHex -> LowHex -> Bool
> :: LowHex -> LowHex -> Bool
$c> :: LowHex -> LowHex -> Bool
<= :: LowHex -> LowHex -> Bool
$c<= :: LowHex -> LowHex -> Bool
< :: LowHex -> LowHex -> Bool
$c< :: LowHex -> LowHex -> Bool
compare :: LowHex -> LowHex -> Ordering
$ccompare :: LowHex -> LowHex -> Ordering
$cp1Ord :: Eq LowHex
Ord, Int -> LowHex -> ShowS
[LowHex] -> ShowS
LowHex -> String
(Int -> LowHex -> ShowS)
-> (LowHex -> String) -> ([LowHex] -> ShowS) -> Show LowHex
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LowHex] -> ShowS
$cshowList :: [LowHex] -> ShowS
show :: LowHex -> String
$cshow :: LowHex -> String
showsPrec :: Int -> LowHex -> ShowS
$cshowsPrec :: Int -> LowHex -> ShowS
Show, ReadPrec [LowHex]
ReadPrec LowHex
Int -> ReadS LowHex
ReadS [LowHex]
(Int -> ReadS LowHex)
-> ReadS [LowHex]
-> ReadPrec LowHex
-> ReadPrec [LowHex]
-> Read LowHex
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [LowHex]
$creadListPrec :: ReadPrec [LowHex]
readPrec :: ReadPrec LowHex
$creadPrec :: ReadPrec LowHex
readList :: ReadS [LowHex]
$creadList :: ReadS [LowHex]
readsPrec :: Int -> ReadS LowHex
$creadsPrec :: Int -> ReadS LowHex
Read )

instance PositionalSystem LowHex where
  systemName :: LowHex -> String
systemName LowHex
_ = String
"lower case hexadecimal"
  {-# INLINE systemName #-}
  radixIn :: LowHex -> α
radixIn LowHex
_ = α
16
  {-# INLINE radixIn #-}
  isDigitIn :: LowHex -> Char -> Bool
isDigitIn LowHex
_ = Char -> Bool
A.isLowHexDigit
  {-# INLINE isDigitIn #-}
  isNzDigitIn :: LowHex -> Char -> Bool
isNzDigitIn LowHex
_ = Char -> Bool
A.isNzLowHexDigit
  {-# INLINE isNzDigitIn #-}
  fromDigitIn :: LowHex -> Char -> Maybe α
fromDigitIn LowHex
_ = Char -> Maybe α
forall a. Num a => Char -> Maybe a
A.fromLowHexDigit
  {-# INLINE fromDigitIn #-}
  fromNzDigitIn :: LowHex -> Char -> Maybe α
fromNzDigitIn LowHex
_ = Char -> Maybe α
forall a. Num a => Char -> Maybe a
A.fromNzLowHexDigit
  {-# INLINE fromNzDigitIn #-}
  unsafeFromDigitIn :: LowHex -> Char -> α
unsafeFromDigitIn LowHex
_ = Char -> α
forall a. Num a => Char -> a
A.unsafeFromLowHexDigit
  {-# INLINE unsafeFromDigitIn #-}
  intToDigitIn :: LowHex -> Int -> Char
intToDigitIn LowHex
_ Int
i | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
10    = Int -> Char
chr (Int -> Char) -> Int -> Char
forall a b. (a -> b) -> a -> b
$! Char -> Int
ord Char
'0' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
i
                   | Bool
otherwise = Int -> Char
chr (Int -> Char) -> Int -> Char
forall a b. (a -> b) -> a -> b
$! Char -> Int
ord Char
'a' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
10) 
  {-# INLINE intToDigitIn #-}
  printZeroIn :: LowHex -> p
printZeroIn LowHex
_ = Char -> p
forall p. Printer p => Char -> p
char7 Char
'0'
  {-# INLINE printZeroIn #-}

instance BitSystem LowHex where
  digitBitsIn :: LowHex -> Int
digitBitsIn LowHex
_ = Int
4
  {-# INLINE digitBitsIn #-}
  digitMaskIn :: LowHex -> α
digitMaskIn LowHex
_ = α
15
  {-# INLINE digitMaskIn #-}
  lastDigitIn :: LowHex -> α -> Int
lastDigitIn LowHex
_ α
n = (if α -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit α
n Int
0 then Int
1 else Int
0)
                  Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (if α -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit α
n Int
1 then Int
2 else Int
0)
                  Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (if α -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit α
n Int
2 then Int
4 else Int
0)
                  Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (if α -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit α
n Int
3 then Int
8 else Int
0)
  {-# INLINABLE lastDigitIn #-}

-- | The hexadecimal numeral system, using upper case digits.
data UpHex = UpHex deriving ( Typeable
#if __GLASGOW_HASKELL__ >= 706
                            , (forall x. UpHex -> Rep UpHex x)
-> (forall x. Rep UpHex x -> UpHex) -> Generic UpHex
forall x. Rep UpHex x -> UpHex
forall x. UpHex -> Rep UpHex x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpHex x -> UpHex
$cfrom :: forall x. UpHex -> Rep UpHex x
Generic
#endif
                            , UpHex -> UpHex -> Bool
(UpHex -> UpHex -> Bool) -> (UpHex -> UpHex -> Bool) -> Eq UpHex
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpHex -> UpHex -> Bool
$c/= :: UpHex -> UpHex -> Bool
== :: UpHex -> UpHex -> Bool
$c== :: UpHex -> UpHex -> Bool
Eq, Eq UpHex
Eq UpHex
-> (UpHex -> UpHex -> Ordering)
-> (UpHex -> UpHex -> Bool)
-> (UpHex -> UpHex -> Bool)
-> (UpHex -> UpHex -> Bool)
-> (UpHex -> UpHex -> Bool)
-> (UpHex -> UpHex -> UpHex)
-> (UpHex -> UpHex -> UpHex)
-> Ord UpHex
UpHex -> UpHex -> Bool
UpHex -> UpHex -> Ordering
UpHex -> UpHex -> UpHex
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: UpHex -> UpHex -> UpHex
$cmin :: UpHex -> UpHex -> UpHex
max :: UpHex -> UpHex -> UpHex
$cmax :: UpHex -> UpHex -> UpHex
>= :: UpHex -> UpHex -> Bool
$c>= :: UpHex -> UpHex -> Bool
> :: UpHex -> UpHex -> Bool
$c> :: UpHex -> UpHex -> Bool
<= :: UpHex -> UpHex -> Bool
$c<= :: UpHex -> UpHex -> Bool
< :: UpHex -> UpHex -> Bool
$c< :: UpHex -> UpHex -> Bool
compare :: UpHex -> UpHex -> Ordering
$ccompare :: UpHex -> UpHex -> Ordering
$cp1Ord :: Eq UpHex
Ord, Int -> UpHex -> ShowS
[UpHex] -> ShowS
UpHex -> String
(Int -> UpHex -> ShowS)
-> (UpHex -> String) -> ([UpHex] -> ShowS) -> Show UpHex
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpHex] -> ShowS
$cshowList :: [UpHex] -> ShowS
show :: UpHex -> String
$cshow :: UpHex -> String
showsPrec :: Int -> UpHex -> ShowS
$cshowsPrec :: Int -> UpHex -> ShowS
Show, ReadPrec [UpHex]
ReadPrec UpHex
Int -> ReadS UpHex
ReadS [UpHex]
(Int -> ReadS UpHex)
-> ReadS [UpHex]
-> ReadPrec UpHex
-> ReadPrec [UpHex]
-> Read UpHex
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpHex]
$creadListPrec :: ReadPrec [UpHex]
readPrec :: ReadPrec UpHex
$creadPrec :: ReadPrec UpHex
readList :: ReadS [UpHex]
$creadList :: ReadS [UpHex]
readsPrec :: Int -> ReadS UpHex
$creadsPrec :: Int -> ReadS UpHex
Read )

instance PositionalSystem UpHex where
  systemName :: UpHex -> String
systemName UpHex
_ = String
"upper case hexadecimal"
  {-# INLINE systemName #-}
  radixIn :: UpHex -> α
radixIn UpHex
_ = α
16
  {-# INLINE radixIn #-}
  isDigitIn :: UpHex -> Char -> Bool
isDigitIn UpHex
_ = Char -> Bool
A.isUpHexDigit
  {-# INLINE isDigitIn #-}
  isNzDigitIn :: UpHex -> Char -> Bool
isNzDigitIn UpHex
_ = Char -> Bool
A.isNzUpHexDigit
  {-# INLINE isNzDigitIn #-}
  fromDigitIn :: UpHex -> Char -> Maybe α
fromDigitIn UpHex
_ = Char -> Maybe α
forall a. Num a => Char -> Maybe a
A.fromUpHexDigit
  {-# INLINE fromDigitIn #-}
  fromNzDigitIn :: UpHex -> Char -> Maybe α
fromNzDigitIn UpHex
_ = Char -> Maybe α
forall a. Num a => Char -> Maybe a
A.fromNzUpHexDigit
  {-# INLINE fromNzDigitIn #-}
  unsafeFromDigitIn :: UpHex -> Char -> α
unsafeFromDigitIn UpHex
_ = Char -> α
forall a. Num a => Char -> a
A.unsafeFromUpHexDigit
  {-# INLINE unsafeFromDigitIn #-}
  intToDigitIn :: UpHex -> Int -> Char
intToDigitIn UpHex
_ Int
i | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
10    = Int -> Char
chr (Int -> Char) -> Int -> Char
forall a b. (a -> b) -> a -> b
$! Char -> Int
ord Char
'0' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
i
                   | Bool
otherwise = Int -> Char
chr (Int -> Char) -> Int -> Char
forall a b. (a -> b) -> a -> b
$! Char -> Int
ord Char
'A' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
10) 
  {-# INLINE intToDigitIn #-}
  printZeroIn :: UpHex -> p
printZeroIn UpHex
_ = Char -> p
forall p. Printer p => Char -> p
char7 Char
'0'
  {-# INLINE printZeroIn #-}

instance BitSystem UpHex where
  digitBitsIn :: UpHex -> Int
digitBitsIn UpHex
_ = Int
4
  {-# INLINE digitBitsIn #-}
  digitMaskIn :: UpHex -> α
digitMaskIn UpHex
_ = α
15
  {-# INLINE digitMaskIn #-}
  lastDigitIn :: UpHex -> α -> Int
lastDigitIn UpHex
_ α
n = (if α -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit α
n Int
0 then Int
1 else Int
0)
                  Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (if α -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit α
n Int
1 then Int
2 else Int
0)
                  Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (if α -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit α
n Int
2 then Int
4 else Int
0)
                  Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (if α -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit α
n Int
3 then Int
8 else Int
0)
  {-# INLINABLE lastDigitIn #-}

-- | Print a non-negative number in the specified positional numeral system.
nonNegative  (PositionalSystem s, Integral α, Printer p)  s  α  p
nonNegative :: s -> α -> p
nonNegative s
s = p -> α -> p
forall t. Printer t => t -> α -> t
go (s -> Char -> p
forall s p. (PositionalSystem s, Printer p) => s -> Char -> p
printDigitIn s
s (Char -> p) -> Char -> p
forall a b. (a -> b) -> a -> b
$! s -> Int -> Char
forall s. PositionalSystem s => s -> Int -> Char
intToDigitIn s
s Int
0)
  where go :: t -> α -> t
go t
p α
0 = t
p
        go t
_ α
m = t -> α -> t
go t
forall a. Monoid a => a
mempty α
q t -> t -> t
forall a. Semigroup a => a -> a -> a
<> s -> Char -> t
forall s p. (PositionalSystem s, Printer p) => s -> Char -> p
printDigitIn s
s Char
d
          where (α
q, α
r) = α -> α -> (α, α)
forall a. Integral a => a -> a -> (a, a)
quotRem α
m α
radix
                !d :: Char
d     = s -> Int -> Char
forall s. PositionalSystem s => s -> Int -> Char
intToDigitIn s
s (Int -> Char) -> Int -> Char
forall a b. (a -> b) -> a -> b
$ α -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral α
r
        radix :: α
radix = s -> α
forall s α. (PositionalSystem s, Num α) => s -> α
radixIn s
s
{-# INLINABLE nonNegative #-}
{-# SPECIALIZE nonNegative  Printer p  Decimal  Int  p #-}
{-# SPECIALIZE nonNegative  Printer p  Decimal  Int8  p #-}
{-# SPECIALIZE nonNegative  Printer p  Decimal  Int16  p #-}
{-# SPECIALIZE nonNegative  Printer p  Decimal  Int32  p #-}
{-# SPECIALIZE nonNegative  Printer p  Decimal  Int64  p #-}
{-# SPECIALIZE nonNegative  Printer p  Decimal  Word  p #-}
{-# SPECIALIZE nonNegative  Printer p  Decimal  Word8  p #-}
{-# SPECIALIZE nonNegative  Printer p  Decimal  Word16  p #-}
{-# SPECIALIZE nonNegative  Printer p  Decimal  Word32  p #-}
{-# SPECIALIZE nonNegative  Printer p  Decimal  Word64  p #-}
{-# SPECIALIZE nonNegative  (Integral α, Printer p)  Binary  α  p #-}
{-# SPECIALIZE nonNegative  (Integral α, Printer p)  Octal  α  p #-}
{-# SPECIALIZE nonNegative  (Integral α, Printer p)  Decimal  α  p #-}
{-# SPECIALIZE nonNegative  (Integral α, Printer p)  LowHex  α  p #-}
{-# SPECIALIZE nonNegative  (Integral α, Printer p)  UpHex  α  p #-}

-- | Print a non-negative number in the binary numeral system.
nnBinary  (Integral α, Printer p)  α  p
nnBinary :: α -> p
nnBinary = Binary -> α -> p
forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
s -> α -> p
nonNegative Binary
Binary
{-# INLINE nnBinary #-}

-- | Print a non-negative number in the octal numeral system.
nnOctal  (Integral α, Printer p)  α  p
nnOctal :: α -> p
nnOctal = Octal -> α -> p
forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
s -> α -> p
nonNegative Octal
Octal
{-# INLINE nnOctal #-}

-- | Print a non-negative number in the decimal numeral system.
nnDecimal  (Integral α, Printer p)  α  p
nnDecimal :: α -> p
nnDecimal = Decimal -> α -> p
forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
s -> α -> p
nonNegative Decimal
Decimal
{-# INLINE nnDecimal #-}

-- | Print a non-negative number in the hexadecimal numeral system
--   using lower case digits.
nnLowHex  (Integral α, Printer p)  α  p
nnLowHex :: α -> p
nnLowHex = LowHex -> α -> p
forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
s -> α -> p
nonNegative LowHex
LowHex
{-# INLINE nnLowHex #-}

-- | Print a non-negative number in the hexadecimal numeral system
--   using upper case digits.
nnUpHex  (Integral α, Printer p)  α  p
nnUpHex :: α -> p
nnUpHex = UpHex -> α -> p
forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
s -> α -> p
nonNegative UpHex
UpHex
{-# INLINE nnUpHex #-}

-- | Print a non-negative binary number in the specified positional numeral
--   system.
nnBits  (BitSystem s, Num α, Bits α, Printer p)  s  α  p
nnBits :: s -> α -> p
nnBits s
s = p -> α -> p
forall t t. (Num t, Printer t, Bits t) => t -> t -> t
go (s -> Char -> p
forall s p. (PositionalSystem s, Printer p) => s -> Char -> p
printDigitIn s
s (Char -> p) -> Char -> p
forall a b. (a -> b) -> a -> b
$! s -> Int -> Char
forall s. PositionalSystem s => s -> Int -> Char
intToDigitIn s
s Int
0)
  where go :: t -> t -> t
go t
p t
0 = t
p
        go t
_ t
m = t -> t -> t
go t
forall a. Monoid a => a
mempty (t -> Int -> t
forall a. Bits a => a -> Int -> a
shiftR t
m Int
digitBits) t -> t -> t
forall a. Semigroup a => a -> a -> a
<> s -> Char -> t
forall s p. (PositionalSystem s, Printer p) => s -> Char -> p
printDigitIn s
s Char
d
          where !d :: Char
d = s -> Int -> Char
forall s. PositionalSystem s => s -> Int -> Char
intToDigitIn s
s (Int -> Char) -> Int -> Char
forall a b. (a -> b) -> a -> b
$ s -> t -> Int
forall s α. (BitSystem s, Bits α) => s -> α -> Int
lastDigitIn s
s t
m
        digitBits :: Int
digitBits = s -> Int
forall s. BitSystem s => s -> Int
digitBitsIn s
s
{-# INLINABLE nnBits #-}
{-# SPECIALIZE nnBits  Printer p  Binary  Int  p #-}
{-# SPECIALIZE nnBits  Printer p  Binary  Int8  p #-}
{-# SPECIALIZE nnBits  Printer p  Binary  Int16  p #-}
{-# SPECIALIZE nnBits  Printer p  Binary  Int32  p #-}
{-# SPECIALIZE nnBits  Printer p  Binary  Int64  p #-}
{-# SPECIALIZE nnBits  Printer p  Binary  Word  p #-}
{-# SPECIALIZE nnBits  Printer p  Binary  Word8  p #-}
{-# SPECIALIZE nnBits  Printer p  Binary  Word16  p #-}
{-# SPECIALIZE nnBits  Printer p  Binary  Word32  p #-}
{-# SPECIALIZE nnBits  Printer p  Binary  Word64  p #-}
{-# SPECIALIZE nnBits  Printer p  Octal  Int  p #-}
{-# SPECIALIZE nnBits  Printer p  Octal  Int8  p #-}
{-# SPECIALIZE nnBits  Printer p  Octal  Int16  p #-}
{-# SPECIALIZE nnBits  Printer p  Octal  Int32  p #-}
{-# SPECIALIZE nnBits  Printer p  Octal  Int64  p #-}
{-# SPECIALIZE nnBits  Printer p  Octal  Word  p #-}
{-# SPECIALIZE nnBits  Printer p  Octal  Word8  p #-}
{-# SPECIALIZE nnBits  Printer p  Octal  Word16  p #-}
{-# SPECIALIZE nnBits  Printer p  Octal  Word32  p #-}
{-# SPECIALIZE nnBits  Printer p  Octal  Word64  p #-}
{-# SPECIALIZE nnBits  Printer p  Hexadecimal  Int  p #-}
{-# SPECIALIZE nnBits  Printer p  Hexadecimal  Int8  p #-}
{-# SPECIALIZE nnBits  Printer p  Hexadecimal  Int16  p #-}
{-# SPECIALIZE nnBits  Printer p  Hexadecimal  Int32  p #-}
{-# SPECIALIZE nnBits  Printer p  Hexadecimal  Int64  p #-}
{-# SPECIALIZE nnBits  Printer p  Hexadecimal  Word  p #-}
{-# SPECIALIZE nnBits  Printer p  Hexadecimal  Word8  p #-}
{-# SPECIALIZE nnBits  Printer p  Hexadecimal  Word16  p #-}
{-# SPECIALIZE nnBits  Printer p  Hexadecimal  Word32  p #-}
{-# SPECIALIZE nnBits  Printer p  Hexadecimal  Word64  p #-}
{-# SPECIALIZE nnBits  Printer p  LowHex  Int  p #-}
{-# SPECIALIZE nnBits  Printer p  LowHex  Int8  p #-}
{-# SPECIALIZE nnBits  Printer p  LowHex  Int16  p #-}
{-# SPECIALIZE nnBits  Printer p  LowHex  Int32  p #-}
{-# SPECIALIZE nnBits  Printer p  LowHex  Int64  p #-}
{-# SPECIALIZE nnBits  Printer p  LowHex  Word  p #-}
{-# SPECIALIZE nnBits  Printer p  LowHex  Word8  p #-}
{-# SPECIALIZE nnBits  Printer p  LowHex  Word16  p #-}
{-# SPECIALIZE nnBits  Printer p  LowHex  Word32  p #-}
{-# SPECIALIZE nnBits  Printer p  LowHex  Word64  p #-}
{-# SPECIALIZE nnBits  Printer p  UpHex  Int  p #-}
{-# SPECIALIZE nnBits  Printer p  UpHex  Int8  p #-}
{-# SPECIALIZE nnBits  Printer p  UpHex  Int16  p #-}
{-# SPECIALIZE nnBits  Printer p  UpHex  Int32  p #-}
{-# SPECIALIZE nnBits  Printer p  UpHex  Int64  p #-}
{-# SPECIALIZE nnBits  Printer p  UpHex  Word  p #-}
{-# SPECIALIZE nnBits  Printer p  UpHex  Word8  p #-}
{-# SPECIALIZE nnBits  Printer p  UpHex  Word16  p #-}
{-# SPECIALIZE nnBits  Printer p  UpHex  Word32  p #-}
{-# SPECIALIZE nnBits  Printer p  UpHex  Word64  p #-}
{-# SPECIALIZE nnBits  (Num α, Bits α, Printer p)  Binary  α  p #-}
{-# SPECIALIZE nnBits  (Num α, Bits α, Printer p)  Octal  α  p #-}
{-# SPECIALIZE nnBits  (Num α, Bits α, Printer p)  Hexadecimal  α  p #-}
{-# SPECIALIZE nnBits  (Num α, Bits α, Printer p)  LowHex  α  p #-}
{-# SPECIALIZE nnBits  (Num α, Bits α, Printer p)  UpHex  α  p #-}

-- | Print a non-negative binary number in the binary numeral system.
nnBinaryBits  (Num α, Bits α, Printer p)  α  p
nnBinaryBits :: α -> p
nnBinaryBits = Binary -> α -> p
forall s α p.
(BitSystem s, Num α, Bits α, Printer p) =>
s -> α -> p
nnBits Binary
Binary
{-# INLINE nnBinaryBits #-}

-- | Print a non-negative binary number in the octal numeral system.
nnOctalBits  (Num α, Bits α, Printer p)  α  p
nnOctalBits :: α -> p
nnOctalBits = Octal -> α -> p
forall s α p.
(BitSystem s, Num α, Bits α, Printer p) =>
s -> α -> p
nnBits Octal
Octal
{-# INLINE nnOctalBits #-}

-- | Print a non-negative binary number in the hexadecimal numeral system
--   using lower case digits.
nnLowHexBits  (Num α, Bits α, Printer p)  α  p
nnLowHexBits :: α -> p
nnLowHexBits = LowHex -> α -> p
forall s α p.
(BitSystem s, Num α, Bits α, Printer p) =>
s -> α -> p
nnBits LowHex
LowHex
{-# INLINE nnLowHexBits #-}

-- | Print a non-negative binary number in the hexadecimal numeral system
--   using upper case digits.
nnUpHexBits  (Num α, Bits α, Printer p)  α  p
nnUpHexBits :: α -> p
nnUpHexBits = UpHex -> α -> p
forall s α p.
(BitSystem s, Num α, Bits α, Printer p) =>
s -> α -> p
nnBits UpHex
UpHex
{-# INLINE nnUpHexBits #-}

-- | Print a non-positive number in the specified positional numeral system.
--   For example, @'nonPositive' 'Decimal' (-/123/)@ would print \"123\".
nonPositive  (PositionalSystem s, Integral α, Printer p)  s  α  p
nonPositive :: s -> α -> p
nonPositive s
s = p -> α -> p
forall t. Printer t => t -> α -> t
go (s -> Char -> p
forall s p. (PositionalSystem s, Printer p) => s -> Char -> p
printDigitIn s
s (Char -> p) -> Char -> p
forall a b. (a -> b) -> a -> b
$! s -> Int -> Char
forall s. PositionalSystem s => s -> Int -> Char
intToDigitIn s
s Int
0)
  where go :: t -> α -> t
go t
p α
0 = t
p
        go t
_ α
m = t -> α -> t
go t
forall a. Monoid a => a
mempty α
q t -> t -> t
forall a. Semigroup a => a -> a -> a
<> s -> Char -> t
forall s p. (PositionalSystem s, Printer p) => s -> Char -> p
printDigitIn s
s Char
d
          where (α
q, α
r) = α -> α -> (α, α)
forall a. Integral a => a -> a -> (a, a)
quotRem α
m α
radix
                !d :: Char
d     = s -> Int -> Char
forall s. PositionalSystem s => s -> Int -> Char
intToDigitIn s
s (Int -> Char) -> Int -> Char
forall a b. (a -> b) -> a -> b
$ Int -> Int
forall a. Num a => a -> a
negate (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ α -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral α
r
        radix :: α
radix = s -> α
forall s α. (PositionalSystem s, Num α) => s -> α
radixIn s
s
{-# INLINABLE nonPositive #-}
{-# SPECIALIZE nonPositive  Printer p  Decimal  Int  p #-}
{-# SPECIALIZE nonPositive  Printer p  Decimal  Int8  p #-}
{-# SPECIALIZE nonPositive  Printer p  Decimal  Int16  p #-}
{-# SPECIALIZE nonPositive  Printer p  Decimal  Int32  p #-}
{-# SPECIALIZE nonPositive  Printer p  Decimal  Int64  p #-}
{-# SPECIALIZE nonPositive  Printer p  Decimal  Word  p #-}
{-# SPECIALIZE nonPositive  Printer p  Decimal  Word8  p #-}
{-# SPECIALIZE nonPositive  Printer p  Decimal  Word16  p #-}
{-# SPECIALIZE nonPositive  Printer p  Decimal  Word32  p #-}
{-# SPECIALIZE nonPositive  Printer p  Decimal  Word64  p #-}
{-# SPECIALIZE nonPositive  (Integral α, Printer p)  Binary  α  p #-}
{-# SPECIALIZE nonPositive  (Integral α, Printer p)  Octal  α  p #-}
{-# SPECIALIZE nonPositive  (Integral α, Printer p)  Decimal  α  p #-}
{-# SPECIALIZE nonPositive  (Integral α, Printer p)  LowHex  α  p #-}
{-# SPECIALIZE nonPositive  (Integral α, Printer p)  UpHex  α  p #-}

-- | Print a non-positive number in the binary numeral system.
npBinary  (Integral α, Printer p)  α  p
npBinary :: α -> p
npBinary = Binary -> α -> p
forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
s -> α -> p
nonPositive Binary
Binary
{-# INLINE npBinary #-}

-- | Print a non-positive number in the octal numeral system.
npOctal  (Integral α, Printer p)  α  p
npOctal :: α -> p
npOctal = Octal -> α -> p
forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
s -> α -> p
nonPositive Octal
Octal
{-# INLINE npOctal #-}

-- | Print a non-positive number in the decimal numeral system.
npDecimal  (Integral α, Printer p)  α  p
npDecimal :: α -> p
npDecimal = Decimal -> α -> p
forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
s -> α -> p
nonPositive Decimal
Decimal
{-# INLINE npDecimal #-}

-- | Print a non-positive number in the hexadecimal numeral system
--   using lower case digits.
npLowHex  (Integral α, Printer p)  α  p
npLowHex :: α -> p
npLowHex = LowHex -> α -> p
forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
s -> α -> p
nonPositive LowHex
LowHex
{-# INLINE npLowHex #-}

-- | Print a non-positive number in the hexadecimal numeral system
--   using upper case digits.
npUpHex  (Integral α, Printer p)  α  p
npUpHex :: α -> p
npUpHex = UpHex -> α -> p
forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
s -> α -> p
nonPositive UpHex
UpHex
{-# INLINE npUpHex #-}

-- | Print a non-positive two-compliment binary number in the specified
--   positional numeral system. For example, @'npBits' 'UpHex' (-/0xABC/)@
--   would print \"ABC\".
npBits  (BitSystem s, Ord α, Num α, Bits α, Printer p)  s  α  p
npBits :: s -> α -> p
npBits s
s α
n = case α -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit α
n Int
0 of
    Bool
True  p -> α -> p
forall t t. (Num t, Printer t, Bits t) => t -> t -> t
go p
forall a. Monoid a => a
mempty (α -> Int -> α
forall a. Bits a => a -> Int -> a
shiftR (α -> α
forall a. Num a => a -> a
negate α
n) Int
digitBits) p -> p -> p
forall a. Semigroup a => a -> a -> a
<> s -> Char -> p
forall s p. (PositionalSystem s, Printer p) => s -> Char -> p
printDigitIn s
s Char
d
      where !d :: Char
d = s -> Int -> Char
forall s. PositionalSystem s => s -> Int -> Char
intToDigitIn s
s (Int -> Char) -> Int -> Char
forall a b. (a -> b) -> a -> b
$ Int
radix Int -> Int -> Int
forall a. Num a => a -> a -> a
- s -> α -> Int
forall s α. (BitSystem s, Bits α) => s -> α -> Int
lastDigitIn s
s α
n
    Bool
False  case α
n α -> α -> Bool
forall a. Ord a => a -> a -> Bool
> α
negRadix of
        Bool
True  s -> Char -> p
forall s p. (PositionalSystem s, Printer p) => s -> Char -> p
printDigitIn s
s Char
d'
        Bool
False  p -> α -> p
forall t t. (Num t, Printer t, Bits t) => t -> t -> t
go p
forall a. Monoid a => a
mempty α
m p -> p -> p
forall a. Semigroup a => a -> a -> a
<> s -> Char -> p
forall s p. (PositionalSystem s, Printer p) => s -> Char -> p
printDigitIn s
s Char
d'
          where m :: α
m | Int
d Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0    = α -> α
forall a. Num a => a -> a
negate (α -> α) -> α -> α
forall a b. (a -> b) -> a -> b
$ α -> Int -> α
forall a. Bits a => a -> Int -> a
shiftR α
n Int
digitBits
                  | Bool
otherwise = α -> α
forall a. Bits a => a -> a
complement (α -> α) -> α -> α
forall a b. (a -> b) -> a -> b
$ α -> Int -> α
forall a. Bits a => a -> Int -> a
shiftR α
n Int
digitBits
      where !d :: Int
d  = s -> α -> Int
forall s α. (BitSystem s, Bits α) => s -> α -> Int
lastDigitIn s
s α
n
            !d' :: Char
d' = s -> Int -> Char
forall s. PositionalSystem s => s -> Int -> Char
intToDigitIn s
s (Int -> Char) -> Int -> Char
forall a b. (a -> b) -> a -> b
$ (Int
radix Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
d) Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int
digitMask
  where go :: t -> t -> t
go t
p t
0 = t
p
        go t
p t
m = t -> t -> t
go t
p (t -> Int -> t
forall a. Bits a => a -> Int -> a
shiftR t
m Int
digitBits) t -> t -> t
forall a. Semigroup a => a -> a -> a
<> s -> Char -> t
forall s p. (PositionalSystem s, Printer p) => s -> Char -> p
printDigitIn s
s Char
d
          where !d :: Char
d = s -> Int -> Char
forall s. PositionalSystem s => s -> Int -> Char
intToDigitIn s
s (Int -> Char) -> Int -> Char
forall a b. (a -> b) -> a -> b
$ s -> t -> Int
forall s α. (BitSystem s, Bits α) => s -> α -> Int
lastDigitIn s
s t
m
        radix :: Int
radix     = s -> Int
forall s α. (PositionalSystem s, Num α) => s -> α
radixIn s
s
        digitMask :: Int
digitMask = s -> Int
forall s α. (BitSystem s, Num α) => s -> α
digitMaskIn s
s
        digitBits :: Int
digitBits = s -> Int
forall s. BitSystem s => s -> Int
digitBitsIn s
s
        negRadix :: α
negRadix  = α -> α
forall a. Bits a => a -> a
complement (α -> α) -> α -> α
forall a b. (a -> b) -> a -> b
$ s -> α
forall s α. (BitSystem s, Num α) => s -> α
digitMaskIn s
s
{-# SPECIALIZE npBits  Printer p  Binary  Int  p #-}
{-# SPECIALIZE npBits  Printer p  Binary  Int8  p #-}
{-# SPECIALIZE npBits  Printer p  Binary  Int16  p #-}
{-# SPECIALIZE npBits  Printer p  Binary  Int32  p #-}
{-# SPECIALIZE npBits  Printer p  Binary  Int64  p #-}
{-# SPECIALIZE npBits  Printer p  Binary  Word  p #-}
{-# SPECIALIZE npBits  Printer p  Binary  Word8  p #-}
{-# SPECIALIZE npBits  Printer p  Binary  Word16  p #-}
{-# SPECIALIZE npBits  Printer p  Binary  Word32  p #-}
{-# SPECIALIZE npBits  Printer p  Binary  Word64  p #-}
{-# SPECIALIZE npBits  Printer p  Octal  Int  p #-}
{-# SPECIALIZE npBits  Printer p  Octal  Int8  p #-}
{-# SPECIALIZE npBits  Printer p  Octal  Int16  p #-}
{-# SPECIALIZE npBits  Printer p  Octal  Int32  p #-}
{-# SPECIALIZE npBits  Printer p  Octal  Int64  p #-}
{-# SPECIALIZE npBits  Printer p  Octal  Word  p #-}
{-# SPECIALIZE npBits  Printer p  Octal  Word8  p #-}
{-# SPECIALIZE npBits  Printer p  Octal  Word16  p #-}
{-# SPECIALIZE npBits  Printer p  Octal  Word32  p #-}
{-# SPECIALIZE npBits  Printer p  Octal  Word64  p #-}
{-# SPECIALIZE npBits  Printer p  Hexadecimal  Int  p #-}
{-# SPECIALIZE npBits  Printer p  Hexadecimal  Int8  p #-}
{-# SPECIALIZE npBits  Printer p  Hexadecimal  Int16  p #-}
{-# SPECIALIZE npBits  Printer p  Hexadecimal  Int32  p #-}
{-# SPECIALIZE npBits  Printer p  Hexadecimal  Int64  p #-}
{-# SPECIALIZE npBits  Printer p  Hexadecimal  Word  p #-}
{-# SPECIALIZE npBits  Printer p  Hexadecimal  Word8  p #-}
{-# SPECIALIZE npBits  Printer p  Hexadecimal  Word16  p #-}
{-# SPECIALIZE npBits  Printer p  Hexadecimal  Word32  p #-}
{-# SPECIALIZE npBits  Printer p  Hexadecimal  Word64  p #-}
{-# SPECIALIZE npBits  Printer p  LowHex  Int  p #-}
{-# SPECIALIZE npBits  Printer p  LowHex  Int8  p #-}
{-# SPECIALIZE npBits  Printer p  LowHex  Int16  p #-}
{-# SPECIALIZE npBits  Printer p  LowHex  Int32  p #-}
{-# SPECIALIZE npBits  Printer p  LowHex  Int64  p #-}
{-# SPECIALIZE npBits  Printer p  LowHex  Word  p #-}
{-# SPECIALIZE npBits  Printer p  LowHex  Word8  p #-}
{-# SPECIALIZE npBits  Printer p  LowHex  Word16  p #-}
{-# SPECIALIZE npBits  Printer p  LowHex  Word32  p #-}
{-# SPECIALIZE npBits  Printer p  LowHex  Word64  p #-}
{-# SPECIALIZE npBits  Printer p  UpHex  Int  p #-}
{-# SPECIALIZE npBits  Printer p  UpHex  Int8  p #-}
{-# SPECIALIZE npBits  Printer p  UpHex  Int16  p #-}
{-# SPECIALIZE npBits  Printer p  UpHex  Int32  p #-}
{-# SPECIALIZE npBits  Printer p  UpHex  Int64  p #-}
{-# SPECIALIZE npBits  Printer p  UpHex  Word  p #-}
{-# SPECIALIZE npBits  Printer p  UpHex  Word8  p #-}
{-# SPECIALIZE npBits  Printer p  UpHex  Word16  p #-}
{-# SPECIALIZE npBits  Printer p  UpHex  Word32  p #-}
{-# SPECIALIZE npBits  Printer p  UpHex  Word64  p #-}
{-# SPECIALIZE npBits  (Ord α, Num α, Bits α, Printer p)  Binary  α  p #-}
{-# SPECIALIZE npBits  (Ord α, Num α, Bits α, Printer p)  Octal  α  p #-}
{-# SPECIALIZE npBits  (Ord α, Num α, Bits α, Printer p)  Hexadecimal  α  p #-}
{-# SPECIALIZE npBits  (Ord α, Num α, Bits α, Printer p)  LowHex  α  p #-}
{-# SPECIALIZE npBits  (Ord α, Num α, Bits α, Printer p)  UpHex  α  p #-}

-- | Print a non-positive binary number in the binary numeral system.
npBinaryBits  (Ord α, Num α, Bits α, Printer p)  α  p
npBinaryBits :: α -> p
npBinaryBits = Binary -> α -> p
forall s α p.
(BitSystem s, Ord α, Num α, Bits α, Printer p) =>
s -> α -> p
npBits Binary
Binary
{-# INLINE npBinaryBits #-}

-- | Print a non-positive binary number in the octal numeral system.
npOctalBits  (Ord α, Num α, Bits α, Printer p)  α  p
npOctalBits :: α -> p
npOctalBits = Octal -> α -> p
forall s α p.
(BitSystem s, Ord α, Num α, Bits α, Printer p) =>
s -> α -> p
npBits Octal
Octal
{-# INLINE npOctalBits #-}

-- | Print a non-positive binary number in the hexadecimal numeral system
--   using lower case digits.
npLowHexBits  (Ord α, Num α, Bits α, Printer p)  α  p
npLowHexBits :: α -> p
npLowHexBits = LowHex -> α -> p
forall s α p.
(BitSystem s, Ord α, Num α, Bits α, Printer p) =>
s -> α -> p
npBits LowHex
LowHex
{-# INLINE npLowHexBits #-}

-- | Print a non-positive binary number in the hexadecimal numeral system
--   using upper case digits.
npUpHexBits  (Ord α, Num α, Bits α, Printer p)  α  p
npUpHexBits :: α -> p
npUpHexBits = UpHex -> α -> p
forall s α p.
(BitSystem s, Ord α, Num α, Bits α, Printer p) =>
s -> α -> p
npBits UpHex
UpHex
{-# INLINE npUpHexBits #-}

-- | Print a number in the specified positional numeral system.
number'  (PositionalSystem s, Integral α, Printer p)
         s
         p -- ^ Prefix for negative values
         p -- ^ Zero printer
         p -- ^ Prefix for positive values
         α  p
number' :: s -> p -> p -> p -> α -> p
number' s
s p
neg p
z p
pos α
n = case α -> α -> Ordering
forall a. Ord a => a -> a -> Ordering
compare α
n α
0 of
    Ordering
LT  p -> α -> p
forall t. Printer t => t -> α -> t
go p
neg α
q p -> p -> p
forall a. Semigroup a => a -> a -> a
<> s -> Char -> p
forall s p. (PositionalSystem s, Printer p) => s -> Char -> p
printDigitIn s
s Char
d
      where (α
q, α
r) = α -> α -> (α, α)
forall a. Integral a => a -> a -> (a, a)
quotRem α
n (α -> α
forall a. Num a => a -> a
negate α
radix)
            !d :: Char
d     = s -> Int -> Char
forall s. PositionalSystem s => s -> Int -> Char
intToDigitIn s
s (Int -> Char) -> Int -> Char
forall a b. (a -> b) -> a -> b
$ Int -> Int
forall a. Num a => a -> a
negate (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ α -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral α
r
    Ordering
EQ  p
z
    Ordering
GT  p -> α -> p
forall t. Printer t => t -> α -> t
go p
pos α
q p -> p -> p
forall a. Semigroup a => a -> a -> a
<> s -> Char -> p
forall s p. (PositionalSystem s, Printer p) => s -> Char -> p
printDigitIn s
s Char
d
      where (α
q, α
r) = α -> α -> (α, α)
forall a. Integral a => a -> a -> (a, a)
quotRem α
n α
radix
            !d :: Char
d     = s -> Int -> Char
forall s. PositionalSystem s => s -> Int -> Char
intToDigitIn s
s (Int -> Char) -> Int -> Char
forall a b. (a -> b) -> a -> b
$ α -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral α
r
  where go :: t -> α -> t
go t
p α
0 = t
p
        go t
p α
m = t -> α -> t
go t
p α
q t -> t -> t
forall a. Semigroup a => a -> a -> a
<> s -> Char -> t
forall s p. (PositionalSystem s, Printer p) => s -> Char -> p
printDigitIn s
s Char
d
          where (α
q, α
r) = α -> α -> (α, α)
forall a. Integral a => a -> a -> (a, a)
quotRem α
m α
radix
                !d :: Char
d     = s -> Int -> Char
forall s. PositionalSystem s => s -> Int -> Char
intToDigitIn s
s (Int -> Char) -> Int -> Char
forall a b. (a -> b) -> a -> b
$ α -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral α
r
        radix :: α
radix = s -> α
forall s α. (PositionalSystem s, Num α) => s -> α
radixIn s
s
{-# SPECIALIZE number'  Printer p  Decimal  p  p  p  Int  p #-}
{-# SPECIALIZE number'  Printer p  Decimal  p  p  p  Int8  p #-}
{-# SPECIALIZE number'  Printer p  Decimal  p  p  p  Int16  p #-}
{-# SPECIALIZE number'  Printer p  Decimal  p  p  p  Int32  p #-}
{-# SPECIALIZE number'  Printer p  Decimal  p  p  p  Int64  p #-}
{-# SPECIALIZE number'  Printer p  Decimal  p  p  p  Word  p #-}
{-# SPECIALIZE number'  Printer p  Decimal  p  p  p  Word8  p #-}
{-# SPECIALIZE number'  Printer p  Decimal  p  p  p  Word16  p #-}
{-# SPECIALIZE number'  Printer p  Decimal  p  p  p  Word32  p #-}
{-# SPECIALIZE number'  Printer p  Decimal  p  p  p  Word64  p #-}
{-# SPECIALIZE number'  (Integral α, Printer p)  Binary  p  p  p  α  p #-}
{-# SPECIALIZE number'  (Integral α, Printer p)  Decimal  p  p  p  α  p #-}
{-# SPECIALIZE number'  (Integral α, Printer p)  Octal  p  p  p  α  p #-}
{-# SPECIALIZE number'  (Integral α, Printer p)  Hexadecimal  p  p  p  α  p #-}
{-# SPECIALIZE number'  (Integral α, Printer p)  LowHex  p  p  p  α  p #-}
{-# SPECIALIZE number'  (Integral α, Printer p)  UpHex  p  p  p  α  p #-}

-- | Print a number in the specified positional numeral system. Negative
--   values are prefixed with a minus sign.
number  (PositionalSystem s, Integral α, Printer p)  s  α  p
number :: s -> α -> p
number s
s = s -> p -> p -> p -> α -> p
forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
s -> p -> p -> p -> α -> p
number' s
s (Char -> p
forall p. Printer p => Char -> p
char7 Char
'-') (s -> p
forall s p. (PositionalSystem s, Printer p) => s -> p
printZeroIn s
s) p
forall a. Monoid a => a
mempty
{-# INLINE number #-}

-- | Print a number in the binary numeral system.
binary'  (Integral α, Printer p)
         p -- ^ Prefix for negative values
         p -- ^ Zero printer
         p -- ^ Prefix for positive values
         α  p
binary' :: p -> p -> p -> α -> p
binary' = Binary -> p -> p -> p -> α -> p
forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
s -> p -> p -> p -> α -> p
number' Binary
Binary
{-# INLINE binary' #-}

-- | Print a number in the binary numeral system. Negative values
--   are prefixed with a minus sign.
binary  (Integral α, Printer p)  α  p
binary :: α -> p
binary = Binary -> α -> p
forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
s -> α -> p
number Binary
Binary
{-# INLINE binary #-}

-- | Print a number in the octal numeral system.
octal'  (Integral α, Printer p)
        p -- ^ Prefix for negative values
        p -- ^ Zero printer
        p -- ^ Prefix for positive values
        α  p
octal' :: p -> p -> p -> α -> p
octal' = Octal -> p -> p -> p -> α -> p
forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
s -> p -> p -> p -> α -> p
number' Octal
Octal
{-# INLINE octal' #-}

-- | Print a number in the octal numeral system. Negative values
--   are prefixed with a minus sign.
octal  (Integral α, Printer p)  α  p
octal :: α -> p
octal = Octal -> α -> p
forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
s -> α -> p
number Octal
Octal
{-# INLINE octal #-}

-- | Print a number in the decimal numeral system.
decimal'  (Integral α, Printer p)
          p -- ^ Prefix for negative values
          p -- ^ Zero printer
          p -- ^ Prefix for positive values
          α  p
decimal' :: p -> p -> p -> α -> p
decimal' = Decimal -> p -> p -> p -> α -> p
forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
s -> p -> p -> p -> α -> p
number' Decimal
Decimal
{-# INLINE decimal' #-}

-- | Print a number in the decimal numeral system. Negative values
--   are prefixed with a minus sign.
decimal  (Integral α, Printer p)  α  p
decimal :: α -> p
decimal = Decimal -> α -> p
forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
s -> α -> p
number Decimal
Decimal
{-# INLINE decimal #-}

-- | Print a number in the hexadecimal numeral system using lower case
--   digits.
lowHex'  (Integral α, Printer p)
         p -- ^ Prefix for negative values
         p -- ^ Zero printer
         p -- ^ Prefix for positive values
         α  p
lowHex' :: p -> p -> p -> α -> p
lowHex' = LowHex -> p -> p -> p -> α -> p
forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
s -> p -> p -> p -> α -> p
number' LowHex
LowHex
{-# INLINE lowHex' #-}

-- | Print a number in the hexadecimal numeral system using lower case
--   digits. Negative values are prefixed with a minus sign.
lowHex  (Integral α, Printer p)  α  p
lowHex :: α -> p
lowHex = LowHex -> α -> p
forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
s -> α -> p
number LowHex
LowHex
{-# INLINE lowHex #-}

-- | Print a number in the hexadecimal numeral system using upper case
--   digits.
upHex'  (Integral α, Printer p)
        p -- ^ Prefix for negative values
        p -- ^ Zero printer
        p -- ^ Prefix for positive values
        α  p
upHex' :: p -> p -> p -> α -> p
upHex' = UpHex -> p -> p -> p -> α -> p
forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
s -> p -> p -> p -> α -> p
number' UpHex
UpHex
{-# INLINE upHex' #-}

-- | Print a number in the hexadecimal numeral system using upper case
--   digits. Negative values are prefixed with a minus sign.
upHex  (Integral α, Printer p)  α  p
upHex :: α -> p
upHex = UpHex -> α -> p
forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
s -> α -> p
number UpHex
UpHex
{-# INLINE upHex #-}

-- | Print a binary number in the specified positional numeral system.
bits'  (BitSystem s, Ord α, Num α, Bits α, Printer p)
       s
       p -- ^ Prefix for negative values
       p -- ^ Zero printer
       p -- ^ Prefix for positive values
       α  p
bits' :: s -> p -> p -> p -> α -> p
bits' s
s p
neg p
z p
pos α
n = case α -> α -> Ordering
forall a. Ord a => a -> a -> Ordering
compare α
n α
0 of
    Ordering
LT  case α -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit α
n Int
0 of
           Bool
True  p -> α -> p
forall t t. (Num t, Printer t, Bits t) => t -> t -> t
go p
neg (α -> Int -> α
forall a. Bits a => a -> Int -> a
shiftR (α -> α
forall a. Num a => a -> a
negate α
n) Int
digitBits) p -> p -> p
forall a. Semigroup a => a -> a -> a
<> s -> Char -> p
forall s p. (PositionalSystem s, Printer p) => s -> Char -> p
printDigitIn s
s Char
d
             where !d :: Char
d = s -> Int -> Char
forall s. PositionalSystem s => s -> Int -> Char
intToDigitIn s
s (Int -> Char) -> Int -> Char
forall a b. (a -> b) -> a -> b
$ Int
radix Int -> Int -> Int
forall a. Num a => a -> a -> a
- s -> α -> Int
forall s α. (BitSystem s, Bits α) => s -> α -> Int
lastDigitIn s
s α
n
           Bool
False  case α
n α -> α -> Bool
forall a. Ord a => a -> a -> Bool
> α
negRadix of
               Bool
True  p
neg p -> p -> p
forall a. Semigroup a => a -> a -> a
<> s -> Char -> p
forall s p. (PositionalSystem s, Printer p) => s -> Char -> p
printDigitIn s
s Char
d'
               Bool
False  p -> α -> p
forall t t. (Num t, Printer t, Bits t) => t -> t -> t
go p
neg α
m p -> p -> p
forall a. Semigroup a => a -> a -> a
<> s -> Char -> p
forall s p. (PositionalSystem s, Printer p) => s -> Char -> p
printDigitIn s
s Char
d'
                 where m :: α
m | Int
d Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0    = α -> α
forall a. Num a => a -> a
negate (α -> α) -> α -> α
forall a b. (a -> b) -> a -> b
$ α -> Int -> α
forall a. Bits a => a -> Int -> a
shiftR α
n Int
digitBits
                         | Bool
otherwise = α -> α
forall a. Bits a => a -> a
complement (α -> α) -> α -> α
forall a b. (a -> b) -> a -> b
$ α -> Int -> α
forall a. Bits a => a -> Int -> a
shiftR α
n Int
digitBits
             where !d :: Int
d  = s -> α -> Int
forall s α. (BitSystem s, Bits α) => s -> α -> Int
lastDigitIn s
s α
n
                   !d' :: Char
d' = s -> Int -> Char
forall s. PositionalSystem s => s -> Int -> Char
intToDigitIn s
s (Int -> Char) -> Int -> Char
forall a b. (a -> b) -> a -> b
$ (Int
radix Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
d) Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int
digitMask
    Ordering
EQ  p
z
    Ordering
GT  p -> α -> p
forall t t. (Num t, Printer t, Bits t) => t -> t -> t
go p
pos (α -> Int -> α
forall a. Bits a => a -> Int -> a
shiftR α
n Int
digitBits) p -> p -> p
forall a. Semigroup a => a -> a -> a
<> s -> Char -> p
forall s p. (PositionalSystem s, Printer p) => s -> Char -> p
printDigitIn s
s Char
d
      where !d :: Char
d = s -> Int -> Char
forall s. PositionalSystem s => s -> Int -> Char
intToDigitIn s
s (Int -> Char) -> Int -> Char
forall a b. (a -> b) -> a -> b
$ s -> α -> Int
forall s α. (BitSystem s, Bits α) => s -> α -> Int
lastDigitIn s
s α
n
  where go :: t -> t -> t
go t
p t
0 = t
p
        go t
p t
m = t -> t -> t
go t
p (t -> Int -> t
forall a. Bits a => a -> Int -> a
shiftR t
m Int
digitBits) t -> t -> t
forall a. Semigroup a => a -> a -> a
<> s -> Char -> t
forall s p. (PositionalSystem s, Printer p) => s -> Char -> p
printDigitIn s
s Char
d
          where !d :: Char
d = s -> Int -> Char
forall s. PositionalSystem s => s -> Int -> Char
intToDigitIn s
s (Int -> Char) -> Int -> Char
forall a b. (a -> b) -> a -> b
$ s -> t -> Int
forall s α. (BitSystem s, Bits α) => s -> α -> Int
lastDigitIn s
s t
m
        radix :: Int
radix     = s -> Int
forall s α. (PositionalSystem s, Num α) => s -> α
radixIn s
s
        digitMask :: Int
digitMask = s -> Int
forall s α. (BitSystem s, Num α) => s -> α
digitMaskIn s
s
        digitBits :: Int
digitBits = s -> Int
forall s. BitSystem s => s -> Int
digitBitsIn s
s
        negRadix :: α
negRadix  = α -> α
forall a. Bits a => a -> a
complement (α -> α) -> α -> α
forall a b. (a -> b) -> a -> b
$ s -> α
forall s α. (BitSystem s, Num α) => s -> α
digitMaskIn s
s
{-# SPECIALIZE bits'  Printer p  Binary  p  p  p  Int  p #-}
{-# SPECIALIZE bits'  Printer p  Binary  p  p  p  Int8  p #-}
{-# SPECIALIZE bits'  Printer p  Binary  p  p  p  Int16  p #-}
{-# SPECIALIZE bits'  Printer p  Binary  p  p  p  Int32  p #-}
{-# SPECIALIZE bits'  Printer p  Binary  p  p  p  Int64  p #-}
{-# SPECIALIZE bits'  Printer p  Binary  p  p  p  Word  p #-}
{-# SPECIALIZE bits'  Printer p  Binary  p  p  p  Word8  p #-}
{-# SPECIALIZE bits'  Printer p  Binary  p  p  p  Word16  p #-}
{-# SPECIALIZE bits'  Printer p  Binary  p  p  p  Word32  p #-}
{-# SPECIALIZE bits'  Printer p  Binary  p  p  p  Word64  p #-}
{-# SPECIALIZE bits'  Printer p  Octal  p  p  p  Int  p #-}
{-# SPECIALIZE bits'  Printer p  Octal  p  p  p  Int8  p #-}
{-# SPECIALIZE bits'  Printer p  Octal  p  p  p  Int16  p #-}
{-# SPECIALIZE bits'  Printer p  Octal  p  p  p  Int32  p #-}
{-# SPECIALIZE bits'  Printer p  Octal  p  p  p  Int64  p #-}
{-# SPECIALIZE bits'  Printer p  Octal  p  p  p  Word  p #-}
{-# SPECIALIZE bits'  Printer p  Octal  p  p  p  Word8  p #-}
{-# SPECIALIZE bits'  Printer p  Octal  p  p  p  Word16  p #-}
{-# SPECIALIZE bits'  Printer p  Octal  p  p  p  Word32  p #-}
{-# SPECIALIZE bits'  Printer p  Octal  p  p  p  Word64  p #-}
{-# SPECIALIZE bits'  Printer p  Hexadecimal  p  p  p  Int  p #-}
{-# SPECIALIZE bits'  Printer p  Hexadecimal  p  p  p  Int8  p #-}
{-# SPECIALIZE bits'  Printer p  Hexadecimal  p  p  p  Int16  p #-}
{-# SPECIALIZE bits'  Printer p  Hexadecimal  p  p  p  Int32  p #-}
{-# SPECIALIZE bits'  Printer p  Hexadecimal  p  p  p  Int64  p #-}
{-# SPECIALIZE bits'  Printer p  Hexadecimal  p  p  p  Word  p #-}
{-# SPECIALIZE bits'  Printer p  Hexadecimal  p  p  p  Word8  p #-}
{-# SPECIALIZE bits'  Printer p  Hexadecimal  p  p  p  Word16  p #-}
{-# SPECIALIZE bits'  Printer p  Hexadecimal  p  p  p  Word32  p #-}
{-# SPECIALIZE bits'  Printer p  Hexadecimal  p  p  p  Word64  p #-}
{-# SPECIALIZE bits'  Printer p  LowHex  p  p  p  Int  p #-}
{-# SPECIALIZE bits'  Printer p  LowHex  p  p  p  Int8  p #-}
{-# SPECIALIZE bits'  Printer p  LowHex  p  p  p  Int16  p #-}
{-# SPECIALIZE bits'  Printer p  LowHex  p  p  p  Int32  p #-}
{-# SPECIALIZE bits'  Printer p  LowHex  p  p  p  Int64  p #-}
{-# SPECIALIZE bits'  Printer p  LowHex  p  p  p  Word  p #-}
{-# SPECIALIZE bits'  Printer p  LowHex  p  p  p  Word8  p #-}
{-# SPECIALIZE bits'  Printer p  LowHex  p  p  p  Word16  p #-}
{-# SPECIALIZE bits'  Printer p  LowHex  p  p  p  Word32  p #-}
{-# SPECIALIZE bits'  Printer p  LowHex  p  p  p  Word64  p #-}
{-# SPECIALIZE bits'  Printer p  UpHex  p  p  p  Int  p #-}
{-# SPECIALIZE bits'  Printer p  UpHex  p  p  p  Int8  p #-}
{-# SPECIALIZE bits'  Printer p  UpHex  p  p  p  Int16  p #-}
{-# SPECIALIZE bits'  Printer p  UpHex  p  p  p  Int32  p #-}
{-# SPECIALIZE bits'  Printer p  UpHex  p  p  p  Int64  p #-}
{-# SPECIALIZE bits'  Printer p  UpHex  p  p  p  Word  p #-}
{-# SPECIALIZE bits'  Printer p  UpHex  p  p  p  Word8  p #-}
{-# SPECIALIZE bits'  Printer p  UpHex  p  p  p  Word16  p #-}
{-# SPECIALIZE bits'  Printer p  UpHex  p  p  p  Word32  p #-}
{-# SPECIALIZE bits'  Printer p  UpHex  p  p  p  Word64  p #-}
{-# SPECIALIZE bits'  (Ord α, Num α, Bits α, Printer p)  Binary  p  p  p  α  p #-}
{-# SPECIALIZE bits'  (Ord α, Num α, Bits α, Printer p)  Octal  p  p  p  α  p #-}
{-# SPECIALIZE bits'  (Ord α, Num α, Bits α, Printer p)  Hexadecimal  p  p  p  α  p #-}
{-# SPECIALIZE bits'  (Ord α, Num α, Bits α, Printer p)  LowHex  p  p  p  α  p #-}
{-# SPECIALIZE bits'  (Ord α, Num α, Bits α, Printer p)  UpHex  p  p  p  α  p #-}

-- | Print a binary number in the specified positional numeral system.
--   Negative values are prefixed with a minus sign.
bits  (BitSystem s, Ord α, Num α, Bits α, Printer p)  s  α  p
bits :: s -> α -> p
bits s
s = s -> p -> p -> p -> α -> p
forall s α p.
(BitSystem s, Ord α, Num α, Bits α, Printer p) =>
s -> p -> p -> p -> α -> p
bits' s
s (Char -> p
forall p. Printer p => Char -> p
char7 Char
'-') (s -> p
forall s p. (PositionalSystem s, Printer p) => s -> p
printZeroIn s
s) p
forall a. Monoid a => a
mempty
{-# INLINE bits #-}

-- | Print a binary number in the binary numeral system.
binaryBits'  (Ord α, Num α, Bits α, Printer p)
             p -- ^ Prefix for negative values
             p -- ^ Zero printer
             p -- ^ Prefix for positive values
             α  p
binaryBits' :: p -> p -> p -> α -> p
binaryBits' = Binary -> p -> p -> p -> α -> p
forall s α p.
(BitSystem s, Ord α, Num α, Bits α, Printer p) =>
s -> p -> p -> p -> α -> p
bits' Binary
Binary
{-# INLINE binaryBits' #-}

-- | Print a binary number in the binary numeral system. Negative values
--   are prefixed with a minus sign.
binaryBits  (Ord α, Num α, Bits α, Printer p)  α  p
binaryBits :: α -> p
binaryBits = Binary -> α -> p
forall s α p.
(BitSystem s, Ord α, Num α, Bits α, Printer p) =>
s -> α -> p
bits Binary
Binary
{-# INLINE binaryBits #-}

-- | Print a binary number in the octal numeral system.
octalBits'  (Ord α, Num α, Bits α, Printer p)
            p -- ^ Prefix for negative values
            p -- ^ Zero printer
            p -- ^ Prefix for positive values
            α  p
octalBits' :: p -> p -> p -> α -> p
octalBits' = Octal -> p -> p -> p -> α -> p
forall s α p.
(BitSystem s, Ord α, Num α, Bits α, Printer p) =>
s -> p -> p -> p -> α -> p
bits' Octal
Octal
{-# INLINE octalBits' #-}

-- | Print a binary number in the octal numeral system. Negative values
--   are prefixed with a minus sign.
octalBits  (Ord α, Num α, Bits α, Printer p)  α  p
octalBits :: α -> p
octalBits = Octal -> α -> p
forall s α p.
(BitSystem s, Ord α, Num α, Bits α, Printer p) =>
s -> α -> p
bits Octal
Octal
{-# INLINE octalBits #-}

-- | Print a binary number in the hexadecimal numeral system using lower
--   case digits.
lowHexBits'  (Ord α, Num α, Bits α, Printer p)
             p -- ^ Prefix for negative values
             p -- ^ Zero printer
             p -- ^ Prefix for positive values
             α  p
lowHexBits' :: p -> p -> p -> α -> p
lowHexBits' = LowHex -> p -> p -> p -> α -> p
forall s α p.
(BitSystem s, Ord α, Num α, Bits α, Printer p) =>
s -> p -> p -> p -> α -> p
bits' LowHex
LowHex
{-# INLINE lowHexBits' #-}

-- | Print a binary number in the hexadecimal numeral system using lower
--   case digits. Negative values are prefixed with a minus sign.
lowHexBits  (Ord α, Num α, Bits α, Printer p)  α  p
lowHexBits :: α -> p
lowHexBits = LowHex -> α -> p
forall s α p.
(BitSystem s, Ord α, Num α, Bits α, Printer p) =>
s -> α -> p
bits LowHex
LowHex
{-# INLINE lowHexBits #-}

-- | Print a binary number in the hexadecimal numeral system using upper
--   case digits.
upHexBits'  (Ord α, Num α, Bits α, Printer p)
            p -- ^ Prefix for negative values
            p -- ^ Zero printer
            p -- ^ Prefix for positive values
            α  p
upHexBits' :: p -> p -> p -> α -> p
upHexBits' = UpHex -> p -> p -> p -> α -> p
forall s α p.
(BitSystem s, Ord α, Num α, Bits α, Printer p) =>
s -> p -> p -> p -> α -> p
bits' UpHex
UpHex
{-# INLINE upHexBits' #-}

-- | Print a binary number in the hexadecimal numeral system using upper
--   case digits. Negative values are prefixed with a minus sign.
upHexBits  (Ord α, Num α, Bits α, Printer p)  α  p
upHexBits :: α -> p
upHexBits = UpHex -> α -> p
forall s α p.
(BitSystem s, Ord α, Num α, Bits α, Printer p) =>
s -> α -> p
bits UpHex
UpHex
{-# INLINE upHexBits #-}