Z-Data-0.1.7.0: Array, vector and text

Copyright(c) Dong Han 2017-2019
LicenseBSD
Maintainerwinterland1989@gmail.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Z.Data.Text.ShowT

Contents

Description

Base on UTF8 compatible textual builders from Builder, we provide a newtype wrapper TextBuilder which can be directly used to build Text.

We also provide faster alternative to Show class, i.e. ShowT, which also provides Generic based instances deriving.

Synopsis

ShowT class

class ShowT a where Source #

A class similar to Show, serving the purpose that quickly convert a data type to a Text value.

You can use newtype or generic deriving to implement instance of this class quickly:

 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
 {-# LANGUAGE DeriveAnyClass #-}
 {-# LANGUAGE DeriveGeneric #-}
 {-# LANGUAGE DerivingStrategies #-}

 import GHC.Generics

 newtype FooInt = FooInt Int deriving (Generic)
                           deriving anyclass ShowT

> showT (FooInt 3)
> "FooInt 3"

 newtype FooInt = FooInt Int deriving (Generic)
                           deriving newtype ShowT

> showT (FooInt 3)
> "3"

Minimal complete definition

Nothing

Methods

toTextBuilder :: Int -> a -> TextBuilder () Source #

toTextBuilder :: (Generic a, GToText (Rep a)) => Int -> a -> TextBuilder () Source #

Instances
ShowT Bool Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT Char Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT Double Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT Float Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT Int Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT Int8 Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT Int16 Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT Int32 Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT Int64 Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT Integer Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT Natural Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT Ordering Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT Word Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT Word8 Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT Word16 Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT Word32 Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT Word64 Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT CallStack Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT () Source # 
Instance details

Defined in Z.Data.Text.ShowT

Methods

toTextBuilder :: Int -> () -> TextBuilder () Source #

ShowT Version Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT ExitCode Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT CChar Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT CSChar Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT CUChar Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT CShort Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT CUShort Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT CInt Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT CUInt Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT CLong Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT CULong Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT CLLong Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT CULLong Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT CBool Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT CFloat Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT CDouble Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT CPtrdiff Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT CSize Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT CWchar Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT CSigAtomic Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT CClock Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT CTime Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT CUSeconds Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT CSUSeconds Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT CIntPtr Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT CUIntPtr Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT CIntMax Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT CUIntMax Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT Scientific Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT Text Source #

The escaping rules is same with Show instance: we reuse JSON escaping rules here, so it will be faster.

Instance details

Defined in Z.Data.Text.ShowT

ShowT FlatIntSet Source # 
Instance details

Defined in Z.Data.Vector.FlatIntSet

ShowT Value Source # 
Instance details

Defined in Z.Data.JSON.Value

ShowT CBytes Source #

This instance provide UTF8 guarantee, illegal codepoints will be written as replacementChars.

Instance details

Defined in Z.Data.CBytes

ShowT a => ShowT [a] Source # 
Instance details

Defined in Z.Data.Text.ShowT

Methods

toTextBuilder :: Int -> [a] -> TextBuilder () Source #

ShowT a => ShowT (Maybe a) Source # 
Instance details

Defined in Z.Data.Text.ShowT

Methods

toTextBuilder :: Int -> Maybe a -> TextBuilder () Source #

(ShowT a, Integral a) => ShowT (Ratio a) Source # 
Instance details

Defined in Z.Data.Text.ShowT

Methods

toTextBuilder :: Int -> Ratio a -> TextBuilder () Source #

HasResolution a => ShowT (Fixed a) Source # 
Instance details

Defined in Z.Data.Text.ShowT

Methods

toTextBuilder :: Int -> Fixed a -> TextBuilder () Source #

ShowT a => ShowT (Min a) Source # 
Instance details

Defined in Z.Data.Text.ShowT

Methods

toTextBuilder :: Int -> Min a -> TextBuilder () Source #

ShowT a => ShowT (Max a) Source # 
Instance details

Defined in Z.Data.Text.ShowT

Methods

toTextBuilder :: Int -> Max a -> TextBuilder () Source #

ShowT a => ShowT (First a) Source # 
Instance details

Defined in Z.Data.Text.ShowT

Methods

toTextBuilder :: Int -> First a -> TextBuilder () Source #

ShowT a => ShowT (Last a) Source # 
Instance details

Defined in Z.Data.Text.ShowT

Methods

toTextBuilder :: Int -> Last a -> TextBuilder () Source #

ShowT a => ShowT (WrappedMonoid a) Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT a => ShowT (Identity a) Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT a => ShowT (First a) Source # 
Instance details

Defined in Z.Data.Text.ShowT

Methods

toTextBuilder :: Int -> First a -> TextBuilder () Source #

ShowT a => ShowT (Last a) Source # 
Instance details

Defined in Z.Data.Text.ShowT

Methods

toTextBuilder :: Int -> Last a -> TextBuilder () Source #

ShowT a => ShowT (Dual a) Source # 
Instance details

Defined in Z.Data.Text.ShowT

Methods

toTextBuilder :: Int -> Dual a -> TextBuilder () Source #

ShowT a => ShowT (NonEmpty a) Source # 
Instance details

Defined in Z.Data.Text.ShowT

(Prim a, ShowT a) => ShowT (PrimArray a) Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT a => ShowT (SmallArray a) Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT a => ShowT (Array a) Source # 
Instance details

Defined in Z.Data.Text.ShowT

Methods

toTextBuilder :: Int -> Array a -> TextBuilder () Source #

(Prim a, ShowT a) => ShowT (PrimVector a) Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT a => ShowT (Vector a) Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT (TextBuilder a) Source # 
Instance details

Defined in Z.Data.Text.ShowT

ShowT v => ShowT (FlatSet v) Source # 
Instance details

Defined in Z.Data.Vector.FlatSet

ShowT v => ShowT (FlatIntMap v) Source # 
Instance details

Defined in Z.Data.Vector.FlatIntMap

(ShowT a, ShowT b) => ShowT (Either a b) Source # 
Instance details

Defined in Z.Data.Text.ShowT

Methods

toTextBuilder :: Int -> Either a b -> TextBuilder () Source #

(ShowT a, ShowT b) => ShowT (a, b) Source # 
Instance details

Defined in Z.Data.Text.ShowT

Methods

toTextBuilder :: Int -> (a, b) -> TextBuilder () Source #

ShowT (Proxy a) Source # 
Instance details

Defined in Z.Data.Text.ShowT

Methods

toTextBuilder :: Int -> Proxy a -> TextBuilder () Source #

(PrimUnlifted a, ShowT a) => ShowT (UnliftedArray a) Source # 
Instance details

Defined in Z.Data.Text.ShowT

(ShowT k, ShowT v) => ShowT (FlatMap k v) Source # 
Instance details

Defined in Z.Data.Vector.FlatMap

Methods

toTextBuilder :: Int -> FlatMap k v -> TextBuilder () Source #

(ShowT a, ShowT b, ShowT c) => ShowT (a, b, c) Source # 
Instance details

Defined in Z.Data.Text.ShowT

Methods

toTextBuilder :: Int -> (a, b, c) -> TextBuilder () Source #

ShowT a => ShowT (Const a b) Source # 
Instance details

Defined in Z.Data.Text.ShowT

Methods

toTextBuilder :: Int -> Const a b -> TextBuilder () Source #

ShowT b => ShowT (Tagged a b) Source # 
Instance details

Defined in Z.Data.Text.ShowT

Methods

toTextBuilder :: Int -> Tagged a b -> TextBuilder () Source #

(ShowT a, ShowT b, ShowT c, ShowT d) => ShowT (a, b, c, d) Source # 
Instance details

Defined in Z.Data.Text.ShowT

Methods

toTextBuilder :: Int -> (a, b, c, d) -> TextBuilder () Source #

(ShowT (f a), ShowT (g a)) => ShowT (Product f g a) Source # 
Instance details

Defined in Z.Data.Text.ShowT

Methods

toTextBuilder :: Int -> Product f g a -> TextBuilder () Source #

(ShowT (f a), ShowT (g a), ShowT a) => ShowT (Sum f g a) Source # 
Instance details

Defined in Z.Data.Text.ShowT

Methods

toTextBuilder :: Int -> Sum f g a -> TextBuilder () Source #

(ShowT a, ShowT b, ShowT c, ShowT d, ShowT e) => ShowT (a, b, c, d, e) Source # 
Instance details

Defined in Z.Data.Text.ShowT

Methods

toTextBuilder :: Int -> (a, b, c, d, e) -> TextBuilder () Source #

ShowT (f (g a)) => ShowT (Compose f g a) Source # 
Instance details

Defined in Z.Data.Text.ShowT

Methods

toTextBuilder :: Int -> Compose f g a -> TextBuilder () Source #

(ShowT a, ShowT b, ShowT c, ShowT d, ShowT e, ShowT f) => ShowT (a, b, c, d, e, f) Source # 
Instance details

Defined in Z.Data.Text.ShowT

Methods

toTextBuilder :: Int -> (a, b, c, d, e, f) -> TextBuilder () Source #

(ShowT a, ShowT b, ShowT c, ShowT d, ShowT e, ShowT f, ShowT g) => ShowT (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Z.Data.Text.ShowT

Methods

toTextBuilder :: Int -> (a, b, c, d, e, f, g) -> TextBuilder () Source #

showT :: ShowT a => a -> Text Source #

Directly convert data to Text.

toBuilder :: ShowT a => a -> Builder () Source #

Directly convert data to Builder.

toBytes :: ShowT a => a -> Bytes Source #

Directly convert data to Bytes.

toString :: ShowT a => a -> String Source #

Faster show replacement.

Textual Builder

data TextBuilder a Source #

Buidlers which guarantee UTF-8 encoding, thus can be used to build text directly.

Notes on IsString instance: It's recommended to use IsString instance, there's a rewrite rule to turn encoding loop into a memcpy, which is much faster (the same rule also apply to stringUTF8). Different from Builder (), TextBuilder ()'s IsString instance will give you desired UTF8 guarantees:

  • NUL will be written directly as x00.
  • xD800 ~ xDFFF will be replaced by replacement char.
Instances
Monad TextBuilder Source # 
Instance details

Defined in Z.Data.Text.ShowT

Functor TextBuilder Source # 
Instance details

Defined in Z.Data.Text.ShowT

Methods

fmap :: (a -> b) -> TextBuilder a -> TextBuilder b #

(<$) :: a -> TextBuilder b -> TextBuilder a #

Applicative TextBuilder Source # 
Instance details

Defined in Z.Data.Text.ShowT

Methods

pure :: a -> TextBuilder a #

(<*>) :: TextBuilder (a -> b) -> TextBuilder a -> TextBuilder b #

liftA2 :: (a -> b -> c) -> TextBuilder a -> TextBuilder b -> TextBuilder c #

(*>) :: TextBuilder a -> TextBuilder b -> TextBuilder b #

(<*) :: TextBuilder a -> TextBuilder b -> TextBuilder a #

Show (TextBuilder a) Source # 
Instance details

Defined in Z.Data.Text.ShowT

a ~ () => IsString (TextBuilder a) Source # 
Instance details

Defined in Z.Data.Text.ShowT

Semigroup (TextBuilder ()) Source # 
Instance details

Defined in Z.Data.Text.ShowT

Monoid (TextBuilder ()) Source # 
Instance details

Defined in Z.Data.Text.ShowT

Arbitrary (TextBuilder ()) Source # 
Instance details

Defined in Z.Data.Text.ShowT

CoArbitrary (TextBuilder ()) Source # 
Instance details

Defined in Z.Data.Text.ShowT

Methods

coarbitrary :: TextBuilder () -> Gen b -> Gen b #

ShowT (TextBuilder a) Source # 
Instance details

Defined in Z.Data.Text.ShowT

unsafeFromBuilder :: Builder a -> TextBuilder a Source #

Unsafely turn a Builder into TextBuilder, thus it's user's responsibility to ensure only UTF-8 complied bytes are written.

buildText :: TextBuilder a -> Text Source #

Build a Text using TextBuilder, which provide UTF-8 encoding guarantee.

Basic UTF8 builders

stringUTF8 :: String -> TextBuilder () Source #

Turn String into TextBuilder with UTF8 encoding

Illegal codepoints will be written as replacementChars. This function will be rewritten into a memcpy if possible, (running a fast UTF-8 validation at runtime first).

charUTF8 :: Char -> TextBuilder () Source #

Turn Char into TextBuilder with UTF8 encoding

Illegal codepoints will be written as replacementChars.

string7 :: String -> TextBuilder () Source #

Turn String into TextBuilder with ASCII7 encoding

Codepoints beyond '\x7F' will be chopped.

char7 :: Char -> TextBuilder () Source #

Turn Char into TextBuilder with ASCII7 encoding

Codepoints beyond '\x7F' will be chopped.

text :: Text -> TextBuilder () Source #

Write UTF8 encoded Text using Builder.

Note, if you're trying to write string literals builders, please open OverloadedStrings and use Builders IsString instance, it will be rewritten into a memcpy.

escapeTextJSON :: Text -> Builder () Source #

Escape text using JSON string escaping rules and add double quotes, escaping rules:

   '\b':  "\b"
   '\f':  "\f"
   '\n':  "\n"
   '\r':  "\r"
   '\t':  "\t"
   '"':  "\""
   '\':  "\\"
   '/':  "\/"
   other chars <= 0x1F: "\u00XX"

Numeric builders

Integral type formatting

data IFormat Source #

Integral formatting options.

Constructors

IFormat 

Fields

Instances
Eq IFormat Source # 
Instance details

Defined in Z.Data.Builder.Numeric

Methods

(==) :: IFormat -> IFormat -> Bool #

(/=) :: IFormat -> IFormat -> Bool #

Ord IFormat Source # 
Instance details

Defined in Z.Data.Builder.Numeric

Show IFormat Source # 
Instance details

Defined in Z.Data.Builder.Numeric

Arbitrary IFormat Source # 
Instance details

Defined in Z.Data.Builder.Numeric

CoArbitrary IFormat Source # 
Instance details

Defined in Z.Data.Builder.Numeric

Methods

coarbitrary :: IFormat -> Gen b -> Gen b #

defaultIFormat :: IFormat Source #

defaultIFormat = IFormat 0 NoPadding False

int :: (Integral a, Bounded a) => a -> TextBuilder () Source #

int = intWith defaultIFormat

intWith :: (Integral a, Bounded a) => IFormat -> a -> TextBuilder () Source #

Format a Bounded Integral type like Int or Word16 into decimal ascii digits.

integer :: Integer -> TextBuilder () Source #

Format a Integer into decimal ascii digits.

Fixded size hexidecimal formatting

hex :: (FiniteBits a, Integral a) => a -> TextBuilder () Source #

Format a FiniteBits Integral type into hex nibbles.

heX :: (FiniteBits a, Integral a) => a -> TextBuilder () Source #

The UPPERCASED version of hex.

IEEE float formating

data FFormat Source #

Control the rendering of floating point numbers.

Constructors

Exponent

Scientific notation (e.g. 2.3e123).

Fixed

Standard decimal notation.

Generic

Use decimal notation for values between 0.1 and 9,999,999, and scientific notation otherwise.

double :: Double -> TextBuilder () Source #

Decimal encoding of an IEEE Double.

Using standard decimal notation for arguments whose absolute value lies between 0.1 and 9,999,999, and scientific notation otherwise.

doubleWith Source #

Arguments

:: FFormat 
-> Maybe Int

Number of decimal places to render.

-> Double 
-> TextBuilder () 

Format double-precision float using drisu3 with dragon4 fallback.

float :: Float -> TextBuilder () Source #

Decimal encoding of an IEEE Float.

Using standard decimal notation for arguments whose absolute value lies between 0.1 and 9,999,999, and scientific notation otherwise.

floatWith Source #

Arguments

:: FFormat 
-> Maybe Int

Number of decimal places to render.

-> Float 
-> TextBuilder () 

Format single-precision float using drisu3 with dragon4 fallback.

scientific :: Scientific -> TextBuilder () Source #

A Builder which renders a scientific number to full precision, using standard decimal notation for arguments whose absolute value lies between 0.1 and 9,999,999, and scientific notation otherwise.

scientificWith Source #

Arguments

:: FFormat 
-> Maybe Int

Number of decimal places to render.

-> Scientific 
-> TextBuilder () 

Like scientific but provides rendering options.

Builder helpers

paren :: TextBuilder () -> TextBuilder () Source #

add (...) to original builder.

parenWhen :: Bool -> TextBuilder () -> TextBuilder () Source #

Add "(..)" around builders when condition is met, otherwise add nothing.

This is useful when defining ShowT instances.

curly :: TextBuilder () -> TextBuilder () Source #

add {...} to original builder.

square :: TextBuilder () -> TextBuilder () Source #

add [...] to original builder.

angle :: TextBuilder () -> TextBuilder () Source #

add ... to original builder.

quotes :: TextBuilder () -> TextBuilder () Source #

add "..." to original builder.

squotes :: TextBuilder () -> TextBuilder () Source #

add ... to original builder.

colon :: TextBuilder () Source #

write an ASCII :

comma :: TextBuilder () Source #

write an ASCII ,

intercalateVec Source #

Arguments

:: Vec v a 
=> TextBuilder ()

the seperator

-> (a -> TextBuilder ())

value formatter

-> v a

value list

-> TextBuilder () 

Use separator to connect a vector of builders.

intercalateList Source #

Arguments

:: TextBuilder ()

the seperator

-> (a -> TextBuilder ())

value formatter

-> [a]

value vector

-> TextBuilder () 

Use separator to connect a list of builders.