module Text.Printer.Fractional
(
PositionalSystem(..)
, BitSystem(..)
, Binary(..)
, Octal(..)
, Decimal(..)
, Hexadecimal(..)
, LowHex(..)
, UpHex(..)
, Optional(..)
, isOptional
, isRequired
, fraction'
, fraction
) where
import Data.Typeable (Typeable)
import Data.Ix (Ix)
import Data.Monoid (mempty)
import Data.Ratio (numerator, denominator)
import Text.Printer
import Text.Printer.Integral
data Optional = Optional
| Required
deriving (Typeable, Show, Read, Eq, Ord, Enum, Bounded, Ix)
isOptional ∷ Optional → Bool
isOptional Optional = True
isOptional Required = False
isRequired ∷ Optional → Bool
isRequired Optional = False
isRequired Required = True
fraction' ∷ (PositionalSystem s, Real α, Printer p)
⇒ s
→ p
→ p
→ p
→ p
→ Optional
→ α → p
fraction' s neg z pos sep i a
| n == 0 = z
| d == 1 = case i of
Optional → number' s neg z pos n
Required → number' s neg z pos n
<> sep
<> (printDigitIn s $! intToDigitIn s 1)
| otherwise = if n < 0
then neg <> nonPositive s n <> sep <> nonNegative s d
else pos <> nonNegative s n <> sep <> nonNegative s d
where r = toRational a
n = numerator r
d = denominator r
fraction ∷ (Real α, Printer p) ⇒ α → p
fraction = fraction' Decimal (char7 '-') (char7 '0')
mempty (char7 '/') Optional