module Text.Builder
  ( Builder,

    -- * Accessors
    run,
    length,
    null,

    -- ** Output IO
    putToStdOut,
    putToStdErr,
    putLnToStdOut,
    putLnToStdErr,

    -- * Constructors

    -- ** Builder manipulators
    intercalate,
    padFromLeft,
    padFromRight,

    -- ** Textual
    text,
    lazyText,
    string,
    asciiByteString,
    hexData,

    -- ** Character
    char,

    -- *** Low-level character
    unicodeCodePoint,
    utf16CodeUnits1,
    utf16CodeUnits2,
    utf8CodeUnits1,
    utf8CodeUnits2,
    utf8CodeUnits3,
    utf8CodeUnits4,

    -- ** Integers

    -- *** Decimal
    decimal,
    unsignedDecimal,
    thousandSeparatedDecimal,
    thousandSeparatedUnsignedDecimal,
    dataSizeInBytesInDecimal,

    -- *** Binary
    unsignedBinary,
    unsignedPaddedBinary,

    -- *** Hexadecimal
    hexadecimal,
    unsignedHexadecimal,

    -- ** Digits
    decimalDigit,
    hexadecimalDigit,

    -- ** Real
    fixedDouble,
    doublePercent,

    -- ** Time
    intervalInSeconds,
  )
where

import qualified Data.Text.Lazy as TextLazy
import Text.Builder.Prelude hiding (intercalate, length, null)
import qualified TextBuilderDev as Dev

-- |
-- Specification of how to efficiently construct strict 'Text'.
-- Provides instances of 'Semigroup' and 'Monoid', which have complexity of /O(1)/.
newtype Builder
  = Builder Dev.TextBuilder
  deriving (Int -> Builder -> ShowS
[Builder] -> ShowS
Builder -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Builder] -> ShowS
$cshowList :: [Builder] -> ShowS
show :: Builder -> String
$cshow :: Builder -> String
showsPrec :: Int -> Builder -> ShowS
$cshowsPrec :: Int -> Builder -> ShowS
Show, String -> Builder
forall a. (String -> a) -> IsString a
fromString :: String -> Builder
$cfromString :: String -> Builder
IsString, NonEmpty Builder -> Builder
Builder -> Builder -> Builder
forall b. Integral b => b -> Builder -> Builder
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
stimes :: forall b. Integral b => b -> Builder -> Builder
$cstimes :: forall b. Integral b => b -> Builder -> Builder
sconcat :: NonEmpty Builder -> Builder
$csconcat :: NonEmpty Builder -> Builder
<> :: Builder -> Builder -> Builder
$c<> :: Builder -> Builder -> Builder
Semigroup, Semigroup Builder
Builder
[Builder] -> Builder
Builder -> Builder -> Builder
forall a.
Semigroup a -> a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
mconcat :: [Builder] -> Builder
$cmconcat :: [Builder] -> Builder
mappend :: Builder -> Builder -> Builder
$cmappend :: Builder -> Builder -> Builder
mempty :: Builder
$cmempty :: Builder
Monoid)

