Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Synopsis
- newtype Enc = Enc {}
- encoding :: Encoding -> Enc
- value :: Value -> Enc
- emptyArray :: Enc
- emptyObject :: Enc
- text :: Text -> Enc
- lazyText :: Text -> Enc
- string :: String -> Enc
- nullOr :: (a -> Enc) -> Maybe a -> Enc
- list :: (a -> Enc) -> [a] -> Enc
- nonEmpty :: (a -> Enc) -> NonEmpty a -> Enc
- object :: Foldable t => t (Text, Enc) -> Enc
- data Choice = Choice Text Enc
- choice :: (from -> Choice) -> from -> Enc
- singleChoice :: Text -> Enc -> Enc
- map :: forall k v. Coercible k Text => (v -> Enc) -> Map k v -> Enc
- keyMap :: (v -> Enc) -> KeyMap v -> Enc
- null :: Enc
- bool :: Bool -> Enc
- integer :: Integer -> Enc
- scientific :: Scientific -> Enc
- natural :: Natural -> Enc
- int :: Int -> Enc
- int64 :: Int64 -> Enc
- utcTime :: UTCTime -> Enc
- class IntegerLiteral a where
- integerLiteral :: Integer -> a
- class RationalLiteral a where
- rationalLiteral :: Rational -> a
- newtype NumLiteralOnly (sym :: Symbol) num = NumLiteralOnly num
Documentation
A JSON encoder.
It is faster than going through Value
, because Encoding
is just a wrapper around a Bytes.Builder
.
But the aeson
interface for Encoding
is extremely bad, so let’s build a better one.
Instances
IsString Enc Source # | You can create an |
Defined in Json.Enc fromString :: String -> Enc # | |
Num Enc Source # | |
Fractional Enc Source # | |
IntegerLiteral Enc Source # | You can create an |
RationalLiteral Enc Source # | You can create an ATTN: Bear in mind that this will crash on repeating rationals, so only use for literals in code! |
emptyArray :: Enc Source #
Encode an empty Array
emptyObject :: Enc Source #
Encode an empty Object
choice :: (from -> Choice) -> from -> Enc Source #
Encode a sum type as a Choice
, an object with a tag
/value
pair,
which is the conventional json sum type representation in our codebase.
foo :: Maybe Text -> Enc foo = choice $ case Nothing -> Choice "no" emptyObject () Just t -> Choice "yes" text t ex = foo Nothing == "{"tag": "no", "value": {}}" ex2 = foo (Just "hi") == "{"tag": "yes", "value": "hi"}"
scientific :: Scientific -> Enc Source #
Encode a Scientific
as Number
.
utcTime :: UTCTime -> Enc Source #
Encode UTCTime as Value
, as an ISO8601 timestamp with timezone (yyyy-mm-ddThh:mm:ss[.sss]Z
)
class IntegerLiteral a where Source #
Implement this class if you want your type to only implement the part of Num
that allows creating them from Integer-literals, then derive Num via NumLiteralOnly
:
data Foo = Foo Integer deriving (Num) via (NumLiteralOnly Foo Foo) instance IntegerLiteral Foo where integerLiteral i = Foo i
integerLiteral :: Integer -> a Source #
class RationalLiteral a where Source #
The same as IntegerLiteral
but for floating point literals.
rationalLiteral :: Rational -> a Source #
newtype NumLiteralOnly (sym :: Symbol) num Source #
Helper class for deriving (Num) via …
, implements only literal syntax for integer and floating point numbers,
and throws descriptive runtime errors for any other methods in Num
.
See IntegerLiteral
and RationalLiteral
for examples.
NumLiteralOnly num |
Instances
(IntegerLiteral num, KnownSymbol sym) => Num (NumLiteralOnly sym num) Source # | |
Defined in Json.Enc (+) :: NumLiteralOnly sym num -> NumLiteralOnly sym num -> NumLiteralOnly sym num # (-) :: NumLiteralOnly sym num -> NumLiteralOnly sym num -> NumLiteralOnly sym num # (*) :: NumLiteralOnly sym num -> NumLiteralOnly sym num -> NumLiteralOnly sym num # negate :: NumLiteralOnly sym num -> NumLiteralOnly sym num # abs :: NumLiteralOnly sym num -> NumLiteralOnly sym num # signum :: NumLiteralOnly sym num -> NumLiteralOnly sym num # fromInteger :: Integer -> NumLiteralOnly sym num # | |
(IntegerLiteral num, RationalLiteral num, KnownSymbol sym) => Fractional (NumLiteralOnly sym num) Source # | |
Defined in Json.Enc (/) :: NumLiteralOnly sym num -> NumLiteralOnly sym num -> NumLiteralOnly sym num # recip :: NumLiteralOnly sym num -> NumLiteralOnly sym num # fromRational :: Rational -> NumLiteralOnly sym num # |