Copyright | (c) Dong Han 2017-2019 |
---|---|
License | BSD |
Maintainer | winterland1989@gmail.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- class ToText a where
- toTextBuilder :: Int -> a -> TextBuilder ()
- toText :: ToText a => a -> Text
- toBuilder :: ToText a => a -> Builder ()
- toBytes :: ToText a => a -> Bytes
- toString :: ToText a => a -> String
- newtype Str = Str {}
- data TextBuilder a
- getBuilder :: TextBuilder a -> Builder a
- unsafeFromBuilder :: Builder a -> TextBuilder a
- buildText :: TextBuilder a -> Text
- stringUTF8 :: String -> TextBuilder ()
- charUTF8 :: Char -> TextBuilder ()
- string7 :: String -> TextBuilder ()
- char7 :: Char -> TextBuilder ()
- text :: Text -> TextBuilder ()
- data IFormat = IFormat {}
- defaultIFormat :: IFormat
- data Padding
- int :: (Integral a, Bounded a) => a -> TextBuilder ()
- intWith :: (Integral a, Bounded a) => IFormat -> a -> TextBuilder ()
- integer :: Integer -> TextBuilder ()
- hex :: (FiniteBits a, Integral a) => a -> TextBuilder ()
- heX :: (FiniteBits a, Integral a) => a -> TextBuilder ()
- data FFormat
- double :: Double -> TextBuilder ()
- doubleWith :: FFormat -> Maybe Int -> Double -> TextBuilder ()
- float :: Float -> TextBuilder ()
- floatWith :: FFormat -> Maybe Int -> Float -> TextBuilder ()
- scientific :: Scientific -> TextBuilder ()
- scientificWith :: FFormat -> Maybe Int -> Scientific -> TextBuilder ()
- paren :: TextBuilder () -> TextBuilder ()
- parenWhen :: Bool -> TextBuilder () -> TextBuilder ()
- curly :: TextBuilder () -> TextBuilder ()
- square :: TextBuilder () -> TextBuilder ()
- angle :: TextBuilder () -> TextBuilder ()
- quotes :: TextBuilder () -> TextBuilder ()
- squotes :: TextBuilder () -> TextBuilder ()
- colon :: TextBuilder ()
- comma :: TextBuilder ()
- intercalateVec :: Vec v a => TextBuilder () -> (a -> TextBuilder ()) -> v a -> TextBuilder ()
- intercalateList :: TextBuilder () -> (a -> TextBuilder ()) -> [a] -> TextBuilder ()
ToText class
Nothing
toTextBuilder :: Int -> a -> TextBuilder () Source #
toTextBuilder :: (Generic a, GToText (Rep a)) => Int -> a -> TextBuilder () Source #
Instances
Str newtype
Newtype wrapper for [Char]
to provide textual instances.
To encourage using Text
as the textual representation, we didn't provide special
treatment to differentiate instances between [a]
and [Char]
in various places.
This newtype is therefore to provide instances similar to T.Text
, in case you really
need to wrap a String
.
Instances
Eq Str Source # | |
Data Str Source # | |
Defined in Std.Data.TextBuilder gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Str -> c Str # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Str # dataTypeOf :: Str -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Str) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Str) # gmapT :: (forall b. Data b => b -> b) -> Str -> Str # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Str -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Str -> r # gmapQ :: (forall d. Data d => d -> u) -> Str -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Str -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Str -> m Str # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Str -> m Str # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Str -> m Str # | |
Ord Str Source # | |
Read Str Source # | |
Show Str Source # | |
Generic Str Source # | |
ToText Str Source # | |
Defined in Std.Data.TextBuilder toTextBuilder :: Int -> Str -> TextBuilder () Source # | |
FromValue Str Source # | |
EncodeJSON Str Source # | |
Defined in Std.Data.JSON.Base encodeJSON :: Str -> Builder () Source # | |
ToValue Str Source # | |
type Rep Str Source # | |
Defined in Std.Data.TextBuilder |
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 asx00
.xD800
~xDFFF
will be replaced by replacement char.
Instances
getBuilder :: TextBuilder a -> Builder a Source #
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 replacementChar
s. 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 replacementChar
s.
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 #
Numeric builders
Integral type formatting
Integral formatting options.
defaultIFormat :: IFormat Source #
defaultIFormat = IFormat 0 NoPadding False
Instances
Enum Padding Source # | |
Eq Padding Source # | |
Ord Padding Source # | |
Show Padding Source # | |
Arbitrary Padding Source # | |
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
Control the rendering of floating point numbers.
Exponent | Scientific notation (e.g. |
Fixed | Standard decimal notation. |
Generic | Use decimal notation for values between |
Instances
Enum FFormat Source # | |
Read FFormat Source # | |
Show FFormat Source # | |
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.
:: 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.
:: 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.
:: 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 ToText
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 ,
:: Vec v a | |
=> TextBuilder () | the seperator |
-> (a -> TextBuilder ()) | value formatter |
-> v a | value list |
-> TextBuilder () |
Use separator to connect a vector of builders.
:: TextBuilder () | the seperator |
-> (a -> TextBuilder ()) | value formatter |
-> [a] | value vector |
-> TextBuilder () |
Use separator to connect a list of builders.