-- | Get the amount of characters
{-# INLINE length #-}
length :: Builder -> Int
length :: Builder -> Int
length = coerce :: forall a b. Coercible a b => a -> b
coerce TextBuilder -> Int
Dev.length

-- | Check whether the builder is empty
{-# INLINE null #-}
null :: Builder -> Bool
null :: Builder -> Bool
null = coerce :: forall a b. Coercible a b => a -> b
coerce TextBuilder -> Bool
Dev.null

-- | Execute a builder producing a strict text
run :: Builder -> Text
run :: Builder -> Text
run = coerce :: forall a b. Coercible a b => a -> b
coerce TextBuilder -> Text
Dev.buildText

-- ** Output IO

-- | Put builder, to stdout
putToStdOut :: Builder -> IO ()
putToStdOut :: Builder -> IO ()
putToStdOut = coerce :: forall a b. Coercible a b => a -> b
coerce TextBuilder -> IO ()
Dev.putToStdOut

-- | Put builder, to stderr
putToStdErr :: Builder -> IO ()
putToStdErr :: Builder -> IO ()
putToStdErr = coerce :: forall a b. Coercible a b => a -> b
coerce TextBuilder -> IO ()
Dev.putToStdErr

-- | Put builder, followed by a line, to stdout
putLnToStdOut :: Builder -> IO ()
putLnToStdOut :: Builder -> IO ()
putLnToStdOut = coerce :: forall a b. Coercible a b => a -> b
coerce TextBuilder -> IO ()
Dev.putLnToStdOut

-- | Put builder, followed by a line, to stderr
putLnToStdErr :: Builder -> IO ()
putLnToStdErr :: Builder -> IO ()
putLnToStdErr = coerce :: forall a b. Coercible a b => a -> b
coerce TextBuilder -> IO ()
Dev.putLnToStdErr

-- * Constructors

-- | Unicode character
{-# INLINE char #-}
char :: Char -> Builder
char :: Char -> Builder
char = coerce :: forall a b. Coercible a b => a -> b
coerce Char -> TextBuilder
Dev.char

-- | Unicode code point
{-# INLINE unicodeCodePoint #-}
unicodeCodePoint :: Int -> Builder
unicodeCodePoint :: Int -> Builder
unicodeCodePoint = coerce :: forall a b. Coercible a b => a -> b
coerce Int -> TextBuilder
Dev.unicodeCodePoint

-- | Single code-unit UTF-16 character
{-# INLINEABLE utf16CodeUnits1 #-}
utf16CodeUnits1 :: Word16 -> Builder
utf16CodeUnits1 :: Word16 -> Builder
utf16CodeUnits1 = coerce :: forall a b. Coercible a b => a -> b
coerce Word16 -> TextBuilder
Dev.utf16CodeUnits1

-- | Double code-unit UTF-16 character
{-# INLINEABLE utf16CodeUnits2 #-}
utf16CodeUnits2 :: Word16 -> Word16 -> Builder
utf16CodeUnits2 :: Word16 -> Word16 -> Builder
utf16CodeUnits2 = coerce :: forall a b. Coercible a b => a -> b
coerce Word16 -> Word16 -> TextBuilder
Dev.utf16CodeUnits2

-- | Single code-unit UTF-8 character
{-# INLINE utf8CodeUnits1 #-}
utf8CodeUnits1 :: Word8 -> Builder
utf8CodeUnits1 :: Word8 -> Builder
utf8CodeUnits1 = coerce :: forall a b. Coercible a b => a -> b
coerce Word8 -> TextBuilder
Dev.utf8CodeUnits1

-- | Double code-unit UTF-8 character
{-# INLINE utf8CodeUnits2 #-}
utf8CodeUnits2 :: Word8 -> Word8 -> Builder
utf8CodeUnits2 :: Word8 -> Word8 -> Builder
utf8CodeUnits2 = coerce :: forall a b. Coercible a b => a -> b
coerce Word8 -> Word8 -> TextBuilder
Dev.utf8CodeUnits2

-- | Triple code-unit UTF-8 character
{-# INLINE utf8CodeUnits3 #-}
utf8CodeUnits3 :: Word8 -> Word8 -> Word8 -> Builder
utf8CodeUnits3 :: Word8 -> Word8 -> Word8 -> Builder
utf8CodeUnits3 = coerce :: forall a b. Coercible a b => a -> b
coerce Word8 -> Word8 -> Word8 -> TextBuilder
Dev.utf8CodeUnits3

-- | UTF-8 character out of 4 code units
{-# INLINE utf8CodeUnits4 #-}
utf8CodeUnits4 :: Word8 -> Word8 -> Word8 -> Word8 -> Builder
utf8CodeUnits4 :: Word8 -> Word8 -> Word8 -> Word8 -> Builder
utf8CodeUnits4 = coerce :: forall a b. Coercible a b => a -> b
coerce Word8 -> Word8 -> Word8 -> Word8 -> TextBuilder
Dev.utf8CodeUnits4

-- | ASCII byte string
{-# INLINE asciiByteString #-}
asciiByteString :: ByteString -> Builder
asciiByteString :: ByteString -> Builder
asciiByteString = coerce :: forall a b. Coercible a b => a -> b
coerce ByteString -> TextBuilder
Dev.asciiByteString

-- | Strict text
{-# INLINE text #-}
text :: Text -> Builder
text :: Text -> Builder
text = coerce :: forall a b. Coercible a b => a -> b
coerce Text -> TextBuilder
Dev.text

-- | Lazy text
{-# INLINE lazyText #-}
lazyText :: TextLazy.Text -> Builder
lazyText :: Text -> Builder
lazyText = coerce :: forall a b. Coercible a b => a -> b
coerce Text -> TextBuilder
Dev.lazyText

-- | String
{-# INLINE string #-}
string :: String -> Builder
string :: String -> Builder
string = coerce :: forall a b. Coercible a b => a -> b
coerce String -> TextBuilder
Dev.string

-- | Decimal representation of an integral value
{-# INLINEABLE decimal #-}
decimal :: (Integral a) => a -> Builder
decimal :: forall a. Integral a => a -> Builder
decimal = coerce :: forall a b. Coercible a b => a -> b
coerce forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a. Integral a => a -> TextBuilder
Dev.decimal

-- | Decimal representation of an unsigned integral value
{-# INLINEABLE unsignedDecimal #-}
unsignedDecimal :: (Integral a) => a -> Builder
unsignedDecimal :: forall a. Integral a => a -> Builder
unsignedDecimal = coerce :: forall a b. Coercible a b => a -> b
coerce forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a. Integral a => a -> TextBuilder
Dev.unsignedDecimal

-- | Decimal representation of an integral value with thousands separated by the specified character
{-# INLINEABLE thousandSeparatedDecimal #-}
thousandSeparatedDecimal :: (Integral a) => Char -> a -> Builder
thousandSeparatedDecimal :: forall a. Integral a => Char -> a -> Builder
thousandSeparatedDecimal = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap coerce :: forall a b. Coercible a b => a -> b
coerce forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a. Integral a => Char -> a -> TextBuilder
Dev.thousandSeparatedDecimal

-- | Decimal representation of an unsigned integral value with thousands separated by the specified character
{-# INLINEABLE thousandSeparatedUnsignedDecimal #-}
thousandSeparatedUnsignedDecimal :: (Integral a) => Char -> a -> Builder
thousandSeparatedUnsignedDecimal :: forall a. Integral a => Char -> a -> Builder
thousandSeparatedUnsignedDecimal = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap coerce :: forall a b. Coercible a b => a -> b
coerce forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a. Integral a => Char -> a -> TextBuilder
Dev.thousandSeparatedUnsignedDecimal

-- | Data size in decimal notation over amount of bytes.
{-# INLINEABLE dataSizeInBytesInDecimal #-}
dataSizeInBytesInDecimal :: (Integral a) => Char -> a -> Builder
dataSizeInBytesInDecimal :: forall a. Integral a => Char -> a -> Builder
dataSizeInBytesInDecimal = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap coerce :: forall a b. Coercible a b => a -> b
coerce forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a. Integral a => Char -> a -> TextBuilder
Dev.dataSizeInBytesInDecimal

-- | Unsigned binary number
{-# INLINE unsignedBinary #-}
unsignedBinary :: (Integral a) => a -> Builder
unsignedBinary :: forall a. Integral a => a -> Builder
unsignedBinary = coerce :: forall a b. Coercible a b => a -> b
coerce forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a. Integral a => a -> TextBuilder
Dev.unsignedBinary

-- | Unsigned binary number
{-# INLINE unsignedPaddedBinary #-}
unsignedPaddedBinary :: (Integral a, FiniteBits a) => a -> Builder
unsignedPaddedBinary :: forall a. (Integral a, FiniteBits a) => a -> Builder
unsignedPaddedBinary = coerce :: forall a b. Coercible a b => a -> b
coerce forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a. (Integral a, FiniteBits a) => a -> TextBuilder
Dev.unsignedPaddedBinary

-- | Hexadecimal representation of an integral value
{-# INLINE hexadecimal #-}
hexadecimal :: (Integral a) => a -> Builder
hexadecimal :: forall a. Integral a => a -> Builder
hexadecimal = coerce :: forall a b. Coercible a b => a -> b
coerce forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a. Integral a => a -> TextBuilder
Dev.hexadecimal

-- | Unsigned hexadecimal representation of an integral value
{-# INLINE unsignedHexadecimal #-}
unsignedHexadecimal :: (Integral a) => a -> Builder
unsignedHexadecimal :: forall a. Integral a => a -> Builder
unsignedHexadecimal = coerce :: forall a b. Coercible a b => a -> b
coerce forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a. Integral a => a -> TextBuilder
Dev.unsignedHexadecimal

-- | Decimal digit
{-# INLINE decimalDigit #-}
decimalDigit :: (Integral a) => a -> Builder
decimalDigit :: forall a. Integral a => a -> Builder
decimalDigit = coerce :: forall a b. Coercible a b => a -> b
coerce forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a. Integral a => a -> TextBuilder
Dev.decimalDigit

-- | Hexadecimal digit
{-# INLINE hexadecimalDigit #-}
hexadecimalDigit :: (Integral a) => a -> Builder
hexadecimalDigit :: forall a. Integral a => a -> Builder
hexadecimalDigit = coerce :: forall a b. Coercible a b => a -> b
coerce forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a. Integral a => a -> TextBuilder
Dev.hexadecimalDigit

-- | Intercalate builders
{-# INLINE intercalate #-}
intercalate :: (Foldable foldable) => Builder -> foldable Builder -> Builder
intercalate :: forall (foldable :: * -> *).
Foldable foldable =>
Builder -> foldable Builder -> Builder
intercalate Builder
a foldable Builder
b = coerce :: forall a b. Coercible a b => a -> b
coerce (forall (f :: * -> *).
Foldable f =>
TextBuilder -> f TextBuilder -> TextBuilder
Dev.intercalate (coerce :: forall a b. Coercible a b => a -> b
coerce Builder
a) (forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ((:) forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. coerce :: forall a b. Coercible a b => a -> b
coerce) [] foldable Builder
b))

-- | Pad a builder from the left side to the specified length with the specified character
{-# INLINEABLE padFromLeft #-}
padFromLeft :: Int -> Char -> Builder -> Builder
padFromLeft :: Int -> Char -> Builder -> Builder
padFromLeft = coerce :: forall a b. Coercible a b => a -> b
coerce Int -> Char -> TextBuilder -> TextBuilder
Dev.padFromLeft

-- | Pad a builder from the right side to the specified length with the specified character
{-# INLINEABLE padFromRight #-}
padFromRight :: Int -> Char -> Builder -> Builder
padFromRight :: Int -> Char -> Builder -> Builder
padFromRight = coerce :: forall a b. Coercible a b => a -> b
coerce Int -> Char -> TextBuilder -> TextBuilder
Dev.padFromRight

-- |
-- Time interval in seconds.
-- Directly applicable to 'DiffTime' and 'NominalDiffTime'.
{-# INLINEABLE intervalInSeconds #-}
intervalInSeconds :: (RealFrac seconds) => seconds -> Builder
intervalInSeconds :: forall seconds. RealFrac seconds => seconds -> Builder
intervalInSeconds = coerce :: forall a b. Coercible a b => a -> b
coerce forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall seconds. RealFrac seconds => seconds -> TextBuilder
Dev.intervalInSeconds

-- | Double with a fixed number of decimal places.
{-# INLINE fixedDouble #-}
fixedDouble ::
  -- | Amount of decimals after point.
  Int ->
  Double ->
  Builder
fixedDouble :: Int -> Double -> Builder
fixedDouble = coerce :: forall a b. Coercible a b => a -> b
coerce Int -> Double -> TextBuilder
Dev.fixedDouble

-- | Double multiplied by 100 with a fixed number of decimal places applied and followed by a percent-sign.
{-# INLINE doublePercent #-}
doublePercent ::
  -- | Amount of decimals after point.
  Int ->
  Double ->
  Builder
doublePercent :: Int -> Double -> Builder
doublePercent = coerce :: forall a b. Coercible a b => a -> b
coerce Int -> Double -> TextBuilder
Dev.doublePercent

-- | Hexadecimal readable representation of binary data.
{-# INLINE hexData #-}
hexData :: ByteString -> Builder
hexData :: ByteString -> Builder
hexData = coerce :: forall a b. Coercible a b => a -> b
coerce ByteString -> TextBuilder
Dev.hexData