Z-Data-0.8.3.0: Array, vector and text
Copyright(c) Dong Han 2017-2019
LicenseBSD
Maintainerwinterland1989@gmail.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Z.Data.Text.Print

Description

This module re-exports some UTF8 compatible textual builders from Builder.

We also provide a faster alternative to Show class, i.e. Print, which can be deriving using Generic. For example to use Print class:


import qualified Z.Data.Text.Print as T

data Foo = Bar Bytes | Qux Text Int deriving Generic
                                    deriving anyclass T.Print

Synopsis

Print class

class Print 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 Print

> toText (FooInt 3)
> "FooInt 3"

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

> toText (FooInt 3)
> "3"

Minimal complete definition

Nothing

Methods

toUTF8BuilderP :: Int -> a -> Builder () Source #

Convert data to Builder with precendence.

You should return a Builder writing in UTF8 encoding only, i.e.

Z.Data.Text.validateMaybe (Z.Data.Builder.build (toUTF8BuilderP p a)) /= Nothing

default toUTF8BuilderP :: (Generic a, GToText (Rep a)) => Int -> a -> Builder () Source #

Instances

Instances details
Print Bool Source # 
Instance details

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> Bool -> Builder () Source #

Print Char Source # 
Instance details

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> Char -> Builder () Source #

Print Double Source # 
Instance details

Defined in Z.Data.Text.Print

Print Float Source # 
Instance details

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> Float -> Builder () Source #

Print Int Source # 
Instance details

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> Int -> Builder () Source #

Print Int8 Source # 
Instance details

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> Int8 -> Builder () Source #

Print Int16 Source # 
Instance details

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> Int16 -> Builder () Source #

Print Int32 Source # 
Instance details

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> Int32 -> Builder () Source #

Print Int64 Source # 
Instance details

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> Int64 -> Builder () Source #

Print Integer Source # 
Instance details

Defined in Z.Data.Text.Print

Print Natural Source # 
Instance details

Defined in Z.Data.Text.Print

Print Ordering Source # 
Instance details

Defined in Z.Data.Text.Print

Print Word Source # 
Instance details

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> Word -> Builder () Source #

Print Word8 Source # 
Instance details

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> Word8 -> Builder () Source #

Print Word16 Source # 
Instance details

Defined in Z.Data.Text.Print

Print Word32 Source # 
Instance details

Defined in Z.Data.Text.Print

Print Word64 Source # 
Instance details

Defined in Z.Data.Text.Print

Print CallStack Source # 
Instance details

Defined in Z.Data.Text.Print

Print () Source # 
Instance details

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> () -> Builder () Source #

Print Version Source # 
Instance details

Defined in Z.Data.Text.Print

Print ExitCode Source # 
Instance details

Defined in Z.Data.Text.Print

Print CChar Source # 
Instance details

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> CChar -> Builder () Source #

Print CSChar Source # 
Instance details

Defined in Z.Data.Text.Print

Print CUChar Source # 
Instance details

Defined in Z.Data.Text.Print

Print CShort Source # 
Instance details

Defined in Z.Data.Text.Print

Print CUShort Source # 
Instance details

Defined in Z.Data.Text.Print

Print CInt Source # 
Instance details

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> CInt -> Builder () Source #

Print CUInt Source # 
Instance details

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> CUInt -> Builder () Source #

Print CLong Source # 
Instance details

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> CLong -> Builder () Source #

Print CULong Source # 
Instance details

Defined in Z.Data.Text.Print

Print CLLong Source # 
Instance details

Defined in Z.Data.Text.Print

Print CULLong Source # 
Instance details

Defined in Z.Data.Text.Print

Print CBool Source # 
Instance details

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> CBool -> Builder () Source #

Print CFloat Source # 
Instance details

Defined in Z.Data.Text.Print

Print CDouble Source # 
Instance details

Defined in Z.Data.Text.Print

Print CPtrdiff Source # 
Instance details

Defined in Z.Data.Text.Print

Print CSize Source # 
Instance details

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> CSize -> Builder () Source #

Print CWchar Source # 
Instance details

Defined in Z.Data.Text.Print

Print CSigAtomic Source # 
Instance details

Defined in Z.Data.Text.Print

Print CClock Source # 
Instance details

Defined in Z.Data.Text.Print

Print CTime Source # 
Instance details

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> CTime -> Builder () Source #

Print CUSeconds Source # 
Instance details

Defined in Z.Data.Text.Print

Print CSUSeconds Source # 
Instance details

Defined in Z.Data.Text.Print

Print CIntPtr Source # 
Instance details

Defined in Z.Data.Text.Print

Print CUIntPtr Source # 
Instance details

Defined in Z.Data.Text.Print

Print CIntMax Source # 
Instance details

