{-# LANGUAGE CPP #-}
{-# LANGUAGE UnicodeSyntax #-}
{-# LANGUAGE DeriveDataTypeable #-}
#if __GLASGOW_HASKELL__ >= 706
{-# LANGUAGE DeriveGeneric #-}
#endif
{-# LANGUAGE BangPatterns #-}
module Text.Printer.Integral
(
PositionalSystem(..)
, BitSystem(..)
, Binary(..)
, Octal(..)
, Decimal(..)
, Hexadecimal(..)
, LowHex(..)
, UpHex(..)
, 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
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
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 p. Printer p => 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 #-}
class PositionalSystem s ⇒ BitSystem s where
digitBitsIn ∷ s → Int
digitMaskIn ∷ Num α ⇒ s → α
lastDigitIn ∷ Bits α ⇒ s → α → Int
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
$cfrom :: forall x. Binary -> Rep Binary x
from :: forall x. Binary -> Rep Binary x
$cto :: forall x. Rep Binary x -> Binary
to :: forall x. Rep Binary x -> Binary
Generic
#endif
, Binary -> Binary -> Bool
(Binary -> Binary -> Bool)
-> (Binary -> Binary -> Bool) -> Eq Binary
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Binary -> Binary -> Bool
== :: Binary -> Binary -> Bool
$c/= :: Binary -> Binary -> Bool
/= :: 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
$ccompare :: Binary -> Binary -> Ordering
compare :: Binary -> Binary -> Ordering
$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
>= :: Binary -> Binary -> Bool
$cmax :: Binary -> Binary -> Binary
max :: Binary -> Binary -> Binary
$cmin :: Binary -> Binary -> Binary
min :: Binary -> Binary -> 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
$cshowsPrec :: Int -> Binary -> ShowS
showsPrec :: Int -> Binary -> ShowS
$cshow :: Binary -> String
show :: Binary -> String
$cshowList :: [Binary] -> ShowS
showList :: [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
$creadsPrec :: Int -> ReadS Binary
readsPrec :: Int -> ReadS Binary
$creadList :: ReadS [Binary]
readList :: ReadS [Binary]
$creadPrec :: ReadPrec Binary
readPrec :: ReadPrec Binary
$creadListPrec :: ReadPrec [Binary]
readListPrec :: ReadPrec [Binary]
Read )
instance PositionalSystem Binary where
systemName :: Binary -> String
systemName Binary
_ = String
"binary"
{-# INLINE systemName #-}
radixIn :: forall α. Num α => 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 :: forall α. Num α => Binary -> Char -> Maybe α
fromDigitIn Binary
_ = Char -> Maybe α
forall a. Num a => Char -> Maybe a
A.fromBinDigit
{-# INLINE fromDigitIn #-}
fromNzDigitIn :: forall α. Num α => Binary -> Char -> Maybe α
fromNzDigitIn Binary
_ = Char -> Maybe α
forall a. Num a => Char -> Maybe a
A.fromNzBinDigit
{-# INLINE fromNzDigitIn #-}
unsafeFromDigitIn :: forall α. Num α => 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 :: forall p. Printer p => 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 :: forall α. Num α => Binary -> α
digitMaskIn Binary
_ = α
1
{-# INLINE digitMaskIn #-}
lastDigitIn :: forall α. Bits α => 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 #-}
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
$cfrom :: forall x. Octal -> Rep Octal x
from :: forall x. Octal -> Rep Octal x
$cto :: forall x. Rep Octal x -> Octal
to :: forall x. Rep Octal x -> Octal
Generic
#endif
, Octal -> Octal -> Bool
(Octal -> Octal -> Bool) -> (Octal -> Octal -> Bool) -> Eq Octal
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Octal -> Octal -> Bool
== :: Octal -> Octal -> Bool
$c/= :: Octal -> Octal -> Bool
/= :: 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
$ccompare :: Octal -> Octal -> Ordering
compare :: Octal -> Octal -> Ordering
$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
>= :: Octal -> Octal -> Bool
$cmax :: Octal -> Octal -> Octal
max :: Octal -> Octal -> Octal
$cmin :: Octal -> Octal -> Octal
min :: Octal -> Octal -> 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
$cshowsPrec :: Int -> Octal -> ShowS
showsPrec :: Int -> Octal -> ShowS
$cshow :: Octal -> String
show :: Octal -> String
$cshowList :: [Octal] -> ShowS
showList :: [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
$creadsPrec :: Int -> ReadS Octal
readsPrec :: Int -> ReadS Octal
$creadList :: ReadS [Octal]
readList :: ReadS [Octal]
$creadPrec :: ReadPrec Octal
readPrec :: ReadPrec Octal
$creadListPrec :: ReadPrec [Octal]
readListPrec :: ReadPrec [Octal]
Read )
instance PositionalSystem Octal where
systemName :: Octal -> String
systemName Octal
_ = String
"octal"
{-# INLINE systemName #-}
radixIn :: forall α. Num α => 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 :: forall α. Num α => Octal -> Char -> Maybe α
fromDigitIn Octal
_ = Char -> Maybe α
forall a. Num a => Char -> Maybe a
A.fromOctDigit
{-# INLINE fromDigitIn #-}
fromNzDigitIn :: forall α. Num α => Octal -> Char -> Maybe α
fromNzDigitIn Octal
_ = Char -> Maybe α
forall a. Num a => Char -> Maybe a
A.fromNzOctDigit
{-# INLINE fromNzDigitIn #-}
unsafeFromDigitIn :: forall α. Num α => 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 :: forall p. Printer p => 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 :: forall α. Num α => Octal -> α
digitMaskIn Octal
_ = α
7
{-# INLINE digitMaskIn #-}
lastDigitIn :: forall α. Bits α => 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 #-}
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
$cfrom :: forall x. Decimal -> Rep Decimal x
from :: forall x. Decimal -> Rep Decimal x
$cto :: forall x. Rep Decimal x -> Decimal
to :: forall x. Rep Decimal x -> Decimal
Generic
#endif
, Decimal -> Decimal -> Bool
(Decimal -> Decimal -> Bool)
-> (Decimal -> Decimal -> Bool) -> Eq Decimal
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Decimal -> Decimal -> Bool
== :: Decimal -> Decimal -> Bool
$c/= :: Decimal -> Decimal -> Bool
/= :: 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
$ccompare :: Decimal -> Decimal -> Ordering
compare :: Decimal -> Decimal -> Ordering
$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
>= :: Decimal -> Decimal -> Bool
$cmax :: Decimal -> Decimal -> Decimal
max :: Decimal -> Decimal -> Decimal
$cmin :: Decimal -> Decimal -> Decimal
min :: Decimal -> Decimal -> 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
$cshowsPrec :: Int -> Decimal -> ShowS
showsPrec :: Int -> Decimal -> ShowS
$cshow :: Decimal -> String
show :: Decimal -> String
$cshowList :: [Decimal] -> ShowS
showList :: [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
$creadsPrec :: Int -> ReadS Decimal
readsPrec :: Int -> ReadS Decimal
$creadList :: ReadS [Decimal]
readList :: ReadS [Decimal]
$creadPrec :: ReadPrec Decimal
readPrec :: ReadPrec Decimal
$creadListPrec :: ReadPrec [Decimal]
readListPrec :: ReadPrec [Decimal]
Read )
instance PositionalSystem Decimal where
systemName :: Decimal -> String
systemName Decimal
_ = String
"decimal"
{-# INLINE systemName #-}
radixIn :: forall α. Num α => 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 :: forall α. Num α => Decimal -> Char -> Maybe α
fromDigitIn Decimal
_ = Char -> Maybe α
forall a. Num a => Char -> Maybe a
A.fromDecDigit
{-# INLINE fromDigitIn #-}
fromNzDigitIn :: forall α. Num α => Decimal -> Char -> Maybe α
fromNzDigitIn Decimal
_ = Char -> Maybe α
forall a. Num a => Char -> Maybe a
A.fromNzDecDigit
{-# INLINE fromNzDigitIn #-}
unsafeFromDigitIn :: forall α. Num α => 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 :: forall p. Printer p => Decimal -> p
printZeroIn Decimal
_ = Char -> p
forall p. Printer p => Char -> p
char7 Char
'0'
{-# INLINE printZeroIn #-}
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
$cfrom :: forall x. Hexadecimal -> Rep Hexadecimal x
from :: forall x. Hexadecimal -> Rep Hexadecimal x
$cto :: forall x. Rep Hexadecimal x -> Hexadecimal
to :: forall x. Rep Hexadecimal x -> Hexadecimal
Generic
#endif
, Hexadecimal -> Hexadecimal -> Bool
(Hexadecimal -> Hexadecimal -> Bool)
-> (Hexadecimal -> Hexadecimal -> Bool) -> Eq Hexadecimal
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Hexadecimal -> Hexadecimal -> Bool
== :: Hexadecimal -> Hexadecimal -> Bool
$c/= :: Hexadecimal -> Hexadecimal -> Bool
/= :: 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
$ccompare :: Hexadecimal -> Hexadecimal -> Ordering
compare :: Hexadecimal -> Hexadecimal -> Ordering
$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
>= :: Hexadecimal -> Hexadecimal -> Bool
$cmax :: Hexadecimal -> Hexadecimal -> Hexadecimal
max :: Hexadecimal -> Hexadecimal -> Hexadecimal
$cmin :: Hexadecimal -> Hexadecimal -> Hexadecimal
min :: Hexadecimal -> Hexadecimal -> 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
$cshowsPrec :: Int -> Hexadecimal -> ShowS
showsPrec :: Int -> Hexadecimal -> ShowS
$cshow :: Hexadecimal -> String
show :: Hexadecimal -> String
$cshowList :: [Hexadecimal] -> ShowS
showList :: [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
$creadsPrec :: Int -> ReadS Hexadecimal
readsPrec :: Int -> ReadS Hexadecimal
$creadList :: ReadS [Hexadecimal]
readList :: ReadS [Hexadecimal]
$creadPrec :: ReadPrec Hexadecimal
readPrec :: ReadPrec Hexadecimal
$creadListPrec :: ReadPrec [Hexadecimal]
readListPrec :: ReadPrec [Hexadecimal]
Read )
instance PositionalSystem Hexadecimal where
systemName :: Hexadecimal -> String
systemName Hexadecimal
_ = String
"hexadecimal"
{-# INLINE systemName #-}
radixIn :: forall α. Num α => 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 :: forall α. Num α => Hexadecimal -> Char -> Maybe α
fromDigitIn Hexadecimal
_ = Char -> Maybe α
forall a. Num a => Char -> Maybe a
A.fromHexDigit
{-# INLINE fromDigitIn #-}
fromNzDigitIn :: forall α. Num α => Hexadecimal -> Char -> Maybe α
fromNzDigitIn Hexadecimal
_ = Char -> Maybe α
forall a. Num a => Char -> Maybe a
A.fromNzHexDigit
{-# INLINE fromNzDigitIn #-}
unsafeFromDigitIn :: forall α. Num α => 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 :: forall p. Printer p => 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 :: forall α. Num α => Hexadecimal -> α
digitMaskIn Hexadecimal
_ = α
15
{-# INLINE digitMaskIn #-}
lastDigitIn :: forall α. Bits α => 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 #-}
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
$cfrom :: forall x. LowHex -> Rep LowHex x
from :: forall x. LowHex -> Rep LowHex x
$cto :: forall x. Rep LowHex x -> LowHex
to :: forall x. Rep LowHex x -> LowHex
Generic
#endif
, LowHex -> LowHex -> Bool
(LowHex -> LowHex -> Bool)
-> (LowHex -> LowHex -> Bool) -> Eq LowHex
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LowHex -> LowHex -> Bool
== :: LowHex -> LowHex -> Bool
$c/= :: LowHex -> LowHex -> Bool
/= :: 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
$ccompare :: LowHex -> LowHex -> Ordering
compare :: LowHex -> LowHex -> Ordering
$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
>= :: LowHex -> LowHex -> Bool
$cmax :: LowHex -> LowHex -> LowHex
max :: LowHex -> LowHex -> LowHex
$cmin :: LowHex -> LowHex -> LowHex
min :: LowHex -> LowHex -> 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
$cshowsPrec :: Int -> LowHex -> ShowS
showsPrec :: Int -> LowHex -> ShowS
$cshow :: LowHex -> String
show :: LowHex -> String
$cshowList :: [LowHex] -> ShowS
showList :: [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
$creadsPrec :: Int -> ReadS LowHex
readsPrec :: Int -> ReadS LowHex
$creadList :: ReadS [LowHex]
readList :: ReadS [LowHex]
$creadPrec :: ReadPrec LowHex
readPrec :: ReadPrec LowHex
$creadListPrec :: ReadPrec [LowHex]
readListPrec :: ReadPrec [LowHex]
Read )
instance PositionalSystem LowHex where
systemName :: LowHex -> String
systemName LowHex
_ = String
"lower case hexadecimal"
{-# INLINE systemName #-}
radixIn :: forall α. Num α => 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 :: forall α. Num α => LowHex -> Char -> Maybe α
fromDigitIn LowHex
_ = Char -> Maybe α
forall a. Num a => Char -> Maybe a
A.fromLowHexDigit
{-# INLINE fromDigitIn #-}
fromNzDigitIn :: forall α. Num α => LowHex -> Char -> Maybe α
fromNzDigitIn LowHex
_ = Char -> Maybe α
forall a. Num a => Char -> Maybe a
A.fromNzLowHexDigit
{-# INLINE fromNzDigitIn #-}
unsafeFromDigitIn :: forall α. Num α => 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 :: forall p. Printer p => 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 :: forall α. Num α => LowHex -> α
digitMaskIn LowHex
_ = α
15
{-# INLINE digitMaskIn #-}
lastDigitIn :: forall α. Bits α => 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 #-}
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
$cfrom :: forall x. UpHex -> Rep UpHex x
from :: forall x. UpHex -> Rep UpHex x
$cto :: forall x. Rep UpHex x -> UpHex
to :: forall x. Rep UpHex x -> UpHex
Generic
#endif
, UpHex -> UpHex -> Bool
(UpHex -> UpHex -> Bool) -> (UpHex -> UpHex -> Bool) -> Eq UpHex
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UpHex -> UpHex -> Bool
== :: UpHex -> UpHex -> Bool
$c/= :: UpHex -> UpHex -> Bool
/= :: 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
$ccompare :: UpHex -> UpHex -> Ordering
compare :: UpHex -> UpHex -> Ordering
$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
>= :: UpHex -> UpHex -> Bool
$cmax :: UpHex -> UpHex -> UpHex
max :: UpHex -> UpHex -> UpHex
$cmin :: UpHex -> UpHex -> UpHex
min :: UpHex -> UpHex -> 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
$cshowsPrec :: Int -> UpHex -> ShowS
showsPrec :: Int -> UpHex -> ShowS
$cshow :: UpHex -> String
show :: UpHex -> String
$cshowList :: [UpHex] -> ShowS
showList :: [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
$creadsPrec :: Int -> ReadS UpHex
readsPrec :: Int -> ReadS UpHex
$creadList :: ReadS [UpHex]
readList :: ReadS [UpHex]
$creadPrec :: ReadPrec UpHex
readPrec :: ReadPrec UpHex
$creadListPrec :: ReadPrec [UpHex]
readListPrec :: ReadPrec [UpHex]
Read )
instance PositionalSystem UpHex where
systemName :: UpHex -> String
systemName UpHex
_ = String
"upper case hexadecimal"
{-# INLINE systemName #-}
radixIn :: forall α. Num α => 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 :: forall α. Num α => UpHex -> Char -> Maybe α
fromDigitIn UpHex
_ = Char -> Maybe α
forall a. Num a => Char -> Maybe a
A.fromUpHexDigit
{-# INLINE fromDigitIn #-}
fromNzDigitIn :: forall α. Num α => UpHex -> Char -> Maybe α
fromNzDigitIn UpHex
_ = Char -> Maybe α
forall a. Num a => Char -> Maybe a
A.fromNzUpHexDigit
{-# INLINE fromNzDigitIn #-}
unsafeFromDigitIn :: forall α. Num α => 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 :: forall p. Printer p => 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 :: forall α. Num α => UpHex -> α
digitMaskIn UpHex
_ = α
15
{-# INLINE digitMaskIn #-}
lastDigitIn :: forall α. Bits α => 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 #-}
nonNegative ∷ (PositionalSystem s, Integral α, Printer p) ⇒ s → α → p
nonNegative :: forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
s -> α -> p
nonNegative s
s = p -> α -> p
forall {t}. Printer t => t -> α -> t
go (s -> Char -> p
forall p. Printer p => 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 p. Printer p => 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 α
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 α. Num α => 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 #-}
nnBinary ∷ (Integral α, Printer p) ⇒ α → p
nnBinary :: forall α p. (Integral α, Printer p) => α -> p
nnBinary = Binary -> α -> p
forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
s -> α -> p
nonNegative Binary
Binary
{-# INLINE nnBinary #-}
nnOctal ∷ (Integral α, Printer p) ⇒ α → p
nnOctal :: forall α p. (Integral α, Printer p) => α -> p
nnOctal = Octal -> α -> p
forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
s -> α -> p
nonNegative Octal
Octal
{-# INLINE nnOctal #-}
nnDecimal ∷ (Integral α, Printer p) ⇒ α → p
nnDecimal :: forall α p. (Integral α, Printer p) => α -> p
nnDecimal = Decimal -> α -> p
forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
s -> α -> p
nonNegative Decimal
Decimal
{-# INLINE nnDecimal #-}
nnLowHex ∷ (Integral α, Printer p) ⇒ α → p
nnLowHex :: forall α p. (Integral α, Printer p) => α -> p
nnLowHex = LowHex -> α -> p
forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
s -> α -> p
nonNegative LowHex
LowHex
{-# INLINE nnLowHex #-}
nnUpHex ∷ (Integral α, Printer p) ⇒ α → p
nnUpHex :: forall α p. (Integral α, Printer p) => α -> p
nnUpHex = UpHex -> α -> p
forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
s -> α -> p
nonNegative UpHex
UpHex
{-# INLINE nnUpHex #-}
nnBits ∷ (BitSystem s, Num α, Bits α, Printer p) ⇒ s → α → p
nnBits :: forall s α p.
(BitSystem s, Num α, Bits α, Printer p) =>
s -> α -> p
nnBits s
s = p -> α -> p
forall {t} {t}. (Num t, Printer t, Bits t) => t -> t -> t
go (s -> Char -> p
forall p. Printer p => 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 p. Printer p => 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 -> t -> Int
forall α. Bits α => s -> α -> 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 #-}
nnBinaryBits ∷ (Num α, Bits α, Printer p) ⇒ α → p
nnBinaryBits :: forall α p. (Num α, Bits α, Printer p) => α -> p
nnBinaryBits = Binary -> α -> p
forall s α p.
(BitSystem s, Num α, Bits α, Printer p) =>
s -> α -> p
nnBits Binary
Binary
{-# INLINE nnBinaryBits #-}
nnOctalBits ∷ (Num α, Bits α, Printer p) ⇒ α → p
nnOctalBits :: forall α p. (Num α, Bits α, Printer p) => α -> p
nnOctalBits = Octal -> α -> p
forall s α p.
(BitSystem s, Num α, Bits α, Printer p) =>
s -> α -> p
nnBits Octal
Octal
{-# INLINE nnOctalBits #-}
nnLowHexBits ∷ (Num α, Bits α, Printer p) ⇒ α → p
nnLowHexBits :: forall α p. (Num α, Bits α, Printer p) => α -> p
nnLowHexBits = LowHex -> α -> p
forall s α p.
(BitSystem s, Num α, Bits α, Printer p) =>
s -> α -> p
nnBits LowHex
LowHex
{-# INLINE nnLowHexBits #-}
nnUpHexBits ∷ (Num α, Bits α, Printer p) ⇒ α → p
nnUpHexBits :: forall α p. (Num α, Bits α, Printer p) => α -> p
nnUpHexBits = UpHex -> α -> p
forall s α p.
(BitSystem s, Num α, Bits α, Printer p) =>
s -> α -> p
nnBits UpHex
UpHex
{-# INLINE nnUpHexBits #-}
nonPositive ∷ (PositionalSystem s, Integral α, Printer p) ⇒ s → α → p
nonPositive :: forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
s -> α -> p
nonPositive s
s = p -> α -> p
forall {t}. Printer t => t -> α -> t
go (s -> Char -> p
forall p. Printer p => 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 p. Printer p => 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 α
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 α. Num α => 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 #-}
npBinary ∷ (Integral α, Printer p) ⇒ α → p
npBinary :: forall α p. (Integral α, Printer p) => α -> p
npBinary = Binary -> α -> p
forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
s -> α -> p
nonPositive Binary
Binary
{-# INLINE npBinary #-}
npOctal ∷ (Integral α, Printer p) ⇒ α → p
npOctal :: forall α p. (Integral α, Printer p) => α -> p
npOctal = Octal -> α -> p
forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
s -> α -> p
nonPositive Octal
Octal
{-# INLINE npOctal #-}
npDecimal ∷ (Integral α, Printer p) ⇒ α → p
npDecimal :: forall α p. (Integral α, Printer p) => α -> p
npDecimal = Decimal -> α -> p
forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
s -> α -> p
nonPositive Decimal
Decimal
{-# INLINE npDecimal #-}
npLowHex ∷ (Integral α, Printer p) ⇒ α → p
npLowHex :: forall α p. (Integral α, Printer p) => α -> p
npLowHex = LowHex -> α -> p
forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
s -> α -> p
nonPositive LowHex
LowHex
{-# INLINE npLowHex #-}
npUpHex ∷ (Integral α, Printer p) ⇒ α → p
npUpHex :: forall α p. (Integral α, Printer p) => α -> p
npUpHex = UpHex -> α -> p
forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
s -> α -> p
nonPositive UpHex
UpHex
{-# INLINE npUpHex #-}
npBits ∷ (BitSystem s, Ord α, Num α, Bits α, Printer p) ⇒ s → α → p
npBits :: forall s α p.
(BitSystem s, Ord α, Num α, Bits α, Printer p) =>
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 p. Printer p => 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 α. Bits α => 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 p. Printer p => 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 p. Printer p => 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 α. Bits α => 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 p. Printer p => 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 -> t -> Int
forall α. Bits α => s -> α -> Int
forall s α. (BitSystem s, Bits α) => s -> α -> Int
lastDigitIn s
s t
m
radix :: Int
radix = s -> Int
forall α. Num α => s -> α
forall s α. (PositionalSystem s, Num α) => s -> α
radixIn s
s
digitMask :: Int
digitMask = s -> Int
forall α. Num α => s -> α
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 α. Num α => 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 #-}
npBinaryBits ∷ (Ord α, Num α, Bits α, Printer p) ⇒ α → p
npBinaryBits :: forall α p. (Ord α, Num α, Bits α, Printer p) => α -> p
npBinaryBits = Binary -> α -> p
forall s α p.
(BitSystem s, Ord α, Num α, Bits α, Printer p) =>
s -> α -> p
npBits Binary
Binary
{-# INLINE npBinaryBits #-}
npOctalBits ∷ (Ord α, Num α, Bits α, Printer p) ⇒ α → p
npOctalBits :: forall α p. (Ord α, Num α, Bits α, Printer p) => α -> p
npOctalBits = Octal -> α -> p
forall s α p.
(BitSystem s, Ord α, Num α, Bits α, Printer p) =>
s -> α -> p
npBits Octal
Octal
{-# INLINE npOctalBits #-}
npLowHexBits ∷ (Ord α, Num α, Bits α, Printer p) ⇒ α → p
npLowHexBits :: forall α p. (Ord α, Num α, Bits α, Printer p) => α -> p
npLowHexBits = LowHex -> α -> p
forall s α p.
(BitSystem s, Ord α, Num α, Bits α, Printer p) =>
s -> α -> p
npBits LowHex
LowHex
{-# INLINE npLowHexBits #-}
npUpHexBits ∷ (Ord α, Num α, Bits α, Printer p) ⇒ α → p
npUpHexBits :: forall α p. (Ord α, Num α, Bits α, Printer p) => α -> p
npUpHexBits = UpHex -> α -> p
forall s α p.
(BitSystem s, Ord α, Num α, Bits α, Printer p) =>
s -> α -> p
npBits UpHex
UpHex
{-# INLINE npUpHexBits #-}
number' ∷ (PositionalSystem s, Integral α, Printer p)
⇒ s
→ p
→ p
→ p
→ α → p
number' :: forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
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 p. Printer p => 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 p. Printer p => 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 p. Printer p => 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 α
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 α. Num α => 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 #-}
number ∷ (PositionalSystem s, Integral α, Printer p) ⇒ s → α → p
number :: forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
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 p. Printer p => s -> p
forall s p. (PositionalSystem s, Printer p) => s -> p
printZeroIn s
s) p
forall a. Monoid a => a
mempty
{-# INLINE number #-}
binary' ∷ (Integral α, Printer p)
⇒ p
→ p
→ p
→ α → p
binary' :: forall α p. (Integral α, Printer p) => 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' #-}
binary ∷ (Integral α, Printer p) ⇒ α → p
binary :: forall α p. (Integral α, Printer p) => α -> p
binary = Binary -> α -> p
forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
s -> α -> p
number Binary
Binary
{-# INLINE binary #-}
octal' ∷ (Integral α, Printer p)
⇒ p
→ p
→ p
→ α → p
octal' :: forall α p. (Integral α, Printer p) => 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' #-}
octal ∷ (Integral α, Printer p) ⇒ α → p
octal :: forall α p. (Integral α, Printer p) => α -> p
octal = Octal -> α -> p
forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
s -> α -> p
number Octal
Octal
{-# INLINE octal #-}
decimal' ∷ (Integral α, Printer p)
⇒ p
→ p
→ p
→ α → p
decimal' :: forall α p. (Integral α, Printer p) => 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' #-}
decimal ∷ (Integral α, Printer p) ⇒ α → p
decimal :: forall α p. (Integral α, Printer p) => α -> p
decimal = Decimal -> α -> p
forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
s -> α -> p
number Decimal
Decimal
{-# INLINE decimal #-}
lowHex' ∷ (Integral α, Printer p)
⇒ p
→ p
→ p
→ α → p
lowHex' :: forall α p. (Integral α, Printer p) => 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' #-}
lowHex ∷ (Integral α, Printer p) ⇒ α → p
lowHex :: forall α p. (Integral α, Printer p) => α -> p
lowHex = LowHex -> α -> p
forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
s -> α -> p
number LowHex
LowHex
{-# INLINE lowHex #-}
upHex' ∷ (Integral α, Printer p)
⇒ p
→ p
→ p
→ α → p
upHex' :: forall α p. (Integral α, Printer p) => 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' #-}
upHex ∷ (Integral α, Printer p) ⇒ α → p
upHex :: forall α p. (Integral α, Printer p) => α -> p
upHex = UpHex -> α -> p
forall s α p.
(PositionalSystem s, Integral α, Printer p) =>
s -> α -> p
number UpHex
UpHex
{-# INLINE upHex #-}
bits' ∷ (BitSystem s, Ord α, Num α, Bits α, Printer p)
⇒ s
→ p
→ p
→ p
→ α → p
bits' :: forall s α p.
(BitSystem s, Ord α, Num α, Bits α, Printer p) =>
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 p. Printer p => 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 α. Bits α => 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 p. Printer p => 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 p. Printer p => 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 α. Bits α => 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 p. Printer p => 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 α. Bits α => 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 p. Printer p => 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 -> t -> Int
forall α. Bits α => s -> α -> Int
forall s α. (BitSystem s, Bits α) => s -> α -> Int
lastDigitIn s
s t
m
radix :: Int
radix = s -> Int
forall α. Num α => s -> α
forall s α. (PositionalSystem s, Num α) => s -> α
radixIn s
s
digitMask :: Int
digitMask = s -> Int
forall α. Num α => s -> α
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 α. Num α => 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 #-}
bits ∷ (BitSystem s, Ord α, Num α, Bits α, Printer p) ⇒ s → α → p
bits :: forall s α p.
(BitSystem s, Ord α, Num α, Bits α, Printer p) =>
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 p. Printer p => s -> p
forall s p. (PositionalSystem s, Printer p) => s -> p
printZeroIn s
s) p
forall a. Monoid a => a
mempty
{-# INLINE bits #-}
binaryBits' ∷ (Ord α, Num α, Bits α, Printer p)
⇒ p
→ p
→ p
→ α → p
binaryBits' :: forall α p.
(Ord α, Num α, Bits α, Printer p) =>
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' #-}
binaryBits ∷ (Ord α, Num α, Bits α, Printer p) ⇒ α → p
binaryBits :: forall α p. (Ord α, Num α, Bits α, Printer p) => α -> p
binaryBits = Binary -> α -> p
forall s α p.
(BitSystem s, Ord α, Num α, Bits α, Printer p) =>
s -> α -> p
bits Binary
Binary
{-# INLINE binaryBits #-}
octalBits' ∷ (Ord α, Num α, Bits α, Printer p)
⇒ p
→ p
→ p
→ α → p
octalBits' :: forall α p.
(Ord α, Num α, Bits α, Printer p) =>
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' #-}
octalBits ∷ (Ord α, Num α, Bits α, Printer p) ⇒ α → p
octalBits :: forall α p. (Ord α, Num α, Bits α, Printer p) => α -> p
octalBits = Octal -> α -> p
forall s α p.
(BitSystem s, Ord α, Num α, Bits α, Printer p) =>
s -> α -> p
bits Octal
Octal
{-# INLINE octalBits #-}
lowHexBits' ∷ (Ord α, Num α, Bits α, Printer p)
⇒ p
→ p
→ p
→ α → p
lowHexBits' :: forall α p.
(Ord α, Num α, Bits α, Printer p) =>
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' #-}
lowHexBits ∷ (Ord α, Num α, Bits α, Printer p) ⇒ α → p
lowHexBits :: forall α p. (Ord α, Num α, Bits α, Printer p) => α -> p
lowHexBits = LowHex -> α -> p
forall s α p.
(BitSystem s, Ord α, Num α, Bits α, Printer p) =>
s -> α -> p
bits LowHex
LowHex
{-# INLINE lowHexBits #-}
upHexBits' ∷ (Ord α, Num α, Bits α, Printer p)
⇒ p
→ p
→ p
→ α → p
upHexBits' :: forall α p.
(Ord α, Num α, Bits α, Printer p) =>
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' #-}
upHexBits ∷ (Ord α, Num α, Bits α, Printer p) ⇒ α → p
upHexBits :: forall α p. (Ord α, Num α, Bits α, Printer p) => α -> p
upHexBits = UpHex -> α -> p
forall s α p.
(BitSystem s, Ord α, Num α, Bits α, Printer p) =>
s -> α -> p
bits UpHex
UpHex
{-# INLINE upHexBits #-}