Z-YAML-0.3.2.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 JSON 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.
  • Does 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.JSON)

> 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

decode :: forall a. (HasCallStack, JSON a) => Bytes -> Either DecodeError a Source #

Decode a JSON instance from YAML bytes.

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

Encode a JSON instance as UTF8 YAML text.

readYAMLFile :: forall a. (HasCallStack, JSON a) => CBytes -> IO a Source #

Decode a JSON instance from a YAML file.

writeYAMLFile :: (HasCallStack, JSON a) => YAMLFormatOpts -> CBytes -> a -> IO () Source #

Encode a JSON instance to YAML file.

Streaming parser and builder

parseSingleDoucment :: HasCallStack => Source MarkedEvent -> IO Value Source #

Parse a single YAML document, throw OtherYAMLError if multiple documents are met.

parseAllDocuments :: HasCallStack => Source MarkedEvent -> IO [Value] Source #

Parse all YAML documents.

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 stream of Events(without document start/end, stream start/end).

Errors

data YAMLError Source #

Instances

Instances details
Eq YAMLError Source # 
Instance details

Defined in Z.Data.YAML.FFI

Show YAMLError Source # 
Instance details

Defined in Z.Data.YAML.FFI

Generic YAMLError Source # 
Instance details

Defined in Z.Data.YAML.FFI

Associated Types

type Rep YAMLError :: Type -> Type #

Print YAMLError Source # 
Instance details

Defined in Z.Data.YAML.FFI

Methods

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

Exception YAMLError Source # 
Instance details

Defined in Z.Data.YAML.FFI

type Rep YAMLError Source # 
Instance details

Defined in Z.Data.YAML.FFI

type Rep YAMLError = D1 ('MetaData "YAMLError" "Z.Data.YAML.FFI" "Z-YAML-0.3.2.0-Iy5ya0bKRJ7BZEQyk88VQP" 'False) ((C1 ('MetaCons "ParseEventException" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CBytes) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CBytes) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Mark))) :+: (C1 ('MetaCons "ParseAliasEventWithEmptyAnchor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Mark) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Mark)) :+: C1 ('MetaCons "ParseYAMLError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 YAMLParseError)))) :+: (C1 ('MetaCons "EmitEventException" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Event) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CInt)) :+: (C1 ('MetaCons "EmitAliasEventWithEmptyAnchor" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OtherYAMLError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))))

data YAMLParseError Source #

Instances

Instances details
Eq YAMLParseError Source # 
Instance details

Defined in Z.Data.YAML.FFI

Show YAMLParseError Source # 
Instance details

Defined in Z.Data.YAML.FFI

Generic YAMLParseError Source # 
Instance details

Defined in Z.Data.YAML.FFI

Associated Types

type Rep YAMLParseError :: Type -> Type #

Print YAMLParseError Source # 
Instance details

Defined in Z.Data.YAML.FFI

Exception YAMLParseError Source # 
Instance details

Defined in Z.Data.YAML.FFI

type Rep YAMLParseError Source # 
Instance details

Defined in Z.Data.YAML.FFI

data ConvertError #

Error info with (JSON) Path info.

Instances

Instances details
Eq ConvertError 
Instance details

Defined in Z.Data.JSON.Converter

Ord ConvertError 
Instance details

Defined in Z.Data.JSON.Converter

Show ConvertError 
Instance details

Defined in Z.Data.JSON.Converter

Generic ConvertError 
Instance details

Defined in Z.Data.JSON.Converter

Associated Types

type Rep ConvertError :: Type -> Type #

Print ConvertError 
Instance details

Defined in Z.Data.JSON.Converter

NFData ConvertError 
Instance details

Defined in Z.Data.JSON.Converter

Methods

rnf :: ConvertError -> () #

type Rep ConvertError 
Instance details

Defined in Z.Data.JSON.Converter

