{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE CPP #-}
module Formatting.Formatters
(
text,
stext,
string,
shown,
char,
builder,
fconst,
int,
float,
fixed,
sci,
scifmt,
shortest,
groupInt,
commas,
ords,
plural,
asInt,
left,
right,
center,
fitLeft,
fitRight,
base,
bin,
oct,
hex,
prefixBin,
prefixOct,
prefixHex,
bytes,
build,
Buildable,
) where
import Formatting.Internal
import Data.Char (chr, ord)
#if !(MIN_VERSION_base(4,11,0))
import Data.Monoid ((<>))
#endif
import Data.Scientific
import qualified Data.Text as S
import qualified Data.Text as T
import Formatting.Buildable (Buildable)
import qualified Formatting.Buildable as B (build)
import qualified Data.Text.Format as T
import Data.Text.Lazy (Text)
import qualified Data.Text.Lazy as LT
import Data.Text.Lazy.Builder (Builder)
import qualified Data.Text.Lazy.Builder as T
import Data.Text.Lazy.Builder.Scientific
import Numeric (showIntAtBase)
text :: Format r (Text -> r)
text = later T.fromLazyText
stext :: Format r (S.Text -> r)
stext = later T.fromText
string :: Format r (String -> r)
string = later (T.fromText . T.pack)
shown :: Show a => Format r (a -> r)
shown = later (T.fromText . T.pack . show)
char :: Format r (Char -> r)
char = later B.build
builder :: Format r (Builder -> r)
builder = later id
fconst :: Builder -> Format r (a -> r)
fconst m = later (const m)
build :: Buildable a => Format r (a -> r)
build = later B.build
int :: Integral a => Format r (a -> r)
int = base 10
float :: Real a => Format r (a -> r)
float = later T.shortest
fixed :: Real a => Int -> Format r (a -> r)
fixed i = later (T.fixed i)
shortest :: Real a => Format r (a -> r)
shortest = later T.shortest
sci :: Format r (Scientific -> r)
sci = later scientificBuilder
scifmt :: FPFormat -> Maybe Int -> Format r (Scientific -> r)
scifmt f i = later (formatScientificBuilder f i)
asInt :: Enum a => Format r (a -> r)
asInt = later (T.shortest . fromEnum)
left :: Buildable a => Int -> Char -> Format r (a -> r)
left i c = later (T.left i c)
right :: Buildable a => Int -> Char -> Format r (a -> r)
right i c = later (T.right i c)
center :: Buildable a => Int -> Char -> Format r (a -> r)
center i c = later centerT where
centerT = T.fromLazyText . LT.center (fromIntegral i) c . T.toLazyText . B.build
groupInt :: (Buildable n,Integral n) => Int -> Char -> Format r (n -> r)
groupInt 0 _ = later B.build
groupInt i c =
later
(\n ->
if n < 0
then "-" <> commaize (negate n)
else commaize n)
where
commaize =
T.fromLazyText .
LT.reverse .
foldr merge "" .
LT.zip (zeros <> cycle' zeros') . LT.reverse . T.toLazyText . B.build
zeros = LT.replicate (fromIntegral i) (LT.singleton '0')
zeros' = LT.singleton c <> LT.tail zeros
merge (f, c') rest
| f == c = LT.singleton c <> LT.singleton c' <> rest
| otherwise = LT.singleton c' <> rest
cycle' xs = xs <> cycle' xs
fitLeft :: Buildable a => Int -> Format r (a -> r)
fitLeft size = later (fit (fromIntegral size)) where
fit i = T.fromLazyText . LT.take i . T.toLazyText . B.build
fitRight :: Buildable a => Int -> Format r (a -> r)
fitRight size = later (fit (fromIntegral size)) where
fit i = T.fromLazyText .
(\t -> LT.drop (LT.length t - i) t)
. T.toLazyText
. B.build
commas :: (Buildable n,Integral n) => Format r (n -> r)
commas = groupInt 3 ','
ords :: Integral n => Format r (n -> r)
ords = later go
where go n
| tens > 3 && tens < 21 = T.fixed 0 n <> "th"
| otherwise =
T.fixed 0 n <>
case n `mod` 10 of
1 -> "st"
2 -> "nd"
3 -> "rd"
_ -> "th"
where tens = n `mod` 100
plural :: (Num a, Eq a) => Text -> Text -> Format r (a -> r)
plural s p = later (\i -> if i == 1 then B.build s else B.build p)
base :: Integral a => Int -> Format r (a -> r)
base numBase = later (B.build . atBase numBase)
bin :: Integral a => Format r (a -> r)
bin = base 2
{-# INLINE bin #-}
oct :: Integral a => Format r (a -> r)
oct = base 8
{-# INLINE oct #-}
hex :: Integral a => Format r (a -> r)
hex = later T.hex
{-# INLINE hex #-}
prefixBin :: Integral a => Format r (a -> r)
prefixBin = "0b" % bin
{-# INLINE prefixBin #-}
prefixOct :: Integral a => Format r (a -> r)
prefixOct = "0o" % oct
{-# INLINE prefixOct #-}
prefixHex :: Integral a => Format r (a -> r)
prefixHex = "0x" % hex
{-# INLINE prefixHex #-}
atBase :: Integral a => Int -> a -> String
atBase b _ | b < 2 || b > 36 = error ("base: 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)
bytes :: (Ord f,Integral a,Fractional f)
=> Format Builder (f -> Builder)
-> Format r (a -> r)
bytes d = later go
where go bs =
bprint d (fromIntegral (signum bs) * dec) <> bytesSuffixes !!
i
where (dec,i) = getSuffix (abs bs)
getSuffix n =
until p
(\(x,y) -> (x / 1024,y + 1))
(fromIntegral n,0)
where p (n',numDivs) =
n' < 1024 || numDivs == (length bytesSuffixes - 1)
bytesSuffixes =
["B","KB","MB","GB","TB","PB","EB","ZB","YB"]