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 Weisz\n  age: 52\n  magic: True\n"
> 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.

decodeValueFromFile :: HasCallStack => CBytes -> IO Value Source #

Decode a Value from file.

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

Decode a FromValue instance from bytes.

decodeValue :: Bytes -> Either YAMLParseException Value Source #

Decode a Value from bytes.

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

Encode a ToValue instance to file.

encodeValueToFile :: HasCallStack => YAMLFormatOpts -> CBytes -> Value -> IO () Source #

Encode a Value 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.

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

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

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

Methods

fromValue :: Value -> Converter Bool #

FromValue Char 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter Char #

FromValue Double 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter Double #

FromValue Float 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter Float #

FromValue Int 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter Int #

FromValue Int8 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter Int8 #

FromValue Int16 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter Int16 #

FromValue Int32 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter Int32 #

FromValue Int64 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter Int64 #

FromValue Integer 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter Integer #

FromValue Natural 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter Natural #

FromValue Ordering 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter Ordering #

FromValue Word 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter Word #

FromValue Word8 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter Word8 #

FromValue Word16 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter Word16 #

FromValue Word32 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter Word32 #

FromValue Word64 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter Word64 #

FromValue () 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter () #

FromValue Version 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter Version #

FromValue ExitCode 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter ExitCode #

FromValue CChar 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter CChar #

FromValue CSChar 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter CSChar #

FromValue CUChar 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter CUChar #

FromValue CShort 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter CShort #

FromValue CUShort 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter CUShort #

FromValue CInt 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter CInt #

FromValue CUInt 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter CUInt #

FromValue CLong 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter CLong #

FromValue CULong 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter CULong #

FromValue CLLong 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter CLLong #

FromValue CULLong 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter CULLong #

FromValue CBool 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter CBool #

FromValue CFloat 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter CFloat #

FromValue CDouble 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter CDouble #

FromValue CPtrdiff 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter CPtrdiff #

FromValue CSize 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter CSize #

FromValue CWchar 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter CWchar #

FromValue CSigAtomic 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter CSigAtomic #

FromValue CClock 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter CClock #

FromValue CTime 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter CTime #

FromValue CUSeconds 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter CUSeconds #

FromValue CSUSeconds 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter CSUSeconds #

FromValue CIntPtr 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter CIntPtr #

FromValue CUIntPtr 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter CUIntPtr #

FromValue CIntMax 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter CIntMax #

FromValue CUIntMax 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter CUIntMax #

FromValue CBytes 
Instance details

Defined in Z.Data.CBytes

Methods

fromValue :: Value -> Converter CBytes #

FromValue Value 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter Value #

FromValue Text 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter Text #

FromValue Scientific 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter Scientific #

FromValue ByteArray 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter ByteArray #

FromValue CPUInfo 
Instance details

Defined in Z.IO.UV.FFI

Methods

fromValue :: Value -> Converter CPUInfo #

FromValue GID 
Instance details

Defined in Z.IO.UV.FFI

Methods

fromValue :: Value -> Converter GID #

FromValue OSName 
Instance details

Defined in Z.IO.UV.FFI

Methods

fromValue :: Value -> Converter OSName #

FromValue PID 
Instance details

Defined in Z.IO.UV.FFI

Methods

fromValue :: Value -> Converter PID #

FromValue PassWD 
Instance details

Defined in Z.IO.UV.FFI

Methods

fromValue :: Value -> Converter PassWD #

FromValue ResUsage 
Instance details

Defined in Z.IO.UV.FFI

Methods

fromValue :: Value -> Converter ResUsage #

FromValue TimeVal 
Instance details

Defined in Z.IO.UV.FFI

Methods

fromValue :: Value -> Converter TimeVal #

FromValue UID 
Instance details

Defined in Z.IO.UV.FFI

Methods

fromValue :: Value -> Converter UID #

FromValue AccessResult 
Instance details

Defined in Z.IO.UV.FFI

Methods

fromValue :: Value -> Converter AccessResult #

FromValue DirEntType 
Instance details

Defined in Z.IO.UV.FFI

Methods

fromValue :: Value -> Converter DirEntType #

FromValue FStat 
Instance details

Defined in Z.IO.UV.FFI

Methods

fromValue :: Value -> Converter FStat #

FromValue UVTimeSpec 
Instance details

Defined in Z.IO.UV.FFI

Methods

fromValue :: Value -> Converter UVTimeSpec #

FromValue Tag Source # 
Instance details

Defined in Z.Data.YAML.FFI

Methods

fromValue :: Value -> Converter Tag #

FromValue Mark Source # 
Instance details

Defined in Z.Data.YAML.FFI

Methods

fromValue :: Value -> Converter Mark #

FromValue MarkedEvent Source # 
Instance details

Defined in Z.Data.YAML.FFI

Methods

fromValue :: Value -> Converter MarkedEvent #

FromValue Event Source # 
Instance details

Defined in Z.Data.YAML.FFI

Methods

fromValue :: Value -> Converter Event #

FromValue FlatIntSet 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter FlatIntSet #

FromValue ProcessOptions 
Instance details

Defined in Z.IO.UV.FFI

Methods

fromValue :: Value -> Converter ProcessOptions #

FromValue ProcessStdStream 
Instance details

Defined in Z.IO.UV.FFI

Methods

fromValue :: Value -> Converter ProcessStdStream #

FromValue SocketAddr 
Instance details

Defined in Z.IO.Network.SocketAddr

Methods

