{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE CPP #-}
module Fmt.Internal.Numeric where
import Data.CallStack
#if __GLASGOW_HASKELL__ < 804
import Data.Monoid ((<>))
#endif
import Numeric
import Data.Char
import Data.Text.Lazy.Builder hiding (fromString)
import Formatting.Buildable (Buildable(..))
import qualified Formatting.Internal.Raw as F
import qualified Data.Text.Lazy as TL
octF :: Integral a => a -> Builder
octF = baseF 8
binF :: Integral a => a -> Builder
binF = baseF 2
baseF :: (HasCallStack, Integral a) => Int -> a -> Builder
baseF numBase = build . atBase numBase
floatF :: Real a => a -> Builder
floatF a | d < 1e-6 || d >= 1e21 = build $ showEFloat Nothing d ""
| otherwise = build $ showFFloat Nothing d ""
where d = realToFrac a :: Double
exptF :: Real a => Int -> a -> Builder
exptF decs a = build $ showEFloat (Just decs) (realToFrac a :: Double) ""
fixedF :: Real a => Int -> a -> Builder
fixedF = F.fixed
commaizeF :: (Buildable a, Integral a) => a -> Builder
commaizeF = groupInt 3 ','
ordinalF :: (Buildable a, Integral a) => a -> Builder
ordinalF n
| tens > 3 && tens < 21 = build n <> "th"
| otherwise = build n <> case n `mod` 10 of
1 -> "st"
2 -> "nd"
3 -> "rd"
_ -> "th"
where
tens = n `mod` 100
groupInt :: (Buildable a, Integral a) => Int -> Char -> a -> Builder
groupInt 0 _ n = build n
groupInt i c n =
fromLazyText . TL.reverse .
foldr merge "" .
TL.zip (zeros <> cycle' zeros') .
TL.reverse .
toLazyText . build
$ n
where
zeros = TL.replicate (fromIntegral i) (TL.singleton '0')
zeros' = TL.singleton c <> TL.tail zeros
merge (f, c') rest
| f == c = TL.singleton c <> TL.singleton c' <> rest
| otherwise = TL.singleton c' <> rest
cycle' xs = xs <> cycle' xs
_ = toInteger n
atBase :: Integral a => Int -> a -> String
atBase b _ | b < 2 || b > 36 = error ("baseF: Invalid base " ++ show b)
atBase b n =
showSigned' (showIntAtBase (toInteger b) intToDigit') (toInteger n) ""
{-# INLINE atBase #-}
showSigned' :: Real a => (a -> ShowS) -> a -> ShowS
showSigned' f n
| n < 0 = showChar '-' . f (negate n)
| otherwise = f n
intToDigit' :: Int -> Char
intToDigit' i
| i >= 0 && i < 10 = chr (ord '0' + i)
| i >= 10 && i < 36 = chr (ord 'a' + i - 10)
| otherwise = error ("intToDigit': Invalid int " ++ show i)