{-# LANGUAGE RankNTypes #-}
-- |
-- Module      : Formatting.ShortFormatters
-- Copyright   : (c) 2013 Chris Done, 2013 Shachaf Ben-Kiki
-- License     : BSD3
-- Maintainer  : chrisdone@gmail.com
-- Stability   : experimental
-- Portability : GHC
--
-- Single letters for short formatting.

module Formatting.ShortFormatters
  ( t
  , d
  , b
  , o
  , x
  , st
  , s
  , sh
  , c
  , f
  , sf
  , l
  , r
  ) where

import           Formatting.Formatters (bin, int, oct)
import           Formatting.Internal

import qualified Data.Text as S
import qualified Data.Text as T
import qualified Data.Text.Format as T
import           Data.Text.Lazy (Text)
import qualified Data.Text.Lazy.Builder as T
import           Formatting.Buildable (Buildable)
import qualified Formatting.Buildable as B (build)

-- | Output a lazy text.
t :: Format r (Text -> r)
t :: Format r (Text -> r)
t = (Text -> Builder) -> Format r (Text -> r)
forall a r. (a -> Builder) -> Format r (a -> r)
later Text -> Builder
T.fromLazyText

-- | Render an integral e.g. 123 -> \"123\", 0 -> \"0\".
d :: Integral a => Format r (a -> r)
d :: Format r (a -> r)
d = Format r (a -> r)
forall a r. Integral a => Format r (a -> r)
int

-- | Render an integer using binary notation. (No leading 0b is
-- added.)
b :: Integral a => Format r (a -> r)
b :: Format r (a -> r)
b = Format r (a -> r)
forall a r. Integral a => Format r (a -> r)
bin

-- | Render an integer using octal notation. (No leading 0o is added.)
o :: Integral a => Format r (a -> r)
o :: Format r (a -> r)
o = Format r (a -> r)
forall a r. Integral a => Format r (a -> r)
oct

-- | Render an integer using hexadecimal notation. (No leading 0x is
-- added.)
x :: Integral a => Format r (a -> r)
x :: Format r (a -> r)
x = (a -> Builder) -> Format r (a -> r)
forall a r. (a -> Builder) -> Format r (a -> r)
later a -> Builder
forall a. Integral a => a -> Builder
T.hex

-- | Output a strict text.
st :: Format r (S.Text -> r)
st :: Format r (Text -> r)
st = (Text -> Builder) -> Format r (Text -> r)
forall a r. (a -> Builder) -> Format r (a -> r)
later Text -> Builder
T.fromText

-- | Output a string.
s :: Format r (String -> r)
s :: Format r (String -> r)
s = (String -> Builder) -> Format r (String -> r)
forall a r. (a -> Builder) -> Format r (a -> r)
later (Text -> Builder
T.fromText (Text -> Builder) -> (String -> Text) -> String -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack)

-- | Output a showable value (instance of 'Show') by turning it into
-- 'Text'.
sh :: Show a => Format r (a -> r)
sh :: Format r (a -> r)
sh = (a -> Builder) -> Format r (a -> r)
forall a r. (a -> Builder) -> Format r (a -> r)
later (Text -> Builder
T.fromText (Text -> Builder) -> (a -> Text) -> a -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack (String -> Text) -> (a -> String) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> String
forall a. Show a => a -> String
show)

-- | Output a character.
c :: Format r (Char -> r)
c :: Format r (Char -> r)
c = (Char -> Builder) -> Format r (Char -> r)
forall a r. (a -> Builder) -> Format r (a -> r)
later Char -> Builder
forall p. Buildable p => p -> Builder
B.build

-- | Render a floating point number using normal notation, with the
-- given number of decimal places.
f :: Real a => Int -> Format r (a -> r)
f :: Int -> Format r (a -> r)
f i :: Int
i = (a -> Builder) -> Format r (a -> r)
forall a r. (a -> Builder) -> Format r (a -> r)
later (Int -> a -> Builder
forall a. Real a => Int -> a -> Builder
T.fixed Int
i)

-- | Render a floating point number using the smallest number of
-- digits that correctly represent it.
sf :: Real a => Format r (a -> r)
sf :: Format r (a -> r)
sf = (a -> Builder) -> Format r (a -> r)
forall a r. (a -> Builder) -> Format r (a -> r)
later a -> Builder
forall a. Real a => a -> Builder
T.shortest

-- | Pad the left hand side of a string until it reaches @k@ characters
-- wide, if necessary filling with character @ch@.
l :: Buildable a => Int -> Char -> Format r (a -> r)
l :: Int -> Char -> Format r (a -> r)
l i :: Int
i ch :: Char
ch = (a -> Builder) -> Format r (a -> r)
forall a r. (a -> Builder) -> Format r (a -> r)
later (Int -> Char -> a -> Builder
forall a. Buildable a => Int -> Char -> a -> Builder
T.left Int
i Char
ch)

-- | Pad the right hand side of a string until it reaches @k@ characters
-- wide, if necessary filling with character @ch@.
r :: Buildable a => Int -> Char -> Format r (a -> r)
r :: Int -> Char -> Format r (a -> r)
r i :: Int
i ch :: Char
ch = (a -> Builder) -> Format r (a -> r)
forall a r. (a -> Builder) -> Format r (a -> r)
later (Int -> Char -> a -> Builder
forall a. Buildable a => Int -> Char -> a -> Builder
T.right Int
i Char
ch)