Defined in Z.Data.Text.Print

Print CUIntMax Source # 
Instance details

Defined in Z.Data.Text.Print

Print SomeException Source # 
Instance details

Defined in Z.Data.Text.Print

Print Scientific Source # 
Instance details

Defined in Z.Data.Text.Print

Print ZonedTime Source #
YYYY-MM-DDTHH:MM:SS.SSSZ
Instance details

Defined in Z.Data.Text.Print

Print LocalTime Source #
YYYY-MM-DDTHH:MM:SS.SSSZ
Instance details

Defined in Z.Data.Text.Print

Print TimeOfDay Source #
HH:MM:SS.SSS
Instance details

Defined in Z.Data.Text.Print

Print CalendarDiffTime Source # 
Instance details

Defined in Z.Data.Text.Print

Print UTCTime Source #
YYYY-MM-DDTHH:MM:SS.SSSZ
Instance details

Defined in Z.Data.Text.Print

Print SystemTime Source # 
Instance details

Defined in Z.Data.Text.Print

Print NominalDiffTime Source # 
Instance details

Defined in Z.Data.Text.Print

Print DiffTime Source # 
Instance details

Defined in Z.Data.Text.Print

Print DayOfWeek Source # 
Instance details

Defined in Z.Data.Text.Print

Print Day Source #
YYYY-MM-DD
Instance details

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> Day -> Builder () Source #

Print CalendarDiffDays Source # 
Instance details

Defined in Z.Data.Text.Print

Print 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.Print

Methods

toUTF8BuilderP :: Int -> Text -> Builder () Source #

Print FlatIntSet Source # 
Instance details

Defined in Z.Data.Vector.FlatIntSet

Print Value Source # 
Instance details

Defined in Z.Data.JSON.Value

Methods

toUTF8BuilderP :: Int -> Value -> Builder () Source #

Print ConvertError Source # 
Instance details

Defined in Z.Data.JSON.Converter

Print HexBytes Source # 
Instance details

Defined in Z.Data.Vector.Hex

Print CBytes Source #

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

Escaping rule is same with String.

Instance details

Defined in Z.Data.CBytes

Print RegexOpts Source # 
Instance details

Defined in Z.Data.Text.Regex

Print Regex Source # 
Instance details

Defined in Z.Data.Text.Regex

Methods

toUTF8BuilderP :: Int -> Regex -> Builder () Source #

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

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> [a] -> Builder () Source #

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

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> Maybe a -> Builder () Source #

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

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> Ratio a -> Builder () Source #

Print (Ptr a) Source # 
Instance details

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> Ptr a -> Builder () Source #

Print (ForeignPtr a) Source # 
Instance details

Defined in Z.Data.Text.Print

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

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> Min a -> Builder () Source #

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

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> Max a -> Builder () Source #

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

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> First a -> Builder () Source #

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

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> Last a -> Builder () Source #

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

Defined in Z.Data.Text.Print

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

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> Identity a -> Builder () Source #

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

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> First a -> Builder () Source #

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

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> Last a -> Builder () Source #

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

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> Dual a -> Builder () Source #

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

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> NonEmpty a -> Builder () Source #

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

Defined in Z.Data.Text.Print

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

Defined in Z.Data.Text.Print

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

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> Array a -> Builder () Source #

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

Defined in Z.Data.Text.Print

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

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> Vector a -> Builder () Source #

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

Defined in Z.Data.Vector.FlatSet

Methods

toUTF8BuilderP :: Int -> FlatSet v -> Builder () Source #

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

Defined in Z.Data.Vector.FlatIntMap

Print (CPtr a) Source # 
Instance details

Defined in Z.Foreign.CPtr

Methods

toUTF8BuilderP :: Int -> CPtr a -> Builder () Source #

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

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> Either a b -> Builder () Source #

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

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> (a, b) -> Builder () Source #

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

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> Fixed a -> Builder () Source #

Print (Proxy a) Source # 
Instance details

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> Proxy a -> Builder () Source #

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

Defined in Z.Data.Text.Print

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

Defined in Z.Data.Vector.FlatMap

Methods

toUTF8BuilderP :: Int -> FlatMap k v -> Builder () Source #

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

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> (a, b, c) -> Builder () Source #

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

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> Const a b -> Builder () Source #

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

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> Tagged a b -> Builder () Source #

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

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> (a, b, c, d) -> Builder () Source #

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

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> Product f g a -> Builder () Source #

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

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> Sum f g a -> Builder () Source #

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

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> (a, b, c, d, e) -> Builder () Source #

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

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> Compose f g a -> Builder () Source #

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

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> (a, b, c, d, e, f) -> Builder () Source #

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

Defined in Z.Data.Text.Print

Methods

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

toText :: Print a => a -> Text Source #