fromValue :: Value -> Converter SocketAddr #

FromValue PathStyle 
Instance details

Defined in Z.IO.FileSystem.FilePath

Methods

fromValue :: Value -> Converter PathStyle #

FromValue IPv4 
Instance details

Defined in Z.IO.Network.SocketAddr

Methods

fromValue :: Value -> Converter IPv4 #

FromValue IPv6 
Instance details

Defined in Z.IO.Network.SocketAddr

Methods

fromValue :: Value -> Converter IPv6 #

FromValue PortNumber 
Instance details

Defined in Z.IO.Network.SocketAddr

Methods

fromValue :: Value -> Converter PortNumber #

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) 
Instance details

Defined in Z.Data.JSON.Base

Methods

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

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

Methods

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

FromValue a => FromValue (Identity a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter (Identity 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 (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

Methods

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

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

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter (PrimVector 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 (PrimArray a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

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

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

Methods

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

FromValue a => FromValue (FlatIntMap a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

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

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

Defined in Z.Data.JSON.Base

Methods

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

(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) #

HasResolution a => FromValue (Fixed a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

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

FromValue (Proxy a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

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

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

Defined in Z.Data.JSON.Base

Methods

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

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

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter (FlatMap Text a) #

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

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter (HashMap Text a) #

(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 #

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 ExitCode 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: ExitCode -> Value #

ToValue CChar 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CChar -> Value #

ToValue CSChar 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CSChar -> Value #

ToValue CUChar 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CUChar -> Value #

ToValue CShort 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CShort -> Value #

ToValue CUShort 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CUShort -> Value #

ToValue CInt 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CInt -> Value #

ToValue CUInt 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CUInt -> Value #

ToValue CLong 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CLong -> Value #

ToValue CULong 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CULong -> Value #

ToValue CLLong 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CLLong -> Value #

ToValue CULLong 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CULLong -> Value #

ToValue CBool 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CBool -> Value #

ToValue CFloat 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CFloat -> Value #

ToValue CDouble 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CDouble -> Value #

ToValue CPtrdiff 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CPtrdiff -> Value #

ToValue CSize 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CSize -> Value #

ToValue CWchar 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CWchar -> Value #

ToValue CSigAtomic 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CSigAtomic -> Value #

ToValue CClock 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CClock -> Value #

ToValue CTime 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CTime -> Value #

ToValue CUSeconds 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CUSeconds -> Value #

ToValue CSUSeconds 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CSUSeconds -> Value #

ToValue CIntPtr 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CIntPtr -> Value #

ToValue CUIntPtr 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CUIntPtr -> Value #

ToValue CIntMax 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CIntMax -> Value #

ToValue CUIntMax 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: CUIntMax -> 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 Text 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Text -> 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 CPUInfo 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: CPUInfo -> Value #

ToValue GID 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: GID -> Value #

ToValue OSName 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: OSName -> Value #

ToValue PID 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: PID -> Value #

ToValue PassWD 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: PassWD -> Value #

ToValue ResUsage 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: ResUsage -> Value #

ToValue TimeVal 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: TimeVal -> Value #

ToValue UID 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: UID -> Value #

ToValue AccessResult 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: AccessResult -> Value #

ToValue DirEntType 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: DirEntType -> Value #

ToValue FStat 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: FStat -> Value #

ToValue UVTimeSpec 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: UVTimeSpec -> 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 FlatIntSet 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: FlatIntSet -> Value #

ToValue ProcessOptions 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: ProcessOptions -> Value #

ToValue ProcessStdStream 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: ProcessStdStream -> Value #

ToValue SocketAddr 
Instance details

Defined in Z.IO.Network.SocketAddr

Methods

toValue :: SocketAddr -> Value #

ToValue PathStyle 
Instance details

Defined in Z.IO.FileSystem.FilePath

Methods

toValue :: PathStyle -> 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 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 (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 #

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

Defined in Z.Data.JSON.Base

Methods

toValue :: PrimVector 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 (PrimArray a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: PrimArray 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 #

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 (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 #

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 #

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

Defined in Z.Data.JSON.Base

Methods

toValue :: UnliftedArray a -> Value #

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

Defined in Z.Data.JSON.Base

Methods

toValue :: FlatMap Text 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 #

Constructors

Object !(Vector (Text, Value)) 
Array !(Vector Value) 
String !Text 
Number !Scientific 
Bool !Bool 
Null 

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 #

NFData Value 
Instance details

Defined in Z.Data.JSON.Value

Methods

rnf :: Value -> () #

Arbitrary Value 
Instance details

Defined in Z.Data.JSON.Value

Methods

arbitrary :: Gen Value

shrink :: 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

Methods

fromValue :: Value -> Converter Value #

ShowT Value 
Instance details

Defined in Z.Data.JSON.Value

Methods

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

ToValue Value 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Value -> Value #

type Rep Value 
Instance details

Defined in Z.Data.JSON.Value

type Rep Value = D1 ('MetaData "Value" "Z.Data.JSON.Value" "Z-Dt-0.2.0.0-0a94a1c5" 'False) ((C1 ('MetaCons "Object" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedUnpack) (Rec0 (Vector (Text, Value)))) :+: (C1 ('MetaCons "Array" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedUnpack) (Rec0 (Vector Value))) :+: C1 ('MetaCons "String" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedUnpack) (Rec0 Text)))) :+: (C1 ('MetaCons "Number" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedUnpack) (Rec0 Scientific)) :+: (C1 ('MetaCons "Bool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :+: C1 ('MetaCons "Null" 'PrefixI 'False) (U1 :: Type -> Type))))