Z-YAML-0.1.0.0: YAML tools
Copyright(c) Dong Han 2020
LicenseBSD
Maintainerwinterland1989@gmail.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Z.Data.YAML

Description

Simple YAML codec using libYAML and JSON's FromValue / ToValue utilities. The design choice to make things as simple as possible since YAML is a complex format, there're some limitations using this approach:

  • Does not support complex keys.
  • Dose not support multiple doucments in one file.

import           GHC.Generics
import qualified Z.Data.YAML as YAML
import qualified Z.Data.Text as T

data Person = Person
    { name  :: T.Text
    , age   :: Int
    , magic :: Bool
    }
  deriving (Show, Generic)
  deriving anyclass (YAML.FromValue, YAML.ToValue)

> YAML.decode @[Person] "- name: Erik Weiszn  age: 52n  magic: Truen"
> Right [Person {name = "Erik Weisz", age = 52, magic = True}]
Synopsis

decode and encode using YAML

decodeFromFile :: (HasCallStack, FromValue a) => CBytes -> IO a Source #

Decode a FromValue instance from file.

decode :: FromValue a => Bytes -> Either YAMLParseException a Source #

Decode a FromValue instance from bytes.

encodeToFile :: (HasCallStack, ToValue a) => YAMLFormatOpts -> CBytes -> a -> IO () Source #

Encode a ToValue instance to file.

encode :: (HasCallStack, ToValue a) => YAMLFormatOpts -> a -> Text Source #

Encode a ToValue instance as UTF8 text.

encodeValue :: HasCallStack => YAMLFormatOpts -> Value -> Text Source #

Encode a Value as UTF8 text.

streaming parser and builder

buildSingleDocument :: HasCallStack => Sink Event -> Value -> IO () Source #

Write a value as a YAML document stream.

Since: 0.11.2.0

buildValue :: HasCallStack => Sink Event -> Value -> IO () Source #

Write a value as a list of Events(without document start/end, stream start/end).

Since: 0.11.2.0

re-exports

class FromValue a where #

Minimal complete definition

Nothing

Methods

fromValue :: Value -> Converter a #

Instances

Instances details
FromValue Bool 
Instance details

Defined in Z.Data.JSON.Base

FromValue Char 
Instance details

Defined in Z.Data.JSON.Base

FromValue Double 
Instance details

Defined in Z.Data.JSON.Base

FromValue Float 
Instance details

Defined in Z.Data.JSON.Base

FromValue Int 
Instance details

Defined in Z.Data.JSON.Base

FromValue Int8 
Instance details

Defined in Z.Data.JSON.Base

FromValue Int16 
Instance details

Defined in Z.Data.JSON.Base

FromValue Int32 
Instance details

Defined in Z.Data.JSON.Base

FromValue Int64 
Instance details

Defined in Z.Data.JSON.Base

FromValue Integer

This instance includes a bounds check to prevent maliciously large inputs to fill up the memory of the target system. You can newtype Scientific and provide your own instance using withScientific if you want to allow larger inputs.

Instance details

Defined in Z.Data.JSON.Base

FromValue Natural 
Instance details

Defined in Z.Data.JSON.Base

FromValue Ordering 
Instance details

Defined in Z.Data.JSON.Base

FromValue Word 
Instance details

Defined in Z.Data.JSON.Base

FromValue Word8 
Instance details

Defined in Z.Data.JSON.Base

FromValue Word16 
Instance details

Defined in Z.Data.JSON.Base

FromValue Word32 
Instance details

Defined in Z.Data.JSON.Base

FromValue Word64 
Instance details

Defined in Z.Data.JSON.Base

FromValue () 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter () #

FromValue Version 
Instance details

Defined in Z.Data.JSON.Base

FromValue Scientific

Note this instance doesn't reject large input

Instance details

Defined in Z.Data.JSON.Base

FromValue ByteArray 
Instance details

Defined in Z.Data.JSON.Base

FromValue CUIntMax 
Instance details

Defined in Z.Data.JSON.Base

FromValue CIntMax 
Instance details

Defined in Z.Data.JSON.Base

FromValue CUIntPtr 
Instance details

Defined in Z.Data.JSON.Base

FromValue CIntPtr 
Instance details

Defined in Z.Data.JSON.Base

FromValue CSUSeconds 
Instance details

Defined in Z.Data.JSON.Base

FromValue CUSeconds 
Instance details

Defined in Z.Data.JSON.Base

FromValue CTime 
Instance details

Defined in Z.Data.JSON.Base

FromValue CClock 
Instance details

