{-# LANGUAGE CPP #-}
module TextBuilderDev
( TextBuilder,
toText,
buildText,
length,
null,
putToStdOut,
putToStdErr,
putLnToStdOut,
putLnToStdErr,
force,
intercalate,
intercalateMap,
padFromLeft,
padFromRight,
text,
lazyText,
string,
asciiByteString,
hexData,
char,
unicodeCodePoint,
utf16CodeUnits1,
utf16CodeUnits2,
utf8CodeUnits1,
utf8CodeUnits2,
utf8CodeUnits3,
utf8CodeUnits4,
decimal,
unsignedDecimal,
fixedUnsignedDecimal,
thousandSeparatedDecimal,
thousandSeparatedUnsignedDecimal,
dataSizeInBytesInDecimal,
unsignedBinary,
unsignedPaddedBinary,
finiteBitsUnsignedBinary,
hexadecimal,
unsignedHexadecimal,
decimalDigit,
hexadecimalDigit,
fixedDouble,
doublePercent,
utcTimeInIso8601,
utcTimestampInIso8601,
intervalInSeconds,
diffTimeCompact,
picosecondsCompact,
IsomorphicToTextBuilder (..),
)
where
import qualified Data.ByteString as ByteString
import qualified Data.List.Split as Split
import qualified Data.Text as Text
import qualified Data.Text.IO as Text
import qualified Data.Text.Lazy as TextLazy
import qualified Data.Text.Lazy.Builder as TextLazyBuilder
import qualified DeferredFolds.Unfoldr as Unfoldr
import qualified IsomorphismClass
import qualified LawfulConversions
import qualified Test.QuickCheck.Gen as QcGen
import qualified TextBuilderDev.Allocator as Allocator
import TextBuilderDev.Prelude hiding (intercalate, length, null)
#if MIN_VERSION_text(2,0,2)
import qualified Data.Text.Encoding as TextEncoding
#endif
class IsomorphicToTextBuilder a where
toTextBuilder :: a -> TextBuilder
fromTextBuilder :: TextBuilder -> a
instance IsomorphicToTextBuilder TextBuilder where
toTextBuilder :: TextBuilder -> TextBuilder
toTextBuilder = TextBuilder -> TextBuilder
forall a. a -> a
forall {k} (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
fromTextBuilder :: TextBuilder -> TextBuilder
fromTextBuilder = TextBuilder -> TextBuilder
forall a. a -> a
forall {k} (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
data TextBuilder
= TextBuilder
{-# UNPACK #-} !Allocator.Allocator
{-# UNPACK #-} !Int
instance Semigroup TextBuilder where
<> :: TextBuilder -> TextBuilder -> TextBuilder
(<>) (TextBuilder Allocator
allocator1 Int
sizeInChars1) (TextBuilder Allocator
allocator2 Int
sizeInChars2) =
Allocator -> Int -> TextBuilder
TextBuilder
(Allocator
allocator1 Allocator -> Allocator -> Allocator
forall a. Semigroup a => a -> a -> a
<> Allocator
allocator2)
(Int
sizeInChars1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
sizeInChars2)
stimes :: forall b. Integral b => b -> TextBuilder -> TextBuilder
stimes b
n (TextBuilder Allocator
allocator Int
size) =
Allocator -> Int -> TextBuilder
TextBuilder (b -> Allocator -> Allocator
forall b. Integral b => b -> Allocator -> Allocator
forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes b
n Allocator
allocator) (Int
size Int -> Int -> Int
forall a. Num a => a -> a -> a
* b -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral b
n)
instance Monoid TextBuilder where
{-# INLINE mempty #-}
mempty :: TextBuilder
mempty = Allocator -> Int -> TextBuilder
TextBuilder Allocator
forall a. Monoid a => a
mempty Int
0
instance IsString TextBuilder where
fromString :: String -> TextBuilder
fromString = String -> TextBuilder
string
instance Show TextBuilder where
show :: TextBuilder -> String
show = Text -> String
Text.unpack (Text -> String) -> (TextBuilder -> Text) -> TextBuilder -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. TextBuilder -> Text
toText
instance Eq TextBuilder where
== :: TextBuilder -> TextBuilder -> Bool
(==) = (Text -> Text -> Bool)
-> (TextBuilder -> Text) -> TextBuilder -> TextBuilder -> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
on Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
(==) TextBuilder -> Text
toText
instance Arbitrary TextBuilder where
arbitrary :: Gen TextBuilder
arbitrary =
[Gen TextBuilder] -> Gen TextBuilder
forall a. HasCallStack => [Gen a] -> Gen a
QcGen.oneof
[ (Int -> Int) -> Gen TextBuilder -> Gen TextBuilder
forall a. (Int -> Int) -> Gen a -> Gen a
QcGen.scale ((Int -> Int -> Int) -> Int -> Int -> Int
forall a b c. (a -> b -> c) -> b -> a -> c
flip Int -> Int -> Int
forall a. Integral a => a -> a -> a
div Int
2)
(Gen TextBuilder -> Gen TextBuilder)
-> Gen TextBuilder -> Gen TextBuilder
forall a b. (a -> b) -> a -> b
$ [Gen TextBuilder] -> Gen TextBuilder
forall a. HasCallStack => [Gen a] -> Gen a
QcGen.oneof
[ TextBuilder -> TextBuilder -> TextBuilder
forall a. Semigroup a => a -> a -> a
(<>) (TextBuilder -> TextBuilder -> TextBuilder)
-> Gen TextBuilder -> Gen (TextBuilder -> TextBuilder)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen TextBuilder
forall a. Arbitrary a => Gen a
arbitrary Gen (TextBuilder -> TextBuilder)
-> Gen TextBuilder -> Gen TextBuilder
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen TextBuilder
forall a. Arbitrary a => Gen a
arbitrary,
NonEmpty TextBuilder -> TextBuilder
forall a. Semigroup a => NonEmpty a -> a
sconcat (NonEmpty TextBuilder -> TextBuilder)
-> Gen (NonEmpty TextBuilder) -> Gen TextBuilder
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen (NonEmpty TextBuilder)
forall a. Arbitrary a => Gen a
arbitrary,
Word8 -> TextBuilder -> TextBuilder
forall b. Integral b => b -> TextBuilder -> TextBuilder
forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes (Word8 -> TextBuilder -> TextBuilder)
-> Gen Word8 -> Gen (TextBuilder -> TextBuilder)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary @Word8 Gen (TextBuilder -> TextBuilder)
-> Gen TextBuilder -> Gen TextBuilder
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen TextBuilder
forall a. Arbitrary a => Gen a
arbitrary,
TextBuilder -> Gen TextBuilder
forall a. a -> Gen a
forall (f :: * -> *) a. Applicative f => a -> f a
pure TextBuilder
forall a. Monoid a => a
mempty,
[TextBuilder] -> TextBuilder
forall a. Monoid a => [a] -> a
mconcat ([TextBuilder] -> TextBuilder)
-> Gen [TextBuilder] -> Gen TextBuilder
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen [TextBuilder]
forall a. Arbitrary a => Gen a
arbitrary
],
Text -> TextBuilder
text (Text -> TextBuilder) -> Gen Text -> Gen TextBuilder
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Text
forall a. Arbitrary a => Gen a
arbitrary,
Text -> TextBuilder
lazyText (Text -> TextBuilder) -> Gen Text -> Gen TextBuilder
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Text
forall a. Arbitrary a => Gen a
arbitrary,
String -> TextBuilder
string (String -> TextBuilder) -> Gen String -> Gen TextBuilder
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen String
forall a. Arbitrary a => Gen a
arbitrary,
ByteString -> TextBuilder
asciiByteString (ByteString -> TextBuilder)
-> (ByteString -> ByteString) -> ByteString -> TextBuilder
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Word8 -> Bool) -> ByteString -> ByteString
ByteString.filter (Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
< Word8
128) (ByteString -> TextBuilder) -> Gen ByteString -> Gen TextBuilder
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen ByteString
forall a. Arbitrary a => Gen a
arbitrary,
ByteString -> TextBuilder
hexData (ByteString -> TextBuilder) -> Gen ByteString -> Gen TextBuilder
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen ByteString
forall a. Arbitrary a => Gen a
arbitrary,
Char -> TextBuilder
char (Char -> TextBuilder) -> Gen Char -> Gen TextBuilder
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Char
forall a. Arbitrary a => Gen a
arbitrary,
forall a. Integral a => a -> TextBuilder
decimal @Integer (Year -> TextBuilder) -> Gen Year -> Gen TextBuilder
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Year
forall a. Arbitrary a => Gen a
arbitrary,
forall a. Integral a => a -> TextBuilder
unsignedDecimal @Natural (Natural -> TextBuilder) -> Gen Natural -> Gen TextBuilder
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Natural
forall a. Arbitrary a => Gen a
arbitrary,
forall a. Integral a => Char -> a -> TextBuilder
thousandSeparatedDecimal @Integer (Char -> Year -> TextBuilder)
-> Gen Char -> Gen (Year -> TextBuilder)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Char
forall a. Arbitrary a => Gen a
arbitrary Gen (Year -> TextBuilder) -> Gen Year -> Gen TextBuilder
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Year
forall a. Arbitrary a => Gen a
arbitrary,
forall a. Integral a => Char -> a -> TextBuilder
thousandSeparatedUnsignedDecimal @Natural (Char -> Natural -> TextBuilder)
-> Gen Char -> Gen (Natural -> TextBuilder)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Char
forall a. Arbitrary a => Gen a
arbitrary Gen (Natural -> TextBuilder) -> Gen Natural -> Gen TextBuilder
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Natural
forall a. Arbitrary a => Gen a
arbitrary,
forall a. Integral a => Char -> a -> TextBuilder
dataSizeInBytesInDecimal @Natural (Char -> Natural -> TextBuilder)
-> Gen Char -> Gen (Natural -> TextBuilder)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Char
forall a. Arbitrary a => Gen a
arbitrary Gen (Natural -> TextBuilder) -> Gen Natural -> Gen TextBuilder
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Natural
forall a. Arbitrary a => Gen a
arbitrary,
forall a. Integral a => a -> TextBuilder
unsignedBinary @Natural (Natural -> TextBuilder) -> Gen Natural -> Gen TextBuilder
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Natural
forall a. Arbitrary a => Gen a
arbitrary,
forall a. (Integral a, FiniteBits a) => a -> TextBuilder
unsignedPaddedBinary @Word (Word -> TextBuilder) -> Gen Word -> Gen TextBuilder
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Word
forall a. Arbitrary a => Gen a
arbitrary,
forall a. FiniteBits a => a -> TextBuilder
finiteBitsUnsignedBinary @Word (Word -> TextBuilder) -> Gen Word -> Gen TextBuilder
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Word
forall a. Arbitrary a => Gen a
arbitrary,
forall a. Integral a => a -> TextBuilder
hexadecimal @Integer (Year -> TextBuilder) -> Gen Year -> Gen TextBuilder
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Year
forall a. Arbitrary a => Gen a
arbitrary,
forall a. Integral a => a -> TextBuilder
unsignedHexadecimal @Natural (Natural -> TextBuilder) -> Gen Natural -> Gen TextBuilder
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Natural
forall a. Arbitrary a => Gen a
arbitrary,
Int -> TextBuilder
forall a. Integral a => a -> TextBuilder
decimalDigit (Int -> TextBuilder) -> Gen Int -> Gen TextBuilder
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Random a => (a, a) -> Gen a
QcGen.choose @Int (Int
0, Int
9),
Int -> TextBuilder
forall a. Integral a => a -> TextBuilder
hexadecimalDigit (Int -> TextBuilder) -> Gen Int -> Gen TextBuilder
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Random a => (a, a) -> Gen a
QcGen.choose @Int (Int
0, Int
15),
Int -> Double -> TextBuilder
fixedDouble (Int -> Double -> TextBuilder)
-> Gen Int -> Gen (Double -> TextBuilder)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Int, Int) -> Gen Int
forall a. Random a => (a, a) -> Gen a
QcGen.choose (Int
0, Int
19) Gen (Double -> TextBuilder) -> Gen Double -> Gen TextBuilder
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Double
forall a. Arbitrary a => Gen a
arbitrary,
Int -> Double -> TextBuilder
doublePercent (Int -> Double -> TextBuilder)
-> Gen Int -> Gen (Double -> TextBuilder)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Int, Int) -> Gen Int
forall a. Random a => (a, a) -> Gen a
QcGen.choose (Int
0, Int
19) Gen (Double -> TextBuilder) -> Gen Double -> Gen TextBuilder
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Double
forall a. Arbitrary a => Gen a
arbitrary,
Int -> Int -> Int -> Int -> Int -> Int -> TextBuilder
utcTimestampInIso8601 (Int -> Int -> Int -> Int -> Int -> Int -> TextBuilder)
-> Gen Int -> Gen (Int -> Int -> Int -> Int -> Int -> TextBuilder)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Int
forall a. Arbitrary a => Gen a
arbitrary Gen (Int -> Int -> Int -> Int -> Int -> TextBuilder)
-> Gen Int -> Gen (Int -> Int -> Int -> Int -> TextBuilder)
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Int
forall a. Arbitrary a => Gen a
arbitrary Gen (Int -> Int -> Int -> Int -> TextBuilder)
-> Gen Int -> Gen (Int -> Int -> Int -> TextBuilder)
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Int
forall a. Arbitrary a => Gen a
arbitrary Gen (Int -> Int -> Int -> TextBuilder)
-> Gen Int -> Gen (Int -> Int -> TextBuilder)
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Int
forall a. Arbitrary a => Gen a
arbitrary Gen (Int -> Int -> TextBuilder)
-> Gen Int -> Gen (Int -> TextBuilder)
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Int
forall a. Arbitrary a => Gen a
arbitrary Gen (Int -> TextBuilder) -> Gen Int -> Gen TextBuilder
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Int
forall a. Arbitrary a => Gen a
arbitrary,
forall seconds. RealFrac seconds => seconds -> TextBuilder
intervalInSeconds @Double (Double -> TextBuilder) -> Gen Double -> Gen TextBuilder
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Double
forall a. Arbitrary a => Gen a
arbitrary
]
instance IsomorphicToTextBuilder Text where
toTextBuilder :: Text -> TextBuilder
toTextBuilder = Text -> TextBuilder
text
fromTextBuilder :: TextBuilder -> Text
fromTextBuilder = TextBuilder -> Text
toText
instance IsomorphismClass.IsomorphicTo TextBuilder Text where
to :: Text -> TextBuilder
to = Text -> TextBuilder
TextBuilderDev.text
instance IsomorphismClass.IsomorphicTo Text TextBuilder where
to :: TextBuilder -> Text
to = TextBuilder -> Text
TextBuilderDev.toText
instance LawfulConversions.IsSome TextBuilder Text where
to :: Text -> TextBuilder
to = Text -> TextBuilder
TextBuilderDev.text
instance LawfulConversions.IsSome Text TextBuilder where
to :: TextBuilder -> Text
to = TextBuilder -> Text
TextBuilderDev.toText
instance LawfulConversions.IsMany TextBuilder Text
instance LawfulConversions.IsMany Text TextBuilder
instance LawfulConversions.Is TextBuilder Text
instance LawfulConversions.Is Text TextBuilder
instance IsomorphicToTextBuilder String where
toTextBuilder :: String -> TextBuilder
toTextBuilder = String -> TextBuilder
forall a. IsString a => String -> a
fromString
fromTextBuilder :: TextBuilder -> String
fromTextBuilder = Text -> String
Text.unpack (Text -> String) -> (TextBuilder -> Text) -> TextBuilder -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. TextBuilder -> Text
toText
instance LawfulConversions.IsSome String TextBuilder where
to :: TextBuilder -> String
to = Text -> String
Text.unpack (Text -> String) -> (TextBuilder -> Text) -> TextBuilder -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. TextBuilder -> Text
toText
maybeFrom :: String -> Maybe TextBuilder
maybeFrom = (Text -> TextBuilder) -> Maybe Text -> Maybe TextBuilder
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> TextBuilder
text (Maybe Text -> Maybe TextBuilder)
-> (String -> Maybe Text) -> String -> Maybe TextBuilder
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. String -> Maybe Text
forall a b. IsSome a b => a -> Maybe b
LawfulConversions.maybeFrom
instance LawfulConversions.IsMany String TextBuilder where
from :: String -> TextBuilder
from = Text -> TextBuilder
text (Text -> TextBuilder) -> (String -> Text) -> String -> TextBuilder
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. String -> Text
forall a b. IsMany a b => a -> b
LawfulConversions.from
instance IsomorphicToTextBuilder TextLazy.Text where
toTextBuilder :: Text -> TextBuilder
toTextBuilder = Text -> TextBuilder
lazyText
fromTextBuilder :: TextBuilder -> Text
fromTextBuilder = Text -> Text
TextLazy.fromStrict (Text -> Text) -> (TextBuilder -> Text) -> TextBuilder -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. TextBuilder -> Text
toText
instance IsomorphismClass.IsomorphicTo TextBuilder TextLazy.Text where
to :: Text -> TextBuilder
to = Text -> TextBuilder
TextBuilderDev.lazyText
instance IsomorphismClass.IsomorphicTo TextLazy.Text TextBuilder where
to :: TextBuilder -> Text
to = Text -> Text
forall a b. IsomorphicTo a b => b -> a
IsomorphismClass.to (Text -> Text) -> (TextBuilder -> Text) -> TextBuilder -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a b. IsomorphicTo a b => b -> a
IsomorphismClass.to @Text
instance LawfulConversions.IsSome TextBuilder TextLazy.Text where
to :: Text -> TextBuilder
to = Text -> TextBuilder
lazyText
instance LawfulConversions.IsSome TextLazy.Text TextBuilder where
to :: TextBuilder -> Text
to = Text -> Text
TextLazy.fromStrict (Text -> Text) -> (TextBuilder -> Text) -> TextBuilder -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. TextBuilder -> Text
toText
instance LawfulConversions.IsMany TextBuilder TextLazy.Text
instance LawfulConversions.IsMany TextLazy.Text TextBuilder
instance LawfulConversions.Is TextBuilder TextLazy.Text
instance LawfulConversions.Is TextLazy.Text TextBuilder
instance IsomorphicToTextBuilder TextLazyBuilder.Builder where
toTextBuilder :: Builder -> TextBuilder
toTextBuilder = Text -> TextBuilder
text (Text -> TextBuilder)
-> (Builder -> Text) -> Builder -> TextBuilder
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Text -> Text
TextLazy.toStrict (Text -> Text) -> (Builder -> Text) -> Builder -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Builder -> Text
TextLazyBuilder.toLazyText
fromTextBuilder :: TextBuilder -> Builder
fromTextBuilder = Text -> Builder
TextLazyBuilder.fromText (Text -> Builder)
-> (TextBuilder -> Text) -> TextBuilder -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. TextBuilder -> Text
toText
instance IsomorphismClass.IsomorphicTo TextBuilder TextLazyBuilder.Builder where
to :: Builder -> TextBuilder
to = Text -> TextBuilder
forall a b. IsomorphicTo a b => b -> a
IsomorphismClass.to (Text -> TextBuilder)
-> (Builder -> Text) -> Builder -> TextBuilder
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a b. IsomorphicTo a b => b -> a
IsomorphismClass.to @TextLazy.Text
instance IsomorphismClass.IsomorphicTo TextLazyBuilder.Builder TextBuilder where
to :: TextBuilder -> Builder
to = Text -> Builder
forall a b. IsomorphicTo a b => b -> a
IsomorphismClass.to (Text -> Builder)
-> (TextBuilder -> Text) -> TextBuilder -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a b. IsomorphicTo a b => b -> a
IsomorphismClass.to @Text
instance LawfulConversions.IsSome TextBuilder TextLazyBuilder.Builder where
to :: Builder -> TextBuilder
to = Text -> TextBuilder
text (Text -> TextBuilder)
-> (Builder -> Text) -> Builder -> TextBuilder
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Text -> Text
TextLazy.toStrict (Text -> Text) -> (Builder -> Text) -> Builder -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Builder -> Text
TextLazyBuilder.toLazyText
instance LawfulConversions.IsSome TextLazyBuilder.Builder TextBuilder where
to :: TextBuilder -> Builder
to = Text -> Builder
TextLazyBuilder.fromText (Text -> Builder)
-> (TextBuilder -> Text) -> TextBuilder -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. TextBuilder -> Text
toText
instance LawfulConversions.IsMany TextBuilder TextLazyBuilder.Builder
instance LawfulConversions.IsMany TextLazyBuilder.Builder TextBuilder
instance LawfulConversions.Is TextBuilder TextLazyBuilder.Builder
instance LawfulConversions.Is TextLazyBuilder.Builder TextBuilder
#if MIN_VERSION_text(2,1,2)
instance IsomorphicToTextBuilder TextEncoding.StrictTextBuilder where
toTextBuilder = toTextBuilder . TextEncoding.strictBuilderToText
fromTextBuilder = TextEncoding.textToStrictBuilder . fromTextBuilder
instance IsomorphismClass.IsomorphicTo TextBuilder TextEncoding.StrictTextBuilder where
to = IsomorphismClass.to . TextEncoding.strictBuilderToText
instance IsomorphismClass.IsomorphicTo TextEncoding.StrictTextBuilder TextBuilder where
to = TextEncoding.textToStrictBuilder . IsomorphismClass.to
instance LawfulConversions.IsSome TextBuilder TextEncoding.StrictTextBuilder where
to = toTextBuilder . TextEncoding.strictBuilderToText
instance LawfulConversions.IsSome TextEncoding.StrictTextBuilder TextBuilder where
to = TextEncoding.textToStrictBuilder . fromTextBuilder
instance LawfulConversions.IsMany TextBuilder TextEncoding.StrictTextBuilder
instance LawfulConversions.IsMany TextEncoding.StrictTextBuilder TextBuilder
instance LawfulConversions.Is TextBuilder TextEncoding.StrictTextBuilder
instance LawfulConversions.Is TextEncoding.StrictTextBuilder TextBuilder
#elif MIN_VERSION_text(2,0,2)
instance IsomorphicToTextBuilder TextEncoding.StrictBuilder where
toTextBuilder :: StrictBuilder -> TextBuilder
toTextBuilder = Text -> TextBuilder
forall a. IsomorphicToTextBuilder a => a -> TextBuilder
toTextBuilder (Text -> TextBuilder)
-> (StrictBuilder -> Text) -> StrictBuilder -> TextBuilder
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. StrictBuilder -> Text
TextEncoding.strictBuilderToText
fromTextBuilder :: TextBuilder -> StrictBuilder
fromTextBuilder = Text -> StrictBuilder
TextEncoding.textToStrictBuilder (Text -> StrictBuilder)
-> (TextBuilder -> Text) -> TextBuilder -> StrictBuilder
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. TextBuilder -> Text
forall a. IsomorphicToTextBuilder a => TextBuilder -> a
fromTextBuilder
instance IsomorphismClass.IsomorphicTo TextBuilder TextEncoding.StrictBuilder where
to :: StrictBuilder -> TextBuilder
to = Text -> TextBuilder
forall a b. IsomorphicTo a b => b -> a
IsomorphismClass.to (Text -> TextBuilder)
-> (StrictBuilder -> Text) -> StrictBuilder -> TextBuilder
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. StrictBuilder -> Text
TextEncoding.strictBuilderToText
instance IsomorphismClass.IsomorphicTo TextEncoding.StrictBuilder TextBuilder where
to :: TextBuilder -> StrictBuilder
to = Text -> StrictBuilder
TextEncoding.textToStrictBuilder (Text -> StrictBuilder)
-> (TextBuilder -> Text) -> TextBuilder -> StrictBuilder
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. TextBuilder -> Text
forall a b. IsomorphicTo a b => b -> a
IsomorphismClass.to
instance LawfulConversions.IsSome TextBuilder TextEncoding.StrictBuilder where
to :: StrictBuilder -> TextBuilder
to = Text -> TextBuilder
forall a. IsomorphicToTextBuilder a => a -> TextBuilder
toTextBuilder (Text -> TextBuilder)
-> (StrictBuilder -> Text) -> StrictBuilder -> TextBuilder
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. StrictBuilder -> Text
TextEncoding.strictBuilderToText
instance LawfulConversions.IsSome TextEncoding.StrictBuilder TextBuilder where
to :: TextBuilder -> StrictBuilder
to = Text -> StrictBuilder
TextEncoding.textToStrictBuilder (Text -> StrictBuilder)
-> (TextBuilder -> Text) -> TextBuilder -> StrictBuilder
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. TextBuilder -> Text
forall a. IsomorphicToTextBuilder a => TextBuilder -> a
fromTextBuilder
instance LawfulConversions.IsMany TextBuilder TextEncoding.StrictBuilder
instance LawfulConversions.IsMany TextEncoding.StrictBuilder TextBuilder
instance LawfulConversions.Is TextBuilder TextEncoding.StrictBuilder
instance LawfulConversions.Is TextEncoding.StrictBuilder TextBuilder
#endif
{-# INLINE length #-}
length :: TextBuilder -> Int
length :: TextBuilder -> Int
length (TextBuilder Allocator
_ Int
x) = Int
x
{-# INLINE null #-}
null :: TextBuilder -> Bool
null :: TextBuilder -> Bool
null = (Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0) (Int -> Bool) -> (TextBuilder -> Int) -> TextBuilder -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. TextBuilder -> Int
length
toText :: TextBuilder -> Text
toText :: TextBuilder -> Text
toText (TextBuilder Allocator
allocator Int
_) =
Allocator -> Text
Allocator.allocate Allocator
allocator
{-# DEPRECATED buildText "Use toText instead" #-}
buildText :: TextBuilder -> Text
buildText :: TextBuilder -> Text
buildText = TextBuilder -> Text
toText
putToStdOut :: TextBuilder -> IO ()
putToStdOut :: TextBuilder -> IO ()
putToStdOut = Handle -> Text -> IO ()
Text.hPutStr Handle
stdout (Text -> IO ()) -> (TextBuilder -> Text) -> TextBuilder -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. TextBuilder -> Text
toText
putToStdErr :: TextBuilder -> IO ()
putToStdErr :: TextBuilder -> IO ()
putToStdErr = Handle -> Text -> IO ()
Text.hPutStr Handle
stderr (Text -> IO ()) -> (TextBuilder -> Text) -> TextBuilder -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. TextBuilder -> Text
toText
putLnToStdOut :: TextBuilder -> IO ()
putLnToStdOut :: TextBuilder -> IO ()
putLnToStdOut = Handle -> Text -> IO ()
Text.hPutStrLn Handle
stdout (Text -> IO ()) -> (TextBuilder -> Text) -> TextBuilder -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. TextBuilder -> Text
toText
putLnToStdErr :: TextBuilder -> IO ()
putLnToStdErr :: TextBuilder -> IO ()
putLnToStdErr = Handle -> Text -> IO ()
Text.hPutStrLn Handle
stderr (Text -> IO ()) -> (TextBuilder -> Text) -> TextBuilder -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. TextBuilder -> Text
toText
{-# INLINE force #-}
force :: TextBuilder -> TextBuilder
force :: TextBuilder -> TextBuilder
force = Text -> TextBuilder
text (Text -> TextBuilder)
-> (TextBuilder -> Text) -> TextBuilder -> TextBuilder
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. TextBuilder -> Text
toText
{-# INLINE char #-}
char :: Char -> TextBuilder
char :: Char -> TextBuilder
char = Int -> TextBuilder
unicodeCodePoint (Int -> TextBuilder) -> (Char -> Int) -> Char -> TextBuilder
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Char -> Int
ord
{-# INLINE unicodeCodePoint #-}
unicodeCodePoint :: Int -> TextBuilder
unicodeCodePoint :: Int -> TextBuilder
unicodeCodePoint Int
a =
Allocator -> Int -> TextBuilder
TextBuilder (Int -> Allocator
Allocator.unicodeCodePoint Int
a) Int
1
{-# INLINEABLE utf16CodeUnits1 #-}
utf16CodeUnits1 :: Word16 -> TextBuilder
utf16CodeUnits1 :: Word16 -> TextBuilder
utf16CodeUnits1 Word16
a =
Allocator -> Int -> TextBuilder
TextBuilder (Word16 -> Allocator
Allocator.utf16CodeUnits1 Word16
a) Int
1
{-# INLINEABLE utf16CodeUnits2 #-}
utf16CodeUnits2 :: Word16 -> Word16 -> TextBuilder
utf16CodeUnits2 :: Word16 -> Word16 -> TextBuilder
utf16CodeUnits2 Word16
a Word16
b =
Allocator -> Int -> TextBuilder
TextBuilder (Word16 -> Word16 -> Allocator
Allocator.utf16CodeUnits2 Word16
a Word16
b) Int
1
{-# INLINE utf8CodeUnits1 #-}
utf8CodeUnits1 :: Word8 -> TextBuilder
utf8CodeUnits1 :: Word8 -> TextBuilder
utf8CodeUnits1 Word8
a =
Allocator -> Int -> TextBuilder
TextBuilder (Word8 -> Allocator
Allocator.utf8CodeUnits1 Word8
a) Int
1
{-# INLINE utf8CodeUnits2 #-}
utf8CodeUnits2 :: Word8 -> Word8 -> TextBuilder
utf8CodeUnits2 :: Word8 -> Word8 -> TextBuilder
utf8CodeUnits2 Word8
a Word8
b =
Allocator -> Int -> TextBuilder
TextBuilder (Word8 -> Word8 -> Allocator
Allocator.utf8CodeUnits2 Word8
a Word8
b) Int
1
{-# INLINE utf8CodeUnits3 #-}
utf8CodeUnits3 :: Word8 -> Word8 -> Word8 -> TextBuilder
utf8CodeUnits3 :: Word8 -> Word8 -> Word8 -> TextBuilder
utf8CodeUnits3 Word8
a Word8
b Word8
c =
Allocator -> Int -> TextBuilder
TextBuilder (Word8 -> Word8 -> Word8 -> Allocator
Allocator.utf8CodeUnits3 Word8
a Word8
b Word8
c) Int
1
{-# INLINE utf8CodeUnits4 #-}
utf8CodeUnits4 :: Word8 -> Word8 -> Word8 -> Word8 -> TextBuilder
utf8CodeUnits4 :: Word8 -> Word8 -> Word8 -> Word8 -> TextBuilder
utf8CodeUnits4 Word8
a Word8
b Word8
c Word8
d =
Allocator -> Int -> TextBuilder
TextBuilder (Word8 -> Word8 -> Word8 -> Word8 -> Allocator
Allocator.utf8CodeUnits4 Word8
a Word8
b Word8
c Word8
d) Int
1
{-# INLINEABLE asciiByteString #-}
asciiByteString :: ByteString -> TextBuilder
asciiByteString :: ByteString -> TextBuilder
asciiByteString ByteString
byteString =
Allocator -> Int -> TextBuilder
TextBuilder
(ByteString -> Allocator
Allocator.asciiByteString ByteString
byteString)
(ByteString -> Int
ByteString.length ByteString
byteString)
{-# INLINEABLE text #-}
text :: Text -> TextBuilder
text :: Text -> TextBuilder
text Text
text =
Allocator -> Int -> TextBuilder
TextBuilder (Text -> Allocator
Allocator.text Text
text) (Text -> Int
Text.length Text
text)
{-# INLINE lazyText #-}
lazyText :: TextLazy.Text -> TextBuilder
lazyText :: Text -> TextBuilder
lazyText =
(Text -> TextBuilder -> TextBuilder)
-> TextBuilder -> Text -> TextBuilder
forall a. (Text -> a -> a) -> a -> Text -> a
TextLazy.foldrChunks (TextBuilder -> TextBuilder -> TextBuilder
forall a. Monoid a => a -> a -> a
mappend (TextBuilder -> TextBuilder -> TextBuilder)
-> (Text -> TextBuilder) -> Text -> TextBuilder -> TextBuilder
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Text -> TextBuilder
text) TextBuilder
forall a. Monoid a => a
mempty
{-# INLINE string #-}
string :: String -> TextBuilder
string :: String -> TextBuilder
string =
(Char -> TextBuilder) -> String -> TextBuilder
forall m a. Monoid m => (a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Char -> TextBuilder
char
{-# INLINEABLE decimal #-}
decimal :: (Integral a) => a -> TextBuilder
decimal :: forall a. Integral a => a -> TextBuilder
decimal a
i =
if a
i a -> a -> Bool
forall a. Ord a => a -> a -> Bool
>= a
0
then a -> TextBuilder
forall a. Integral a => a -> TextBuilder
unsignedDecimal a
i
else Int -> TextBuilder
unicodeCodePoint Int
45 TextBuilder -> TextBuilder -> TextBuilder
forall a. Semigroup a => a -> a -> a
<> a -> TextBuilder
forall a. Integral a => a -> TextBuilder
unsignedDecimal (a -> a
forall a. Num a => a -> a
negate a
i)
{-# INLINEABLE unsignedDecimal #-}
unsignedDecimal :: (Integral a) => a -> TextBuilder
unsignedDecimal :: forall a. Integral a => a -> TextBuilder
unsignedDecimal =
(a -> TextBuilder) -> Unfoldr a -> TextBuilder
forall m a. Monoid m => (a -> m) -> Unfoldr a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap a -> TextBuilder
forall a. Integral a => a -> TextBuilder
decimalDigit (Unfoldr a -> TextBuilder) -> (a -> Unfoldr a) -> a -> TextBuilder
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. a -> Unfoldr a
forall a. Integral a => a -> Unfoldr a
Unfoldr.decimalDigits
fixedUnsignedDecimal :: (Integral a) => Int -> a -> TextBuilder
fixedUnsignedDecimal :: forall a. Integral a => Int -> a -> TextBuilder
fixedUnsignedDecimal Int
size a
val =
Allocator -> Int -> TextBuilder
TextBuilder (Int -> a -> Allocator
forall a. Integral a => Int -> a -> Allocator
Allocator.fixedUnsignedDecimal Int
size a
val) Int
size
{-# INLINEABLE thousandSeparatedDecimal #-}
thousandSeparatedDecimal :: (Integral a) => Char -> a -> TextBuilder
thousandSeparatedDecimal :: forall a. Integral a => Char -> a -> TextBuilder
thousandSeparatedDecimal Char
separatorChar a
a =
if a
a a -> a -> Bool
forall a. Ord a => a -> a -> Bool
>= a
0
then Char -> a -> TextBuilder
forall a. Integral a => Char -> a -> TextBuilder
thousandSeparatedUnsignedDecimal Char
separatorChar a
a
else Int -> TextBuilder
unicodeCodePoint Int
45 TextBuilder -> TextBuilder -> TextBuilder
forall a. Semigroup a => a -> a -> a
<> Char -> a -> TextBuilder
forall a. Integral a => Char -> a -> TextBuilder
thousandSeparatedUnsignedDecimal Char
separatorChar (a -> a
forall a. Num a => a -> a
negate a
a)
{-# INLINEABLE thousandSeparatedUnsignedDecimal #-}
thousandSeparatedUnsignedDecimal :: (Integral a) => Char -> a -> TextBuilder
thousandSeparatedUnsignedDecimal :: forall a. Integral a => Char -> a -> TextBuilder
thousandSeparatedUnsignedDecimal Char
separatorChar =
a -> TextBuilder
processRightmostDigit
where
processRightmostDigit :: a -> TextBuilder
processRightmostDigit a
value =
case a -> a -> (a, a)
forall a. Integral a => a -> a -> (a, a)
divMod a
value a
10 of
(a
value, a
digit) ->
[TextBuilder] -> Int -> a -> TextBuilder
processAnotherDigit [a -> TextBuilder
forall a. Integral a => a -> TextBuilder
decimalDigit a
digit] (Int
1 :: Int) a
value
processAnotherDigit :: [TextBuilder] -> Int -> a -> TextBuilder
processAnotherDigit [TextBuilder]
builders Int
index a
value =
if a
value a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
0
then [TextBuilder] -> TextBuilder
forall a. Monoid a => [a] -> a
mconcat [TextBuilder]
builders
else case a -> a -> (a, a)
forall a. Integral a => a -> a -> (a, a)
divMod a
value a
10 of
(a
value, a
digit) ->
if Int -> Int -> Int
forall a. Integral a => a -> a -> a
mod Int
index Int
3 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
then
[TextBuilder] -> Int -> a -> TextBuilder
processAnotherDigit
(a -> TextBuilder
forall a. Integral a => a -> TextBuilder
decimalDigit a
digit TextBuilder -> [TextBuilder] -> [TextBuilder]
forall a. a -> [a] -> [a]
: Char -> TextBuilder
char Char
separatorChar TextBuilder -> [TextBuilder] -> [TextBuilder]
forall a. a -> [a] -> [a]
: [TextBuilder]
builders)
(Int -> Int
forall a. Enum a => a -> a
succ Int
index)
a
value
else
[TextBuilder] -> Int -> a -> TextBuilder
processAnotherDigit
(a -> TextBuilder
forall a. Integral a => a -> TextBuilder
decimalDigit a
digit TextBuilder -> [TextBuilder] -> [TextBuilder]
forall a. a -> [a] -> [a]
: [TextBuilder]
builders)
(Int -> Int
forall a. Enum a => a -> a
succ Int
index)
a
value
{-# INLINEABLE dataSizeInBytesInDecimal #-}
dataSizeInBytesInDecimal :: (Integral a) => Char -> a -> TextBuilder
dataSizeInBytesInDecimal :: forall a. Integral a => Char -> a -> TextBuilder
dataSizeInBytesInDecimal Char
separatorChar a
amount =
if a
amount a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
1000
then a -> TextBuilder
forall a. Integral a => a -> TextBuilder
unsignedDecimal a
amount TextBuilder -> TextBuilder -> TextBuilder
forall a. Semigroup a => a -> a -> a
<> TextBuilder
"B"
else
if a
amount a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
1000000
then Char -> a -> a -> TextBuilder
forall a. Integral a => Char -> a -> a -> TextBuilder
dividedDecimal Char
separatorChar a
100 a
amount TextBuilder -> TextBuilder -> TextBuilder
forall a. Semigroup a => a -> a -> a
<> TextBuilder
"kB"
else
if a
amount a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
1000000000
then Char -> a -> a -> TextBuilder
forall a. Integral a => Char -> a -> a -> TextBuilder
dividedDecimal Char
separatorChar a
100000 a
amount TextBuilder -> TextBuilder -> TextBuilder
forall a. Semigroup a => a -> a -> a
<> TextBuilder
"MB"
else
if a
amount a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
1000000000000
then Char -> a -> a -> TextBuilder
forall a. Integral a => Char -> a -> a -> TextBuilder
dividedDecimal Char
separatorChar a
100000000 a
amount TextBuilder -> TextBuilder -> TextBuilder
forall a. Semigroup a => a -> a -> a
<> TextBuilder
"GB"
else
if a
amount a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
1000000000000000
then Char -> a -> a -> TextBuilder
forall a. Integral a => Char -> a -> a -> TextBuilder
dividedDecimal Char
separatorChar a
100000000000 a
amount TextBuilder -> TextBuilder -> TextBuilder
forall a. Semigroup a => a -> a -> a
<> TextBuilder
"TB"
else
if a
amount a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
1000000000000000000
then Char -> a -> a -> TextBuilder
forall a. Integral a => Char -> a -> a -> TextBuilder
dividedDecimal Char
separatorChar a
100000000000000 a
amount TextBuilder -> TextBuilder -> TextBuilder
forall a. Semigroup a => a -> a -> a
<> TextBuilder
"PB"
else
if a
amount a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
1000000000000000000000
then Char -> a -> a -> TextBuilder
forall a. Integral a => Char -> a -> a -> TextBuilder
dividedDecimal Char
separatorChar a
100000000000000000 a
amount TextBuilder -> TextBuilder -> TextBuilder
forall a. Semigroup a => a -> a -> a
<> TextBuilder
"EB"
else
if a
amount a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
1000000000000000000000000
then Char -> a -> a -> TextBuilder
forall a. Integral a => Char -> a -> a -> TextBuilder
dividedDecimal Char
separatorChar a
100000000000000000000 a
amount TextBuilder -> TextBuilder -> TextBuilder
forall a. Semigroup a => a -> a -> a
<> TextBuilder
"ZB"
else Char -> a -> a -> TextBuilder
forall a. Integral a => Char -> a -> a -> TextBuilder
dividedDecimal Char
separatorChar a
100000000000000000000000 a
amount TextBuilder -> TextBuilder -> TextBuilder
forall a. Semigroup a => a -> a -> a
<> TextBuilder
"YB"
dividedDecimal :: (Integral a) => Char -> a -> a -> TextBuilder
dividedDecimal :: forall a. Integral a => Char -> a -> a -> TextBuilder
dividedDecimal Char
separatorChar a
divisor a
n =
let byDivisor :: a
byDivisor = a -> a -> a
forall a. Integral a => a -> a -> a
div a
n a
divisor
byExtraTen :: a
byExtraTen = a -> a -> a
forall a. Integral a => a -> a -> a
div a
byDivisor a
10
remainder :: a
remainder = a
byDivisor a -> a -> a
forall a. Num a => a -> a -> a
- a
byExtraTen a -> a -> a
forall a. Num a => a -> a -> a
* a
10
in if a
remainder a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
0 Bool -> Bool -> Bool
|| a
byExtraTen a -> a -> Bool
forall a. Ord a => a -> a -> Bool
>= a
10
then Char -> a -> TextBuilder
forall a. Integral a => Char -> a -> TextBuilder
thousandSeparatedDecimal Char
separatorChar a
byExtraTen
else Char -> a -> TextBuilder
forall a. Integral a => Char -> a -> TextBuilder
thousandSeparatedDecimal Char
separatorChar a
byExtraTen TextBuilder -> TextBuilder -> TextBuilder
forall a. Semigroup a => a -> a -> a
<> TextBuilder
"." TextBuilder -> TextBuilder -> TextBuilder
forall a. Semigroup a => a -> a -> a
<> a -> TextBuilder
forall a. Integral a => a -> TextBuilder
decimalDigit a
remainder
{-# INLINE unsignedBinary #-}
unsignedBinary :: (Integral a) => a -> TextBuilder
unsignedBinary :: forall a. Integral a => a -> TextBuilder
unsignedBinary =
(a -> TextBuilder) -> Unfoldr a -> TextBuilder
forall m a. Monoid m => (a -> m) -> Unfoldr a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap a -> TextBuilder
forall a. Integral a => a -> TextBuilder
decimalDigit (Unfoldr a -> TextBuilder) -> (a -> Unfoldr a) -> a -> TextBuilder
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. a -> Unfoldr a
forall a. Integral a => a -> Unfoldr a
Unfoldr.binaryDigits
finiteBitsUnsignedBinary :: (FiniteBits a) => a -> TextBuilder
finiteBitsUnsignedBinary :: forall a. FiniteBits a => a -> TextBuilder
finiteBitsUnsignedBinary a
a =
Allocator -> Int -> TextBuilder
TextBuilder Allocator
allocator Int
size
where
allocator :: Allocator
allocator = a -> Allocator
forall a. FiniteBits a => a -> Allocator
Allocator.finiteBitsUnsignedBinary a
a
size :: Int
size = Allocator -> Int
Allocator.sizeBound Allocator
allocator
{-# INLINE unsignedPaddedBinary #-}
unsignedPaddedBinary :: (Integral a, FiniteBits a) => a -> TextBuilder
unsignedPaddedBinary :: forall a. (Integral a, FiniteBits a) => a -> TextBuilder
unsignedPaddedBinary a
a =
Int -> Char -> TextBuilder -> TextBuilder
padFromLeft (a -> Int
forall b. FiniteBits b => b -> Int
finiteBitSize a
a) Char
'0' (TextBuilder -> TextBuilder) -> TextBuilder -> TextBuilder
forall a b. (a -> b) -> a -> b
$ (a -> TextBuilder) -> Unfoldr a -> TextBuilder
forall m a. Monoid m => (a -> m) -> Unfoldr a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap a -> TextBuilder
forall a. Integral a => a -> TextBuilder
decimalDigit (Unfoldr a -> TextBuilder) -> Unfoldr a -> TextBuilder
forall a b. (a -> b) -> a -> b
$ a -> Unfoldr a
forall a. Integral a => a -> Unfoldr a
Unfoldr.binaryDigits a
a
{-# INLINE hexadecimal #-}
hexadecimal :: (Integral a) => a -> TextBuilder
hexadecimal :: forall a. Integral a => a -> TextBuilder
hexadecimal a
i =
if a
i a -> a -> Bool
forall a. Ord a => a -> a -> Bool
>= a
0
then a -> TextBuilder
forall a. Integral a => a -> TextBuilder
unsignedHexadecimal a
i
else Int -> TextBuilder
unicodeCodePoint Int
45 TextBuilder -> TextBuilder -> TextBuilder
forall a. Semigroup a => a -> a -> a
<> a -> TextBuilder
forall a. Integral a => a -> TextBuilder
unsignedHexadecimal (a -> a
forall a. Num a => a -> a
negate a
i)
{-# INLINE unsignedHexadecimal #-}
unsignedHexadecimal :: (Integral a) => a -> TextBuilder
unsignedHexadecimal :: forall a. Integral a => a -> TextBuilder
unsignedHexadecimal =
(a -> TextBuilder) -> Unfoldr a -> TextBuilder
forall m a. Monoid m => (a -> m) -> Unfoldr a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap a -> TextBuilder
forall a. Integral a => a -> TextBuilder
hexadecimalDigit (Unfoldr a -> TextBuilder) -> (a -> Unfoldr a) -> a -> TextBuilder
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. a -> Unfoldr a
forall a. Integral a => a -> Unfoldr a
Unfoldr.hexadecimalDigits
{-# INLINE decimalDigit #-}
decimalDigit :: (Integral a) => a -> TextBuilder
decimalDigit :: forall a. Integral a => a -> TextBuilder
decimalDigit (a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> Int
n) =
Int -> TextBuilder
unicodeCodePoint (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
48)
{-# INLINE hexadecimalDigit #-}
hexadecimalDigit :: (Integral a) => a -> TextBuilder
hexadecimalDigit :: forall a. Integral a => a -> TextBuilder
hexadecimalDigit (a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> Int
n) =
if Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
9
then Int -> TextBuilder
unicodeCodePoint (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
48)
else Int -> TextBuilder
unicodeCodePoint (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
87)
{-# INLINE intercalate #-}
intercalate :: (Foldable f) => TextBuilder -> f TextBuilder -> TextBuilder
intercalate :: forall (f :: * -> *).
Foldable f =>
TextBuilder -> f TextBuilder -> TextBuilder
intercalate TextBuilder
separator = Product2 Bool TextBuilder -> TextBuilder
forall {a} {b}. Product2 a b -> b
extract (Product2 Bool TextBuilder -> TextBuilder)
-> (f TextBuilder -> Product2 Bool TextBuilder)
-> f TextBuilder
-> TextBuilder
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Product2 Bool TextBuilder
-> TextBuilder -> Product2 Bool TextBuilder)
-> Product2 Bool TextBuilder
-> f TextBuilder
-> Product2 Bool TextBuilder
forall b a. (b -> a -> b) -> b -> f a -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' Product2 Bool TextBuilder
-> TextBuilder -> Product2 Bool TextBuilder
step Product2 Bool TextBuilder
forall {b}. Monoid b => Product2 Bool b
init
where
init :: Product2 Bool b
init = Bool -> b -> Product2 Bool b
forall a b. a -> b -> Product2 a b
Product2 Bool
False b
forall a. Monoid a => a
mempty
step :: Product2 Bool TextBuilder
-> TextBuilder -> Product2 Bool TextBuilder
step (Product2 Bool
isNotFirst TextBuilder
builder) TextBuilder
element =
Bool -> TextBuilder -> Product2 Bool TextBuilder
forall a b. a -> b -> Product2 a b
Product2 Bool
True
(TextBuilder -> Product2 Bool TextBuilder)
-> TextBuilder -> Product2 Bool TextBuilder
forall a b. (a -> b) -> a -> b
$ if Bool
isNotFirst
then TextBuilder
builder TextBuilder -> TextBuilder -> TextBuilder
forall a. Semigroup a => a -> a -> a
<> TextBuilder
separator TextBuilder -> TextBuilder -> TextBuilder
forall a. Semigroup a => a -> a -> a
<> TextBuilder
element
else TextBuilder
element
extract :: Product2 a b -> b
extract (Product2 a
_ b
builder) = b
builder
{-# INLINE intercalateMap #-}
intercalateMap :: (Foldable f) => TextBuilder -> (a -> TextBuilder) -> f a -> TextBuilder
intercalateMap :: forall (f :: * -> *) a.
Foldable f =>
TextBuilder -> (a -> TextBuilder) -> f a -> TextBuilder
intercalateMap TextBuilder
separator a -> TextBuilder
mapper = Maybe TextBuilder -> TextBuilder
forall {a}. Monoid a => Maybe a -> a
extract (Maybe TextBuilder -> TextBuilder)
-> (f a -> Maybe TextBuilder) -> f a -> TextBuilder
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Maybe TextBuilder -> a -> Maybe TextBuilder)
-> Maybe TextBuilder -> f a -> Maybe TextBuilder
forall b a. (b -> a -> b) -> b -> f a -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' Maybe TextBuilder -> a -> Maybe TextBuilder
step Maybe TextBuilder
forall {a}. Maybe a
init
where
init :: Maybe a
init = Maybe a
forall {a}. Maybe a
Nothing
step :: Maybe TextBuilder -> a -> Maybe TextBuilder
step Maybe TextBuilder
acc a
element =
TextBuilder -> Maybe TextBuilder
forall a. a -> Maybe a
Just (TextBuilder -> Maybe TextBuilder)
-> TextBuilder -> Maybe TextBuilder
forall a b. (a -> b) -> a -> b
$ case Maybe TextBuilder
acc of
Maybe TextBuilder
Nothing -> a -> TextBuilder
mapper a
element
Just TextBuilder
acc -> TextBuilder
acc TextBuilder -> TextBuilder -> TextBuilder
forall a. Semigroup a => a -> a -> a
<> TextBuilder
separator TextBuilder -> TextBuilder -> TextBuilder
forall a. Semigroup a => a -> a -> a
<> a -> TextBuilder
mapper a
element
extract :: Maybe a -> a
extract = a -> Maybe a -> a
forall a. a -> Maybe a -> a
fromMaybe a
forall a. Monoid a => a
mempty
{-# INLINEABLE padFromLeft #-}
padFromLeft :: Int -> Char -> TextBuilder -> TextBuilder
padFromLeft :: Int -> Char -> TextBuilder -> TextBuilder
padFromLeft Int
paddedLength Char
paddingChar TextBuilder
builder =
let builderLength :: Int
builderLength = TextBuilder -> Int
length TextBuilder
builder
in if Int
paddedLength Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
builderLength
then TextBuilder
builder
else (Char -> TextBuilder) -> String -> TextBuilder
forall m a. Monoid m => (a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Char -> TextBuilder
char (Int -> Char -> String
forall a. Int -> a -> [a]
replicate (Int
paddedLength Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
builderLength) Char
paddingChar) TextBuilder -> TextBuilder -> TextBuilder
forall a. Semigroup a => a -> a -> a
<> TextBuilder
builder
{-# INLINEABLE padFromRight #-}
padFromRight :: Int -> Char -> TextBuilder -> TextBuilder
padFromRight :: Int -> Char -> TextBuilder -> TextBuilder
padFromRight Int
paddedLength Char
paddingChar TextBuilder
builder =
let builderLength :: Int
builderLength = TextBuilder -> Int
length TextBuilder
builder
in if Int
paddedLength Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
builderLength
then TextBuilder
builder
else TextBuilder
builder TextBuilder -> TextBuilder -> TextBuilder
forall a. Semigroup a => a -> a -> a
<> (Char -> TextBuilder) -> String -> TextBuilder
forall m a. Monoid m => (a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Char -> TextBuilder
char (Int -> Char -> String
forall a. Int -> a -> [a]
replicate (Int
paddedLength Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
builderLength) Char
paddingChar)
utcTimeInIso8601 :: UTCTime -> TextBuilder
utcTimeInIso8601 :: UTCTime -> TextBuilder
utcTimeInIso8601 UTCTime {Day
DiffTime
utctDay :: Day
utctDayTime :: DiffTime
utctDay :: UTCTime -> Day
utctDayTime :: UTCTime -> DiffTime
..} =
let (Year
year, Int
month, Int
day) = Day -> (Year, Int, Int)
toGregorian Day
utctDay
daySeconds :: Int
daySeconds = DiffTime -> Int
forall b. Integral b => DiffTime -> b
forall a b. (RealFrac a, Integral b) => a -> b
round DiffTime
utctDayTime
(Int
dayMinutes, Int
second) = Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
divMod Int
daySeconds Int
60
(Int
hour, Int
minute) = Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
divMod Int
dayMinutes Int
60
in Int -> Int -> Int -> Int -> Int -> Int -> TextBuilder
utcTimestampInIso8601 (Year -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Year
year) Int
month Int
day Int
hour Int
minute Int
second
utcTimestampInIso8601 ::
Int ->
Int ->
Int ->
Int ->
Int ->
Int ->
TextBuilder
utcTimestampInIso8601 :: Int -> Int -> Int -> Int -> Int -> Int -> TextBuilder
utcTimestampInIso8601 Int
y Int
mo Int
d Int
h Int
mi Int
s =
[TextBuilder] -> TextBuilder
forall a. Monoid a => [a] -> a
mconcat
[ Int -> Int -> TextBuilder
forall a. Integral a => Int -> a -> TextBuilder
fixedUnsignedDecimal Int
4 Int
y,
TextBuilder
"-",
Int -> Int -> TextBuilder
forall a. Integral a => Int -> a -> TextBuilder
fixedUnsignedDecimal Int
2 Int
mo,
TextBuilder
"-",
Int -> Int -> TextBuilder
forall a. Integral a => Int -> a -> TextBuilder
fixedUnsignedDecimal Int
2 Int
d,
TextBuilder
"T",
Int -> Int -> TextBuilder
forall a. Integral a => Int -> a -> TextBuilder
fixedUnsignedDecimal Int
2 Int
h,
TextBuilder
":",
Int -> Int -> TextBuilder
forall a. Integral a => Int -> a -> TextBuilder
fixedUnsignedDecimal Int
2 Int
mi,
TextBuilder
":",
Int -> Int -> TextBuilder
forall a. Integral a => Int -> a -> TextBuilder
fixedUnsignedDecimal Int
2 Int
s,
TextBuilder
"Z"
]
{-# INLINEABLE intervalInSeconds #-}
intervalInSeconds :: (RealFrac seconds) => seconds -> TextBuilder
intervalInSeconds :: forall seconds. RealFrac seconds => seconds -> TextBuilder
intervalInSeconds seconds
interval = (State Int TextBuilder -> Int -> TextBuilder)
-> Int -> State Int TextBuilder -> TextBuilder
forall a b c. (a -> b -> c) -> b -> a -> c
flip State Int TextBuilder -> Int -> TextBuilder
forall s a. State s a -> s -> a
evalState (seconds -> Int
forall b. Integral b => seconds -> b
forall a b. (RealFrac a, Integral b) => a -> b
round seconds
interval :: Int) (State Int TextBuilder -> TextBuilder)
-> State Int TextBuilder -> TextBuilder
forall a b. (a -> b) -> a -> b
$ do
Int
seconds <- (Int -> (Int, Int)) -> StateT Int Identity Int
forall (m :: * -> *) s a. Monad m => (s -> (a, s)) -> StateT s m a
state ((Int, Int) -> (Int, Int)
forall a b. (a, b) -> (b, a)
swap ((Int, Int) -> (Int, Int))
-> (Int -> (Int, Int)) -> Int -> (Int, Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Int -> Int -> (Int, Int)) -> Int -> Int -> (Int, Int)
forall a b c. (a -> b -> c) -> b -> a -> c
flip Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
divMod Int
60)
Int
minutes <- (Int -> (Int, Int)) -> StateT Int Identity Int
forall (m :: * -> *) s a. Monad m => (s -> (a, s)) -> StateT s m a
state ((Int, Int) -> (Int, Int)
forall a b. (a, b) -> (b, a)
swap ((Int, Int) -> (Int, Int))
-> (Int -> (Int, Int)) -> Int -> (Int, Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Int -> Int -> (Int, Int)) -> Int -> Int -> (Int, Int)
forall a b c. (a -> b -> c) -> b -> a -> c
flip Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
divMod Int
60)
Int
hours <- (Int -> (Int, Int)) -> StateT Int Identity Int
forall (m :: * -> *) s a. Monad m => (s -> (a, s)) -> StateT s m a
state ((Int, Int) -> (Int, Int)
forall a b. (a, b) -> (b, a)
swap ((Int, Int) -> (Int, Int))
-> (Int -> (Int, Int)) -> Int -> (Int, Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Int -> Int -> (Int, Int)) -> Int -> Int -> (Int, Int)
forall a b c. (a -> b -> c) -> b -> a -> c
flip Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
divMod Int
24)
Int
days <- StateT Int Identity Int
forall (m :: * -> *) s. Monad m => StateT s m s
get
TextBuilder -> State Int TextBuilder
forall a. a -> StateT Int Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return
(TextBuilder -> State Int TextBuilder)
-> TextBuilder -> State Int TextBuilder
forall a b. (a -> b) -> a -> b
$ Int -> Char -> TextBuilder -> TextBuilder
padFromLeft Int
2 Char
'0' (Int -> TextBuilder
forall a. Integral a => a -> TextBuilder
decimal Int
days)
TextBuilder -> TextBuilder -> TextBuilder
forall a. Semigroup a => a -> a -> a
<> TextBuilder
":"
TextBuilder -> TextBuilder -> TextBuilder
forall a. Semigroup a => a -> a -> a
<> Int -> Char -> TextBuilder -> TextBuilder
padFromLeft Int
2 Char
'0' (Int -> TextBuilder
forall a. Integral a => a -> TextBuilder
decimal Int
hours)
TextBuilder -> TextBuilder -> TextBuilder
forall a. Semigroup a => a -> a -> a
<> TextBuilder
":"
TextBuilder -> TextBuilder -> TextBuilder
forall a. Semigroup a => a -> a -> a
<> Int -> Char -> TextBuilder -> TextBuilder
padFromLeft Int
2 Char
'0' (Int -> TextBuilder
forall a. Integral a => a -> TextBuilder
decimal Int
minutes)
TextBuilder -> TextBuilder -> TextBuilder
forall a. Semigroup a => a -> a -> a
<> TextBuilder
":"
TextBuilder -> TextBuilder -> TextBuilder
forall a. Semigroup a => a -> a -> a
<> Int -> Char -> TextBuilder -> TextBuilder
padFromLeft Int
2 Char
'0' (Int -> TextBuilder
forall a. Integral a => a -> TextBuilder
decimal Int
seconds)
diffTimeCompact :: DiffTime -> TextBuilder
diffTimeCompact :: DiffTime -> TextBuilder
diffTimeCompact = Year -> TextBuilder
picosecondsCompact (Year -> TextBuilder)
-> (DiffTime -> Year) -> DiffTime -> TextBuilder
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. DiffTime -> Year
diffTimeToPicoseconds
picosecondsCompact :: Integer -> TextBuilder
picosecondsCompact :: Year -> TextBuilder
picosecondsCompact Year
x =
Year -> TextBuilder -> TextBuilder -> TextBuilder
attemptOr Year
1_000_000_000_000 TextBuilder
"s"
(TextBuilder -> TextBuilder) -> TextBuilder -> TextBuilder
forall a b. (a -> b) -> a -> b
$ Year -> TextBuilder -> TextBuilder -> TextBuilder
attemptOr Year
1_000_000_000 TextBuilder
"ms"
(TextBuilder -> TextBuilder) -> TextBuilder -> TextBuilder
forall a b. (a -> b) -> a -> b
$ Year -> TextBuilder -> TextBuilder -> TextBuilder
attemptOr Year
1_000_000 TextBuilder
"us"
(TextBuilder -> TextBuilder) -> TextBuilder -> TextBuilder
forall a b. (a -> b) -> a -> b
$ Year -> TextBuilder -> TextBuilder -> TextBuilder
attemptOr Year
1_000 TextBuilder
"ns"
(TextBuilder -> TextBuilder) -> TextBuilder -> TextBuilder
forall a b. (a -> b) -> a -> b
$ Year -> TextBuilder
forall a. Integral a => a -> TextBuilder
decimal Year
x
TextBuilder -> TextBuilder -> TextBuilder
forall a. Semigroup a => a -> a -> a
<> TextBuilder
"ps"
where
attemptOr :: Year -> TextBuilder -> TextBuilder -> TextBuilder
attemptOr Year
factor TextBuilder
suffix TextBuilder
alternative =
if Year
x Year -> Year -> Bool
forall a. Eq a => a -> a -> Bool
== Year
divided Year -> Year -> Year
forall a. Num a => a -> a -> a
* Year
factor
then Year -> TextBuilder
forall a. Integral a => a -> TextBuilder
decimal Year
divided TextBuilder -> TextBuilder -> TextBuilder
forall a. Semigroup a => a -> a -> a
<> TextBuilder
suffix
else TextBuilder
alternative
where
divided :: Year
divided = Year -> Year -> Year
forall a. Integral a => a -> a -> a
div Year
x Year
factor
{-# INLINE fixedDouble #-}
fixedDouble ::
Int ->
Double ->
TextBuilder
fixedDouble :: Int -> Double -> TextBuilder
fixedDouble Int
decimalPlaces = String -> TextBuilder
forall a. IsString a => String -> a
fromString (String -> TextBuilder)
-> (Double -> String) -> Double -> TextBuilder
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. String -> Double -> String
forall r. PrintfType r => String -> r
printf (String
"%." String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
decimalPlaces String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"f")
{-# INLINE doublePercent #-}
doublePercent ::
Int ->
Double ->
TextBuilder
doublePercent :: Int -> Double -> TextBuilder
doublePercent Int
decimalPlaces Double
x = Int -> Double -> TextBuilder
fixedDouble Int
decimalPlaces (Double
x Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
100) TextBuilder -> TextBuilder -> TextBuilder
forall a. Semigroup a => a -> a -> a
<> TextBuilder
"%"
{-# INLINE hexData #-}
hexData :: ByteString -> TextBuilder
hexData :: ByteString -> TextBuilder
hexData =
TextBuilder -> [TextBuilder] -> TextBuilder
forall (f :: * -> *).
Foldable f =>
TextBuilder -> f TextBuilder -> TextBuilder
intercalate TextBuilder
" "
([TextBuilder] -> TextBuilder)
-> (ByteString -> [TextBuilder]) -> ByteString -> TextBuilder
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ([TextBuilder] -> TextBuilder) -> [[TextBuilder]] -> [TextBuilder]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [TextBuilder] -> TextBuilder
forall a. Monoid a => [a] -> a
mconcat
([[TextBuilder]] -> [TextBuilder])
-> (ByteString -> [[TextBuilder]]) -> ByteString -> [TextBuilder]
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int -> [TextBuilder] -> [[TextBuilder]]
forall e. Int -> [e] -> [[e]]
Split.chunksOf Int
2
([TextBuilder] -> [[TextBuilder]])
-> (ByteString -> [TextBuilder]) -> ByteString -> [[TextBuilder]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Word8 -> TextBuilder) -> [Word8] -> [TextBuilder]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Word8 -> TextBuilder
forall a. Integral a => a -> TextBuilder
byte
([Word8] -> [TextBuilder])
-> (ByteString -> [Word8]) -> ByteString -> [TextBuilder]
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> [Word8]
ByteString.unpack
where
byte :: a -> TextBuilder
byte =
Int -> Char -> TextBuilder -> TextBuilder
padFromLeft Int
2 Char
'0' (TextBuilder -> TextBuilder)
-> (a -> TextBuilder) -> a -> TextBuilder
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. a -> TextBuilder
forall a. Integral a => a -> TextBuilder
unsignedHexadecimal