Convert data to Text.

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

Convert data to String, faster show replacement.

toUTF8Builder :: Print a => a -> Builder () Source #

Convert data to Builder.

toUTF8Bytes :: Print a => a -> Bytes Source #

Convert data to Bytes in UTF8 encoding.

Basic UTF8 builders

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"

stringUTF8 :: String -> Builder () Source #

Turn String into Builder with UTF8 encoding

Illegal codepoints will be written as replacementChars.

This is different from writing string literals builders via OverloadedStrings, because string literals do not provide UTF8 guarantees.

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

charUTF8 :: Char -> Builder () Source #

Turn Char into Builder with UTF8 encoding

Illegal codepoints will be written as replacementChars.

string7 :: String -> Builder () Source #

Turn String into Builder with ASCII7 encoding

Codepoints beyond 'x7F' will be chopped.

char7 :: Char -> Builder () Source #

Turn Char into Builder with ASCII7 encoding

Codepoints beyond 'x7F' will be chopped.

text :: Text -> Builder () 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.

Numeric builders

Integral type formatting

data IFormat Source #

Integral formatting options.

Constructors

IFormat 

Fields

Instances

Instances details
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

data Padding Source #

Instances

Instances details
Enum Padding Source # 
Instance details

Defined in Z.Data.Builder.Numeric

Eq Padding Source # 
Instance details

Defined in Z.Data.Builder.Numeric

Methods

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

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

Ord Padding Source # 
Instance details

Defined in Z.Data.Builder.Numeric

Show Padding Source # 
Instance details

Defined in Z.Data.Builder.Numeric

Arbitrary Padding Source # 
Instance details

Defined in Z.Data.Builder.Numeric

CoArbitrary Padding Source # 
Instance details

Defined in Z.Data.Builder.Numeric

Methods

coarbitrary :: Padding -> Gen b -> Gen b #

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

int = intWith defaultIFormat

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

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

import Z.Data.Builder as B

> B.buildText $ B.intWith defaultIFormat  (12345 :: Int)
"12345"
> B.buildText $ B.intWith defaultIFormat{width=10, padding=RightSpacePadding} (12345 :: Int)
"12345     "
> B.buildText $ B.intWith defaultIFormat{width=10, padding=ZeroPadding} (12345 :: Int)
"0000012345"

integer :: Integer -> Builder () Source #

Format a Integer into decimal ASCII digits.

Fixded size hexidecimal formatting

hex :: forall a. (FiniteBits a, Integral a) => a -> Builder () Source #

Format a FiniteBits Integral type into hex nibbles.

import Z.Data.Builder as B
import Z.Data.Text    as T
import Data.Word
import Data.Int

> T.validate . B.build $ B.hex (125 :: Int8)
"7d"
> T.validate . B.build $ B.hex (-1 :: Int8)
"ff"
> T.validate . B.build $ B.hex (125 :: Word16)
"007d"

hexUpper :: forall a. (FiniteBits a, Integral a) => a -> Builder () 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 -> Builder () 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 
-> Builder () 

Format double-precision float using drisu3 with dragon4 fallback.

float :: Float -> Builder () 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 
-> Builder () 

Format single-precision float using drisu3 with dragon4 fallback.

scientific :: Scientific -> Builder () 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.

scientific' :: Scientific -> Builder () Source #

This builder try to avoid scientific notation when 0 <= exponent < 16.

scientificWith Source #

Arguments

:: FFormat 
-> Maybe Int

Number of decimal places to render.

-> Scientific 
-> Builder () 

Like scientific but provides rendering options.

Helpers

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

add (...) to original builder.

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

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

This is useful when defining Print instances.

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

add {...} to original builder.

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

add [...] to original builder.

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

add <...> to original builder.

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

add "..." to original builder.

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

add '...' to original builder.

colon :: Builder () Source #

write an ASCII :

comma :: Builder () Source #

write an ASCII ,

intercalateVec Source #

Arguments

:: Vec v a 
=> Builder ()

the seperator

-> (a -> Builder ())

value formatter

-> v a

value vector

-> Builder () 

Use separator to connect a vector of builders.

import Z.Data.Builder as B
import Z.Data.Text    as T
import Z.Data.Vector  as V

> T.validate . B.build $ B.intercalateVec "," B.int (V.pack [1,2,3,4] :: V.PrimVector Int)
"1,2,3,4"

intercalateList Source #

Arguments

:: Builder ()

the seperator

-> (a -> Builder ())

value formatter

-> [a]

value list

-> Builder () 

Use separator to connect list of builders.

import Z.Data.Builder as B
import Z.Data.Text    as T
import Z.Data.Vector  as V

T.validate . B.build $ B.intercalateList "," B.int ([1,2,3,4] :: [Int])
"1,2,3,4"