Defined in Z.Data.JSON.Base

FromValue CSigAtomic 
Instance details

Defined in Z.Data.JSON.Base

FromValue CWchar 
Instance details

Defined in Z.Data.JSON.Base

FromValue CSize 
Instance details

Defined in Z.Data.JSON.Base

FromValue CPtrdiff 
Instance details

Defined in Z.Data.JSON.Base

FromValue CDouble 
Instance details

Defined in Z.Data.JSON.Base

FromValue CFloat 
Instance details

Defined in Z.Data.JSON.Base

FromValue CBool 
Instance details

Defined in Z.Data.JSON.Base

FromValue CULLong 
Instance details

Defined in Z.Data.JSON.Base

FromValue CLLong 
Instance details

Defined in Z.Data.JSON.Base

FromValue CULong 
Instance details

Defined in Z.Data.JSON.Base

FromValue CLong 
Instance details

Defined in Z.Data.JSON.Base

FromValue CUInt 
Instance details

Defined in Z.Data.JSON.Base

FromValue CInt 
Instance details

Defined in Z.Data.JSON.Base

FromValue CUShort 
Instance details

Defined in Z.Data.JSON.Base

FromValue CShort 
Instance details

Defined in Z.Data.JSON.Base

FromValue CUChar 
Instance details

Defined in Z.Data.JSON.Base

FromValue CSChar 
Instance details

Defined in Z.Data.JSON.Base

FromValue CChar 
Instance details

Defined in Z.Data.JSON.Base

FromValue CBytes

JSON instances check if CBytes is proper UTF8 encoded, if it is, decode/encode it as Text, otherwise as Bytes.

> encodeText ("hello" :: CBytes)
""hello""
> encodeText ("hello\NUL" :: CBytes)     -- \NUL is encoded as C0 80
"[104,101,108,108,111,192,128]"
Instance details

Defined in Z.Data.CBytes

FromValue Value 
Instance details

Defined in Z.Data.JSON.Base

FromValue FlatIntSet 
Instance details

Defined in Z.Data.JSON.Base

FromValue Text 
Instance details

Defined in Z.Data.JSON.Base

FromValue PathStyle 
Instance details

Defined in Z.IO.FileSystem.FilePath

FromValue DirEntType 
Instance details

Defined in Z.IO.UV.FFI

FromValue UVTimeSpec 
Instance details

Defined in Z.IO.UV.FFI

FromValue FStat 
Instance details

Defined in Z.IO.UV.FFI

FromValue AccessResult 
Instance details

Defined in Z.IO.UV.FFI

FromValue UID 
Instance details

Defined in Z.IO.UV.FFI

FromValue GID 
Instance details

Defined in Z.IO.UV.FFI

FromValue ProcessOptions 
Instance details

Defined in Z.IO.UV.FFI

FromValue ProcessStdStream 
Instance details

Defined in Z.IO.UV.FFI

FromValue TimeVal 
Instance details

Defined in Z.IO.UV.FFI

FromValue ResUsage 
Instance details

Defined in Z.IO.UV.FFI

FromValue PID 
Instance details

Defined in Z.IO.UV.FFI

FromValue OSName 
Instance details

Defined in Z.IO.UV.FFI

FromValue PassWD 
Instance details

Defined in Z.IO.UV.FFI

FromValue CPUInfo 
Instance details

Defined in Z.IO.UV.FFI

FromValue SocketAddr 
Instance details

Defined in Z.IO.Network.SocketAddr

FromValue IPv4 
Instance details

Defined in Z.IO.Network.SocketAddr

FromValue IPv6 
Instance details

Defined in Z.IO.Network.SocketAddr

FromValue PortNumber 
Instance details

Defined in Z.IO.Network.SocketAddr

FromValue ExitCode 
Instance details

Defined in Z.Data.JSON.Base

FromValue Tag Source # 
Instance details

Defined in Z.Data.YAML.FFI

FromValue Mark Source # 
Instance details

Defined in Z.Data.YAML.FFI

FromValue MarkedEvent Source # 
Instance details

Defined in Z.Data.YAML.FFI

FromValue Event Source # 
Instance details

Defined in Z.Data.YAML.FFI

FromValue a => FromValue [a] 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter [a] #