type Rep ConvertError = D1 ('MetaData "ConvertError" "Z.Data.JSON.Converter" "Z-Data-0.6.0.0-6EPTULxocQtBtAKoZfHPhU" 'False) (C1 ('MetaCons "ConvertError" 'PrefixI 'True) (S1 ('MetaSel ('Just "errPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PathElement]) :*: S1 ('MetaSel ('Just "errMsg") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

Re-Exports

class JSON a where #

Type class for encode & decode JSON.

Minimal complete definition

Nothing

Methods

fromValue :: Value -> Converter a #

toValue :: a -> Value #

encodeJSON :: a -> Builder () #

Instances

Instances details
JSON Bool 
Instance details

Defined in Z.Data.JSON.Base

JSON Char 
Instance details

Defined in Z.Data.JSON.Base

JSON Double 
Instance details

Defined in Z.Data.JSON.Base

JSON Float 
Instance details

Defined in Z.Data.JSON.Base

JSON Int 
Instance details

Defined in Z.Data.JSON.Base

JSON Int8 
Instance details

Defined in Z.Data.JSON.Base

JSON Int16 
Instance details

Defined in Z.Data.JSON.Base

JSON Int32 
Instance details

Defined in Z.Data.JSON.Base

JSON Int64 
Instance details

Defined in Z.Data.JSON.Base

JSON Integer

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

Instance details

Defined in Z.Data.JSON.Base

JSON Natural

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

Instance details

Defined in Z.Data.JSON.Base

JSON Ordering 
Instance details

Defined in Z.Data.JSON.Base

JSON Word 
Instance details

Defined in Z.Data.JSON.Base

JSON Word8 
Instance details

Defined in Z.Data.JSON.Base

JSON Word16 
Instance details

Defined in Z.Data.JSON.Base

JSON Word32 
Instance details

Defined in Z.Data.JSON.Base

JSON Word64 
Instance details

Defined in Z.Data.JSON.Base

JSON () 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter () #

toValue :: () -> Value #

encodeJSON :: () -> Builder () #

JSON Version

Only round trip versionBranch as JSON array.

Instance details

Defined in Z.Data.JSON.Base

JSON NominalDiffTime

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

Instance details

Defined in Z.Data.JSON.Base

JSON DiffTime

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

Instance details

Defined in Z.Data.JSON.Base

JSON Scientific

Note this instance doesn't reject large input

Instance details

Defined in Z.Data.JSON.Base

JSON ZonedTime
YYYY-MM-DDTHH:MM:SS.SSSZ
Instance details

Defined in Z.Data.JSON.Base

JSON LocalTime
YYYY-MM-DDTHH:MM:SS.SSSZ
Instance details

Defined in Z.Data.JSON.Base

JSON UTCTime
YYYY-MM-DDTHH:MM:SS.SSSZ
Instance details

Defined in Z.Data.JSON.Base

JSON ByteArray 
Instance details

Defined in Z.Data.JSON.Base

JSON CUIntMax 
Instance details

Defined in Z.Data.JSON.Base

JSON CIntMax 
Instance details

Defined in Z.Data.JSON.Base

JSON CUIntPtr 
Instance details

Defined in Z.Data.JSON.Base

JSON CIntPtr 
Instance details

Defined in Z.Data.JSON.Base

JSON CSUSeconds 
Instance details

Defined in Z.Data.JSON.Base

JSON CUSeconds 
Instance details

Defined in Z.Data.JSON.Base

JSON CTime 
Instance details

Defined in Z.Data.JSON.Base

JSON CClock 
Instance details

Defined in Z.Data.JSON.Base

JSON CSigAtomic 
Instance details

Defined in Z.Data.JSON.Base

JSON CWchar 
Instance details

Defined in Z.Data.JSON.Base

JSON CSize 
Instance details

Defined in Z.Data.JSON.Base

JSON CPtrdiff 
Instance details

Defined in Z.Data.JSON.Base

JSON CDouble 
Instance details

Defined in Z.Data.JSON.Base

JSON CFloat 
Instance details

Defined in Z.Data.JSON.Base

JSON CBool 
Instance details

Defined in Z.Data.JSON.Base

JSON CULLong 
Instance details

Defined in Z.Data.JSON.Base

JSON CLLong 
Instance details

Defined in Z.Data.JSON.Base

JSON CULong 
Instance details

Defined in Z.Data.JSON.Base

JSON CLong 
Instance details

Defined in Z.Data.JSON.Base

JSON CUInt 
Instance details

Defined in Z.Data.JSON.Base

JSON CInt 
Instance details

Defined in Z.Data.JSON.Base

JSON CUShort 
Instance details

Defined in Z.Data.JSON.Base

JSON CShort 
Instance details

Defined in Z.Data.JSON.Base

JSON CUChar 
Instance details

Defined in Z.Data.JSON.Base

JSON CSChar 
Instance details

Defined in Z.Data.JSON.Base

JSON CChar 
Instance details

Defined in Z.Data.JSON.Base

JSON CBytes

JSON instances check if CBytes is properly UTF8 encoded, if it is, decode/encode it as Text, otherwise as an object with a base64 field.

> encodeText ("hello" :: CBytes)
""hello""
> encodeText ("hello\NUL" :: CBytes)     -- \NUL is encoded as C0 80, which is illegal UTF8
"{"base64":"aGVsbG/AgA=="}"
Instance details

Defined in Z.Data.CBytes

JSON Value 
Instance details

Defined in Z.Data.JSON.Base

JSON FlatIntSet 
Instance details

Defined in Z.Data.JSON.Base

JSON Text 
Instance details

Defined in Z.Data.JSON.Base

JSON Bytes

This is an INCOHERENT instance, encode binary data with base64 encoding.

Instance details

Defined in Z.Data.JSON.Base

JSON FileEvent 
Instance details

Defined in Z.IO.FileSystem.Watch

JSON PathStyle 
Instance details

Defined in Z.IO.FileSystem.FilePath

JSON DirEntType 
Instance details

Defined in Z.IO.UV.FFI

JSON UVTimeSpec 
Instance details

Defined in Z.IO.UV.FFI

JSON FStat 
Instance details

Defined in Z.IO.UV.FFI

JSON AccessResult 
Instance details

Defined in Z.IO.UV.FFI

JSON UID 
Instance details

Defined in Z.IO.UV.FFI

JSON GID 
Instance details

Defined in Z.IO.UV.FFI

JSON ProcessOptions 
Instance details

Defined in Z.IO.UV.FFI

JSON ProcessStdStream 
Instance details

Defined in Z.IO.UV.FFI

JSON TimeVal 
Instance details

Defined in Z.IO.UV.FFI

JSON ResUsage 
Instance details

Defined in Z.IO.UV.FFI

JSON PID 
Instance details

Defined in Z.IO.UV.FFI

JSON OSName 
Instance details

Defined in Z.IO.UV.FFI

JSON PassWD 
Instance details

Defined in Z.IO.UV.FFI

JSON CPUInfo 
Instance details

Defined in Z.IO.UV.FFI

JSON TimeVal64 
Instance details

Defined in Z.IO.UV.FFI

JSON SocketAddr 
Instance details

Defined in Z.IO.Network.SocketAddr

JSON IPv4 
Instance details

Defined in Z.IO.Network.SocketAddr

JSON IPv6 
Instance details

Defined in Z.IO.Network.SocketAddr

JSON PortNumber 
Instance details

Defined in Z.IO.Network.SocketAddr

JSON SystemTime

{"seconds": SSS, "nanoseconds": NNN}.

Instance details

Defined in Z.Data.JSON.Base

JSON ExitCode 
Instance details

Defined in Z.Data.JSON.Base

JSON IntSet 
Instance details

Defined in Z.Data.JSON.Base

JSON TimeOfDay
HH:MM:SS.SSS
Instance details

Defined in Z.Data.JSON.Base

JSON CalendarDiffTime 
Instance details

Defined in Z.Data.JSON.Base

JSON DayOfWeek 
Instance details

Defined in Z.Data.JSON.Base

JSON Day
YYYY-MM-DD
Instance details

Defined in Z.Data.JSON.Base

JSON CalendarDiffDays 
Instance details

Defined in Z.Data.JSON.Base

JSON Tag Source # 
Instance details

Defined in Z.Data.YAML.FFI

JSON Mark Source # 
Instance details

Defined in Z.Data.YAML.FFI

JSON MarkedEvent Source # 
Instance details

Defined in Z.Data.YAML.FFI

JSON Event Source # 
Instance details

Defined in Z.Data.YAML.FFI

JSON [Char]

This is an INCOHERENT instance, to provide JSON text encoding behaviour.

Instance details

Defined in Z.Data.JSON.Base

JSON a => JSON [a] 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter [a] #

toValue :: [a] -> Value #

encodeJSON :: [a] -> Builder () #

JSON a => JSON (Maybe a) 
Instance details

Defined in Z.Data.JSON.Base

(JSON a, Integral a) => JSON (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

JSON a => JSON (FlatIntMap a) 
Instance details

Defined in Z.Data.JSON.Base

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

Defined in Z.Data.JSON.Base

JSON a => JSON (Vector a) 
Instance details

Defined in Z.Data.JSON.Base

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

Defined in Z.Data.JSON.Base

JSON a => JSON (Array a) 
Instance details

Defined in Z.Data.JSON.Base

JSON a => JSON (SmallArray a) 
Instance details

Defined in Z.Data.JSON.Base

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

Defined in Z.Data.JSON.Base

JSON a => JSON (Min a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

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

toValue :: Min a -> Value #

encodeJSON :: Min a -> Builder () #

JSON a => JSON (Max a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

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

toValue :: Max a -> Value #

encodeJSON :: Max a -> Builder () #

JSON a => JSON (First a) 
Instance details

Defined in Z.Data.JSON.Base

JSON a => JSON (Last a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

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

toValue :: Last a -> Value #

encodeJSON :: Last a -> Builder () #

JSON a => JSON (WrappedMonoid a) 
Instance details

Defined in Z.Data.JSON.Base

JSON a => JSON (Identity a) 
Instance details

Defined in Z.Data.JSON.Base

JSON a => JSON (First a) 
Instance details

Defined in Z.Data.JSON.Base

JSON a => JSON (Last a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

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

toValue :: Last a -> Value #

encodeJSON :: Last a -> Builder () #

JSON a => JSON (Dual a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

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

toValue :: Dual a -> Value #

encodeJSON :: Dual a -> Builder () #

JSON a => JSON (NonEmpty a) 
Instance details

Defined in Z.Data.JSON.Base

JSON a => JSON (IntMap a) 
Instance details

Defined in Z.Data.JSON.Base

JSON a => JSON (Tree a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

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

toValue :: Tree a -> Value #

encodeJSON :: Tree a -> Builder () #

JSON a => JSON (Seq a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

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

toValue :: Seq a -> Value #

encodeJSON :: Seq a -> Builder () #

(Ord a, JSON a) => JSON (Set a) 
Instance details

Defined in Z.Data.JSON.Base

Methods

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

toValue :: Set a -> Value #

encodeJSON :: Set a -> Builder () #

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

Defined in Z.Data.JSON.Base

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

Defined in Z.Data.JSON.Base

Methods

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

toValue :: Either a b -> Value #

encodeJSON :: Either a b -> Builder () #

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

Defined in Z.Data.JSON.Base

Methods

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

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

encodeJSON :: (a, b) -> Builder () #

JSON a => JSON (FlatMap Text a)

default instance prefer later key

Instance details

Defined in Z.Data.JSON.Base

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

Defined in Z.Data.JSON.Base

HasResolution a => JSON (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

JSON (Proxy a)

Use Null as Proxy a

Instance details

Defined in Z.Data.JSON.Base

JSON a => JSON (Map Text a) 
Instance details

Defined in Z.Data.JSON.Base

JSON a => JSON (HashMap Text a)

default instance prefer later key

Instance details

Defined in Z.Data.JSON.Base

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

Defined in Z.Data.JSON.Base

Methods

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

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

encodeJSON :: (a, b, c) -> Builder () #

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

Defined in Z.Data.JSON.Base

Methods

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

toValue :: Const a b -> Value #

encodeJSON :: Const a b -> Builder () #

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

Defined in Z.Data.JSON.Base

Methods

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

toValue :: Tagged a b -> Value #

encodeJSON :: Tagged a b -> Builder () #

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

Defined in Z.Data.JSON.Base

Methods

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

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

encodeJSON :: (a, b, c, d) -> Builder () #

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

Defined in Z.Data.JSON.Base

Methods

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

toValue :: Product f g a -> Value #

encodeJSON :: Product f g a -> Builder () #

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

Defined in Z.Data.JSON.Base

Methods

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

toValue :: Sum f g a -> Value #

encodeJSON :: Sum f g a -> Builder () #

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

Defined in Z.Data.JSON.Base

Methods

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

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

encodeJSON :: (a, b, c, d, e) -> Builder () #

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

Defined in Z.Data.JSON.Base

Methods

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

toValue :: Compose f g a -> Value #

encodeJSON :: Compose f g a -> Builder () #

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

Defined in Z.Data.JSON.Base

Methods

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

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

encodeJSON :: (a, b, c, d, e, f) -> Builder () #

(JSON a, JSON b, JSON c, JSON d, JSON e, JSON f, JSON g) => JSON (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) #

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

encodeJSON :: (a, b, c, d, e, f, g) -> Builder () #

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 #

Ord Value 
Instance details

Defined in Z.Data.JSON.Value

Methods

compare :: Value -> Value -> Ordering #

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

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

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

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

max :: Value -> Value -> Value #

min :: Value -> Value -> Value #

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

JSON Value 
Instance details

Defined in Z.Data.JSON.Base

Print 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