FromValue a => FromValue (Maybe a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter (Maybe a) #

(FromValue a, Integral a) => FromValue (Ratio a)

This instance includes a bounds check to prevent maliciously large inputs to fill up the memory of the target system. You can newtype Ratio and provide your own instance using withScientific if you want to allow larger inputs.

Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter (Ratio a) #

FromValue a => FromValue (FlatIntMap a) 
Instance details

Defined in Z.Data.JSON.Base

(Ord a, FromValue a) => FromValue (FlatSet a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter (FlatSet a) #

FromValue a => FromValue (Vector a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter (Vector a) #

(Prim a, FromValue a) => FromValue (PrimVector a) 
Instance details

Defined in Z.Data.JSON.Base

FromValue a => FromValue (Array a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter (Array a) #

FromValue a => FromValue (SmallArray a) 
Instance details

Defined in Z.Data.JSON.Base

(Prim a, FromValue a) => FromValue (PrimArray a) 
Instance details

Defined in Z.Data.JSON.Base

FromValue a => FromValue (Min a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter (Min a) #

FromValue a => FromValue (Max a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter (Max a) #

FromValue a => FromValue (First a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter (First a) #

FromValue a => FromValue (Last a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter (Last a) #

FromValue a => FromValue (WrappedMonoid a) 
Instance details

Defined in Z.Data.JSON.Base

FromValue a => FromValue (Identity a) 
Instance details

Defined in Z.Data.JSON.Base

FromValue a => FromValue (First a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter (First a) #

FromValue a => FromValue (Last a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter (Last a) #

FromValue a => FromValue (Dual a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter (Dual a) #

FromValue a => FromValue (NonEmpty a) 
Instance details

Defined in Z.Data.JSON.Base

(Eq a, Hashable a, FromValue a) => FromValue (HashSet a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter (HashSet a) #

(FromValue a, FromValue b) => FromValue (Either a b) 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter (Either a b) #

(FromValue a, FromValue b) => FromValue (a, b) 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter (a, b) #

FromValue a => FromValue (FlatMap Text a)

default instance prefer later key

Instance details

Defined in Z.Data.JSON.Base

(PrimUnlifted a, FromValue a) => FromValue (UnliftedArray a) 
Instance details

Defined in Z.Data.JSON.Base

HasResolution a => FromValue (Fixed a)

This instance includes a bounds check to prevent maliciously large inputs to fill up the memory of the target system. You can newtype Fixed and provide your own instance using withScientific if you want to allow larger inputs.

Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter (Fixed a) #

FromValue (Proxy a)

Use Null as Proxy a

Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter (Proxy a) #

FromValue a => FromValue (HashMap Text a)

default instance prefer later key

Instance details

Defined in Z.Data.JSON.Base

(FromValue a, FromValue b, FromValue c) => FromValue (a, b, c) 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter (a, b, c) #

FromValue a => FromValue (Const a b) 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter (Const a b) #

FromValue b => FromValue (Tagged a b) 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter (Tagged a b) #

(FromValue a, FromValue b, FromValue c, FromValue d) => FromValue (a, b, c, d) 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter (a, b, c, d) #

(FromValue (f a), FromValue (g a)) => FromValue (Product f g a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter (Product f g a) #

(FromValue (f a), FromValue (g a), FromValue a) => FromValue (Sum f g a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter (Sum f g a) #

(FromValue a, FromValue b, FromValue c, FromValue d, FromValue e) => FromValue (a, b, c, d, e) 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter (a, b, c, d, e) #

FromValue (f (g a)) => FromValue (Compose f g a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter (Compose f g a) #

(FromValue a, FromValue b, FromValue c, FromValue d, FromValue e, FromValue f) => FromValue (a, b, c, d, e, f) 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter (a, b, c, d, e, f) #

(FromValue a, FromValue b, FromValue c, FromValue d, FromValue e, FromValue f, FromValue g) => FromValue (a, b, c, d, e, f, g) 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter (a, b, c, d, e, f, g) #

class ToValue a where #

Typeclass for converting to JSON Value.

Minimal complete definition

Nothing

Methods

toValue :: a -> Value #

Instances

Instances details
ToValue Bool 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Bool -> Value #

ToValue Char 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Char -> Value #

ToValue Double 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Double -> Value #

ToValue Float 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Float -> Value #

ToValue Int 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Int -> Value #

ToValue Int8 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Int8 -> Value #

ToValue Int16 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Int16 -> Value #

ToValue Int32 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Int32 -> Value #

ToValue Int64 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Int64 -> Value #

ToValue Integer 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Integer -> Value #

ToValue Natural 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Natural -> Value #

ToValue Ordering 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Ordering -> Value #

ToValue Word 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Word -> Value #

ToValue Word8 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Word8 -> Value #

ToValue Word16 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Word16 -> Value #

ToValue Word32 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Word32 -> Value #

ToValue Word64 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Word64 -> Value #

ToValue () 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: () -> Value #

ToValue Version 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Version -> Value #

ToValue Scientific 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Scientific -> Value #

ToValue ByteArray 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: ByteArray -> Value #

ToValue CUIntMax 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CUIntMax -> Value #

ToValue CIntMax 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CIntMax -> Value #

ToValue CUIntPtr 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CUIntPtr -> Value #

ToValue CIntPtr 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CIntPtr -> Value #

ToValue CSUSeconds 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CSUSeconds -> Value #

ToValue CUSeconds 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CUSeconds -> Value #

ToValue CTime 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CTime -> Value #

ToValue CClock 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CClock -> Value #

ToValue CSigAtomic 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CSigAtomic -> Value #

ToValue CWchar 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CWchar -> Value #

ToValue CSize 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CSize -> Value #

ToValue CPtrdiff 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CPtrdiff -> Value #

ToValue CDouble 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CDouble -> Value #

ToValue CFloat 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CFloat -> Value #

ToValue CBool 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CBool -> Value #

ToValue CULLong 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CULLong -> Value #

ToValue CLLong 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CLLong -> Value #

ToValue CULong 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CULong -> Value #

ToValue CLong 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CLong -> Value #

ToValue CUInt 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CUInt -> Value #

ToValue CInt 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CInt -> Value #

ToValue CUShort 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CUShort -> Value #

ToValue CShort 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CShort -> Value #

ToValue CUChar 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CUChar -> Value #

ToValue CSChar 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CSChar -> Value #

ToValue CChar 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CChar -> Value #

ToValue CBytes 
Instance details

Defined in Z.Data.CBytes

Methods

toValue :: CBytes -> Value #

ToValue Value 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Value -> Value #

ToValue FlatIntSet 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: FlatIntSet -> Value #

ToValue Text 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Text -> Value #

ToValue PathStyle 
Instance details

Defined in Z.IO.FileSystem.FilePath

Methods

toValue :: PathStyle -> Value #

ToValue DirEntType 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: DirEntType -> Value #

ToValue UVTimeSpec 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: UVTimeSpec -> Value #

ToValue FStat 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: FStat -> Value #

ToValue AccessResult 
Instance details

Defined in Z.IO.UV.FFI

ToValue UID 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: UID -> Value #

ToValue GID 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: GID -> Value #

ToValue ProcessOptions 
Instance details

Defined in Z.IO.UV.FFI

ToValue ProcessStdStream 
Instance details

Defined in Z.IO.UV.FFI

ToValue TimeVal 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: TimeVal -> Value #

ToValue ResUsage 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: ResUsage -> Value #

ToValue PID 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: PID -> Value #

ToValue OSName 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: OSName -> Value #

ToValue PassWD 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: PassWD -> Value #

ToValue CPUInfo 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: CPUInfo -> Value #

ToValue SocketAddr 
Instance details

Defined in Z.IO.Network.SocketAddr

Methods

toValue :: SocketAddr -> Value #

ToValue IPv4 
Instance details

Defined in Z.IO.Network.SocketAddr

Methods

toValue :: IPv4 -> Value #

ToValue IPv6 
Instance details

Defined in Z.IO.Network.SocketAddr

Methods

toValue :: IPv6 -> Value #

ToValue PortNumber 
Instance details

Defined in Z.IO.Network.SocketAddr

Methods

toValue :: PortNumber -> Value #

ToValue ExitCode 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: ExitCode -> Value #

ToValue Tag Source # 
Instance details

Defined in Z.Data.YAML.FFI

Methods

toValue :: Tag -> Value #

ToValue Mark Source # 
Instance details

Defined in Z.Data.YAML.FFI

Methods

toValue :: Mark -> Value #

ToValue MarkedEvent Source # 
Instance details

Defined in Z.Data.YAML.FFI

Methods

toValue :: MarkedEvent -> Value #

ToValue Event Source # 
Instance details

Defined in Z.Data.YAML.FFI

Methods

toValue :: Event -> Value #

ToValue a => ToValue [a] 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: [a] -> Value #

ToValue a => ToValue (Maybe a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Maybe a -> Value #

(ToValue a, Integral a) => ToValue (Ratio a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Ratio a -> Value #

ToValue a => ToValue (FlatIntMap a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: FlatIntMap a -> Value #

ToValue a => ToValue (FlatSet a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: FlatSet a -> Value #

ToValue a => ToValue (Vector a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Vector a -> Value #

(Prim a, ToValue a) => ToValue (PrimVector a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: PrimVector a -> Value #

ToValue a => ToValue (Array a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Array a -> Value #

ToValue a => ToValue (SmallArray a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: SmallArray a -> Value #

(Prim a, ToValue a) => ToValue (PrimArray a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: PrimArray a -> Value #

ToValue a => ToValue (Min a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Min a -> Value #

ToValue a => ToValue (Max a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Max a -> Value #

ToValue a => ToValue (First a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: First a -> Value #

ToValue a => ToValue (Last a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Last a -> Value #

ToValue a => ToValue (WrappedMonoid a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: WrappedMonoid a -> Value #

ToValue a => ToValue (Identity a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Identity a -> Value #

ToValue a => ToValue (First a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: First a -> Value #

ToValue a => ToValue (Last a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Last a -> Value #

ToValue a => ToValue (Dual a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Dual a -> Value #

ToValue a => ToValue (NonEmpty a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: NonEmpty a -> Value #

ToValue a => ToValue (HashSet a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: HashSet a -> Value #

(ToValue a, ToValue b) => ToValue (Either a b) 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Either a b -> Value #

(ToValue a, ToValue b) => ToValue (a, b) 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: (a, b) -> Value #

ToValue a => ToValue (FlatMap Text a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: FlatMap Text a -> Value #

(PrimUnlifted a, ToValue a) => ToValue (UnliftedArray a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: UnliftedArray a -> Value #

HasResolution a => ToValue (Fixed a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Fixed a -> Value #

ToValue (Proxy a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Proxy a -> Value #

ToValue a => ToValue (HashMap Text a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: HashMap Text a -> Value #

(ToValue a, ToValue b, ToValue c) => ToValue (a, b, c) 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: (a, b, c) -> Value #

ToValue a => ToValue (Const a b) 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Const a b -> Value #

ToValue b => ToValue (Tagged a b) 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Tagged a b -> Value #

(ToValue a, ToValue b, ToValue c, ToValue d) => ToValue (a, b, c, d) 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: (a, b, c, d) -> Value #

(ToValue (f a), ToValue (g a)) => ToValue (Product f g a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Product f g a -> Value #

(ToValue (f a), ToValue (g a), ToValue a) => ToValue (Sum f g a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Sum f g a -> Value #

(ToValue a, ToValue b, ToValue c, ToValue d, ToValue e) => ToValue (a, b, c, d, e) 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: (a, b, c, d, e) -> Value #

ToValue (f (g a)) => ToValue (Compose f g a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Compose f g a -> Value #

(ToValue a, ToValue b, ToValue c, ToValue d, ToValue e, ToValue f) => ToValue (a, b, c, d, e, f) 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: (a, b, c, d, e, f) -> Value #

(ToValue a, ToValue b, ToValue c, ToValue d, ToValue e, ToValue f, ToValue g) => ToValue (a, b, c, d, e, f, g) 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: (a, b, c, d, e, f, g) -> Value #

data Value #

A JSON value represented as a Haskell value.

The Object's payload is a key-value vector instead of a map, which parsed directly from JSON document. This design choice has following advantages:

  • Allow different strategies handling duplicated keys.
  • Allow different Map type to do further parsing, e.g. FlatMap
  • Roundtrip without touching the original key-value order.
  • Save time if constructing map is not neccessary, e.g. using a linear scan to find a key if only that key is needed.

Instances

Instances details
Eq Value 
Instance details

Defined in Z.Data.JSON.Value

Methods

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

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

Show Value 
Instance details

Defined in Z.Data.JSON.Value

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

Generic Value 
Instance details

Defined in Z.Data.JSON.Value

Associated Types

type Rep Value :: Type -> Type #

Methods

from :: Value -> Rep Value x #

to :: Rep Value x -> Value #

Arbitrary Value 
Instance details

Defined in Z.Data.JSON.Value

Methods

arbitrary :: Gen Value #

shrink :: Value -> [Value] #

ToValue Value 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Value -> Value #

EncodeJSON Value 
Instance details

Defined in Z.Data.JSON.Base

Methods

encodeJSON :: Value -> Builder () #

FromValue Value 
Instance details

Defined in Z.Data.JSON.Base

ShowT Value 
Instance details

Defined in Z.Data.JSON.Value

Methods

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

NFData Value 
Instance details

Defined in Z.Data.JSON.Value

Methods

rnf :: Value -> () #

type Rep Value 
Instance details

Defined in Z.Data.JSON.Value