Safe Haskell | None |
---|---|
Language | Haskell2010 |
Data.Yaml
Description
Provides a high-level interface for processing YAML files.
This module reuses most of the infrastructure from the aeson
package.
This means that you can use all of the existing tools for JSON
processing for processing YAML files. As a result, much of the
documentation below mentions JSON; do not let that confuse you, it's
intentional.
For the most part, YAML content translates directly into JSON, and therefore there is very little data loss. If you need to deal with YAML more directly (e.g., directly deal with aliases), you should use the Text.Libyaml module instead.
For documentation on the aeson
types, functions, classes, and
operators, please see the Data.Aeson
module of the aeson
package.
Look in the examples directory of the source repository for some initial pointers on how to use this library.
Synopsis
- encode :: ToJSON a => a -> ByteString
- encodeWith :: ToJSON a => EncodeOptions -> a -> ByteString
- encodeFile :: ToJSON a => FilePath -> a -> IO ()
- encodeFileWith :: ToJSON a => EncodeOptions -> FilePath -> a -> IO ()
- decodeEither' :: FromJSON a => ByteString -> Either ParseException a
- decodeFileEither :: FromJSON a => FilePath -> IO (Either ParseException a)
- decodeFileWithWarnings :: FromJSON a => FilePath -> IO (Either ParseException ([Warning], a))
- decodeThrow :: (MonadThrow m, FromJSON a) => ByteString -> m a
- decodeFileThrow :: (MonadIO m, FromJSON a) => FilePath -> m a
- decodeAllEither' :: FromJSON a => ByteString -> Either ParseException [a]
- decodeAllFileEither :: FromJSON a => FilePath -> IO (Either ParseException [a])
- decodeAllFileWithWarnings :: FromJSON a => FilePath -> IO (Either ParseException ([Warning], [a]))
- decodeAllThrow :: (MonadThrow m, FromJSON a) => ByteString -> m [a]
- decodeAllFileThrow :: (MonadIO m, FromJSON a) => FilePath -> m [a]
- decodeHelper :: FromJSON a => ConduitM () Event Parse () -> IO (Either ParseException ([Warning], Either String a))
- data Value
- data Parser a
- type Object = KeyMap Value
- type Array = Vector Value
- data ParseException
- = NonScalarKey
- | UnknownAlias {
- _anchorName :: AnchorName
- | UnexpectedEvent { }
- | InvalidYaml (Maybe YamlException)
- | MultipleDocuments
- | AesonException String
- | OtherParseException SomeException
- | NonStringKey JSONPath
- | NonStringKeyAlias AnchorName Value
- | CyclicIncludes
- | LoadSettingsException FilePath ParseException
- prettyPrintParseException :: ParseException -> String
- data YamlException
- = YamlException String
- | YamlParseException {
- yamlProblem :: String
- yamlContext :: String
- yamlProblemMark :: YamlMark
- data YamlMark = YamlMark {
- yamlIndex :: Int
- yamlLine :: Int
- yamlColumn :: Int
- object :: [Pair] -> Value
- array :: [Value] -> Value
- (.=) :: (KeyValue e kv, ToJSON v) => Key -> v -> kv
- (.:) :: FromJSON a => Object -> Key -> Parser a
- (.:?) :: FromJSON a => Object -> Key -> Parser (Maybe a)
- (.!=) :: Parser (Maybe a) -> a -> Parser a
- withObject :: String -> (Object -> Parser a) -> Value -> Parser a
- withText :: String -> (Text -> Parser a) -> Value -> Parser a
- withArray :: String -> (Array -> Parser a) -> Value -> Parser a
- withScientific :: String -> (Scientific -> Parser a) -> Value -> Parser a
- withBool :: String -> (Bool -> Parser a) -> Value -> Parser a
- parseMonad :: MonadFail m => (a -> Parser b) -> a -> m b
- parseEither :: (a -> Parser b) -> a -> Either String b
- parseMaybe :: (a -> Parser b) -> a -> Maybe b
- class ToJSON a where
- toJSON :: a -> Value
- toEncoding :: a -> Encoding
- toJSONList :: [a] -> Value
- toEncodingList :: [a] -> Encoding
- omitField :: a -> Bool
- class FromJSON a where
- parseJSON :: Value -> Parser a
- parseJSONList :: Value -> Parser [a]
- omittedField :: Maybe a
- isSpecialString :: Text -> Bool
- data EncodeOptions
- defaultEncodeOptions :: EncodeOptions
- defaultStringStyle :: StringStyle
- setStringStyle :: (Text -> (Tag, Style)) -> EncodeOptions -> EncodeOptions
- setFormat :: FormatOptions -> EncodeOptions -> EncodeOptions
- data FormatOptions
- defaultFormatOptions :: FormatOptions
- setWidth :: Maybe Int -> FormatOptions -> FormatOptions
- decode :: FromJSON a => ByteString -> Maybe a
- decodeFile :: FromJSON a => FilePath -> IO (Maybe a)
- decodeEither :: FromJSON a => ByteString -> Either String a
Encoding
encodeWith :: ToJSON a => EncodeOptions -> a -> ByteString Source #
Encode a value into its YAML representation with custom styling.
Since: 0.10.2.0
encodeFile :: ToJSON a => FilePath -> a -> IO () Source #
Encode a value into its YAML representation and save to the given file.
encodeFileWith :: ToJSON a => EncodeOptions -> FilePath -> a -> IO () Source #
Encode a value into its YAML representation with custom styling and save to the given file.
Since: 0.10.2.0
Decoding
decodeEither' :: FromJSON a => ByteString -> Either ParseException a Source #
More helpful version of decodeEither
which returns the YamlException
.
Since: 0.8.3
decodeFileEither :: FromJSON a => FilePath -> IO (Either ParseException a) Source #
A version of decodeFile
which should not throw runtime exceptions.
Since: 0.8.4
decodeFileWithWarnings :: FromJSON a => FilePath -> IO (Either ParseException ([Warning], a)) Source #
A version of decodeFileEither
that returns warnings along with the parse
result.
Since: 0.10.0
decodeThrow :: (MonadThrow m, FromJSON a) => ByteString -> m a Source #
A version of decodeEither'
lifted to MonadThrow
Since: 0.8.31
decodeFileThrow :: (MonadIO m, FromJSON a) => FilePath -> m a Source #
A version of decodeFileEither
lifted to MonadIO
Since: 0.8.31
Decoding multiple documents
For situations where we need to be able to parse multiple documents separated by `---` in a YAML stream, these functions decode a list of values rather than a single value.
decodeAllEither' :: FromJSON a => ByteString -> Either ParseException [a] Source #
Like decodeEither'
, but decode multiple documents.
Since: 0.11.5.0
decodeAllFileEither :: FromJSON a => FilePath -> IO (Either ParseException [a]) Source #
Like decodeFileEither
, but decode multiple documents.
Since: 0.11.5.0
decodeAllFileWithWarnings :: FromJSON a => FilePath -> IO (Either ParseException ([Warning], [a])) Source #
Like decodeFileWithWarnings
, but decode multiple documents.
Since: 0.11.5.0
decodeAllThrow :: (MonadThrow m, FromJSON a) => ByteString -> m [a] Source #
Like decodeThrow
, but decode multiple documents.
Since: 0.11.5.0
decodeAllFileThrow :: (MonadIO m, FromJSON a) => FilePath -> m [a] Source #
Like decodeFileThrow
, but decode multiple documents.
Since: 0.11.5.0
More control over decoding
decodeHelper :: FromJSON a => ConduitM () Event Parse () -> IO (Either ParseException ([Warning], Either String a)) Source #
Types
Instances
Arbitrary Value | |||||
CoArbitrary Value | |||||
Defined in Data.Aeson.Types.Internal Methods coarbitrary :: Value -> Gen b -> Gen b | |||||
Function Value | |||||
Defined in Data.Aeson.Types.Internal | |||||
FromJSON Value | |||||
Defined in Data.Aeson.Types.FromJSON | |||||
ToJSON Value | |||||
Defined in Data.Aeson.Types.ToJSON | |||||
NFData Value | |||||
Defined in Data.Aeson.Types.Internal | |||||
Data Value | |||||
Defined in Data.Aeson.Types.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Value -> c Value gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Value dataTypeOf :: Value -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Value) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Value) gmapT :: (forall b. Data b => b -> b) -> Value -> Value gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Value -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Value -> r gmapQ :: (forall d. Data d => d -> u) -> Value -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> Value -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> Value -> m Value gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Value -> m Value gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Value -> m Value | |||||
IsString Value | |||||
Defined in Data.Aeson.Types.Internal Methods fromString :: String -> Value | |||||
Generic Value | |||||
Defined in Data.Aeson.Types.Internal Associated Types
| |||||
Read Value | |||||
Defined in Data.Aeson.Types.Internal | |||||
Show Value | |||||
Eq Value | |||||
Ord Value | |||||
Hashable Value | |||||
Defined in Data.Aeson.Types.Internal | |||||
KeyValue Encoding Series | |||||
Defined in Data.Aeson.Types.ToJSON Methods (.=) :: ToJSON v => Key -> v -> Series # explicitToField :: (v -> Encoding) -> Key -> v -> Series | |||||
KeyValueOmit Encoding Series | |||||
Defined in Data.Aeson.Types.ToJSON Methods (.?=) :: ToJSON v => Key -> v -> Series explicitToFieldOmit :: (v -> Bool) -> (v -> Encoding) -> Key -> v -> Series | |||||
Lift Value | |||||
(GToJSON' Encoding arity a, ConsToJSON Encoding arity a, Constructor c) => SumToJSON' TwoElemArray Encoding arity (C1 c a) | |||||
Defined in Data.Aeson.Types.ToJSON Methods sumToJSON' :: Options -> ToArgs Encoding arity a0 -> C1 c a a0 -> Tagged TwoElemArray Encoding | |||||
(GToJSON' Value arity a, ConsToJSON Value arity a, Constructor c) => SumToJSON' TwoElemArray Value arity (C1 c a) | |||||
Defined in Data.Aeson.Types.ToJSON Methods sumToJSON' :: Options -> ToArgs Value arity a0 -> C1 c a a0 -> Tagged TwoElemArray Value | |||||
GToJSON' Encoding arity (U1 :: Type -> Type) | |||||
Defined in Data.Aeson.Types.ToJSON Methods gToJSON :: Options -> ToArgs Encoding arity a -> U1 a -> Encoding | |||||
GToJSON' Encoding arity (V1 :: Type -> Type) | |||||
Defined in Data.Aeson.Types.ToJSON Methods gToJSON :: Options -> ToArgs Encoding arity a -> V1 a -> Encoding | |||||
GToJSON' Value arity (U1 :: Type -> Type) | |||||
Defined in Data.Aeson.Types.ToJSON | |||||
GToJSON' Value arity (V1 :: Type -> Type) | |||||
Defined in Data.Aeson.Types.ToJSON | |||||
ToJSON1 f => GToJSON' Encoding One (Rec1 f) | |||||
Defined in Data.Aeson.Types.ToJSON Methods gToJSON :: Options -> ToArgs Encoding One a -> Rec1 f a -> Encoding | |||||
ToJSON1 f => GToJSON' Value One (Rec1 f) | |||||
Defined in Data.Aeson.Types.ToJSON | |||||
(EncodeProduct arity a, EncodeProduct arity b) => GToJSON' Encoding arity (a :*: b) | |||||
Defined in Data.Aeson.Types.ToJSON Methods gToJSON :: Options -> ToArgs Encoding arity a0 -> (a :*: b) a0 -> Encoding | |||||
ToJSON a => GToJSON' Encoding arity (K1 i a :: Type -> Type) | |||||
Defined in Data.Aeson.Types.ToJSON Methods gToJSON :: Options -> ToArgs Encoding arity a0 -> K1 i a a0 -> Encoding | |||||
(WriteProduct arity a, WriteProduct arity b, ProductSize a, ProductSize b) => GToJSON' Value arity (a :*: b) | |||||
Defined in Data.Aeson.Types.ToJSON | |||||
ToJSON a => GToJSON' Value arity (K1 i a :: Type -> Type) | |||||
Defined in Data.Aeson.Types.ToJSON | |||||
(ToJSON1 f, GToJSON' Encoding One g) => GToJSON' Encoding One (f :.: g) | |||||
Defined in Data.Aeson.Types.ToJSON Methods gToJSON :: Options -> ToArgs Encoding One a -> (f :.: g) a -> Encoding | |||||
(ToJSON1 f, GToJSON' Value One g) => GToJSON' Value One (f :.: g) | |||||
Defined in Data.Aeson.Types.ToJSON | |||||
FromPairs Value (DList Pair) | |||||
Defined in Data.Aeson.Types.ToJSON | |||||
value ~ Value => KeyValue Value (KeyMap value) | |||||
Defined in Data.Aeson.Types.ToJSON Methods (.=) :: ToJSON v => Key -> v -> KeyMap value # explicitToField :: (v -> Value) -> Key -> v -> KeyMap value | |||||
value ~ Value => KeyValueOmit Value (KeyMap value) | |||||
Defined in Data.Aeson.Types.ToJSON Methods (.?=) :: ToJSON v => Key -> v -> KeyMap value explicitToFieldOmit :: (v -> Bool) -> (v -> Value) -> Key -> v -> KeyMap value | |||||
v ~ Value => KeyValuePair v (DList Pair) | |||||
Defined in Data.Aeson.Types.ToJSON Methods pair :: Key -> v -> DList Pair | |||||
(key ~ Key, value ~ Value) => KeyValue Value (key, value) | |||||
Defined in Data.Aeson.Types.ToJSON Methods (.=) :: ToJSON v => Key -> v -> (key, value) # explicitToField :: (v -> Value) -> Key -> v -> (key, value) | |||||
type Rep Value | |||||
Defined in Data.Aeson.Types.Internal type Rep Value = D1 ('MetaData "Value" "Data.Aeson.Types.Internal" "aeson-2.2.3.0-5h6SkiockB6KKRjZY80R09" 'False) ((C1 ('MetaCons "Object" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Object)) :+: (C1 ('MetaCons "Array" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Array)) :+: C1 ('MetaCons "String" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)))) :+: (C1 ('MetaCons "Number" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (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)))) |
data ParseException Source #
Constructors
NonScalarKey | |
UnknownAlias | |
Fields
| |
UnexpectedEvent | |
InvalidYaml (Maybe YamlException) | |
MultipleDocuments | |
AesonException String | |
OtherParseException SomeException | |
NonStringKey JSONPath | |
NonStringKeyAlias AnchorName Value | |
CyclicIncludes | |
LoadSettingsException FilePath ParseException |
Instances
Exception ParseException Source # | |
Defined in Data.Yaml.Internal Methods toException :: ParseException -> SomeException fromException :: SomeException -> Maybe ParseException displayException :: ParseException -> String backtraceDesired :: ParseException -> Bool | |
Show ParseException Source # | |
Defined in Data.Yaml.Internal Methods showsPrec :: Int -> ParseException -> ShowS show :: ParseException -> String showList :: [ParseException] -> ShowS |
prettyPrintParseException :: ParseException -> String Source #
Alternative to show
to display a ParseException
on the screen.
Instead of displaying the data constructors applied to their arguments,
a more textual output is returned. For example, instead of printing:
InvalidYaml (Just (YamlParseException {yamlProblem = "did not find expected ',' or '}'", yamlContext = "while parsing a flow mapping", yamlProblemMark = YamlMark {yamlIndex = 42, yamlLine = 2, yamlColumn = 12}})))
It looks more pleasant to print:
YAML parse exception at line 2, column 12, while parsing a flow mapping: did not find expected ',' or '}'
Since 0.8.11
data YamlException #
Constructors
YamlException String | |
YamlParseException | |
Fields
|
Instances
Exception YamlException | |
Defined in Text.Libyaml Methods toException :: YamlException -> SomeException fromException :: SomeException -> Maybe YamlException displayException :: YamlException -> String backtraceDesired :: YamlException -> Bool | |
Show YamlException | |
Defined in Text.Libyaml Methods showsPrec :: Int -> YamlException -> ShowS show :: YamlException -> String showList :: [YamlException] -> ShowS |
Constructors
YamlMark | |
Fields
|
Constructors and accessors
With helpers (since 0.8.23)
withScientific :: String -> (Scientific -> Parser a) -> Value -> Parser a #
Parsing
parseMonad :: MonadFail m => (a -> Parser b) -> a -> m b Source #
Deprecated: With the MonadFail split, this function is going to be removed in the future. Please migrate to parseEither.
parseEither :: (a -> Parser b) -> a -> Either String b #
parseMaybe :: (a -> Parser b) -> a -> Maybe b #
Classes
Minimal complete definition
Nothing
Instances
ToJSON Key | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Key -> Encoding # toJSONList :: [Key] -> Value # toEncodingList :: [Key] -> Encoding # | |
ToJSON DotNetTime | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: DotNetTime -> Value # toEncoding :: DotNetTime -> Encoding # toJSONList :: [DotNetTime] -> Value # toEncodingList :: [DotNetTime] -> Encoding # | |
ToJSON Value | |
Defined in Data.Aeson.Types.ToJSON | |
ToJSON IntSet | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: IntSet -> Encoding # toJSONList :: [IntSet] -> Value # toEncodingList :: [IntSet] -> Encoding # | |
ToJSON Void | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Void -> Encoding # toJSONList :: [Void] -> Value # toEncodingList :: [Void] -> Encoding # | |
ToJSON All | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: All -> Encoding # toJSONList :: [All] -> Value # toEncodingList :: [All] -> Encoding # | |
ToJSON Any | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Any -> Encoding # toJSONList :: [Any] -> Value # toEncodingList :: [Any] -> Encoding # | |
ToJSON Version | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Version -> Encoding # toJSONList :: [Version] -> Value # toEncodingList :: [Version] -> Encoding # | |
ToJSON CTime | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: CTime -> Encoding # toJSONList :: [CTime] -> Value # toEncodingList :: [CTime] -> Encoding # | |
ToJSON Int16 | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Int16 -> Encoding # toJSONList :: [Int16] -> Value # toEncodingList :: [Int16] -> Encoding # | |
ToJSON Int32 | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Int32 -> Encoding # toJSONList :: [Int32] -> Value # toEncodingList :: [Int32] -> Encoding # | |
ToJSON Int64 | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Int64 -> Encoding # toJSONList :: [Int64] -> Value # toEncodingList :: [Int64] -> Encoding # | |
ToJSON Int8 | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Int8 -> Encoding # toJSONList :: [Int8] -> Value # toEncodingList :: [Int8] -> Encoding # | |
ToJSON Word16 | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Word16 -> Encoding # toJSONList :: [Word16] -> Value # toEncodingList :: [Word16] -> Encoding # | |
ToJSON Word32 | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Word32 -> Encoding # toJSONList :: [Word32] -> Value # toEncodingList :: [Word32] -> Encoding # | |
ToJSON Word64 | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Word64 -> Encoding # toJSONList :: [Word64] -> Value # toEncodingList :: [Word64] -> Encoding # | |
ToJSON Word8 | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Word8 -> Encoding # toJSONList :: [Word8] -> Value # toEncodingList :: [Word8] -> Encoding # | |
ToJSON Ordering | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Ordering -> Encoding # toJSONList :: [Ordering] -> Value # toEncodingList :: [Ordering] -> Encoding # | |
ToJSON URI | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: URI -> Encoding # toJSONList :: [URI] -> Value # toEncodingList :: [URI] -> Encoding # | |
ToJSON Scientific | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: Scientific -> Value # toEncoding :: Scientific -> Encoding # toJSONList :: [Scientific] -> Value # toEncodingList :: [Scientific] -> Encoding # | |
ToJSON Text | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Text -> Encoding # toJSONList :: [Text] -> Value # toEncodingList :: [Text] -> Encoding # | |
ToJSON Text | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Text -> Encoding # toJSONList :: [Text] -> Value # toEncodingList :: [Text] -> Encoding # | |
ToJSON ShortText | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: ShortText -> Value # toEncoding :: ShortText -> Encoding # toJSONList :: [ShortText] -> Value # toEncodingList :: [ShortText] -> Encoding # | |
ToJSON CalendarDiffDays | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: CalendarDiffDays -> Value # toEncoding :: CalendarDiffDays -> Encoding # toJSONList :: [CalendarDiffDays] -> Value # toEncodingList :: [CalendarDiffDays] -> Encoding # | |
ToJSON Day | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Day -> Encoding # toJSONList :: [Day] -> Value # toEncodingList :: [Day] -> Encoding # | |
ToJSON Month | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Month -> Encoding # toJSONList :: [Month] -> Value # toEncodingList :: [Month] -> Encoding # | |
ToJSON Quarter | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Quarter -> Encoding # toJSONList :: [Quarter] -> Value # toEncodingList :: [Quarter] -> Encoding # | |
ToJSON QuarterOfYear | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: QuarterOfYear -> Value # toEncoding :: QuarterOfYear -> Encoding # toJSONList :: [QuarterOfYear] -> Value # toEncodingList :: [QuarterOfYear] -> Encoding # | |
ToJSON DayOfWeek | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: DayOfWeek -> Value # toEncoding :: DayOfWeek -> Encoding # toJSONList :: [DayOfWeek] -> Value # toEncodingList :: [DayOfWeek] -> Encoding # | |
ToJSON DiffTime | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: DiffTime -> Encoding # toJSONList :: [DiffTime] -> Value # toEncodingList :: [DiffTime] -> Encoding # | |
ToJSON NominalDiffTime | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: NominalDiffTime -> Value # toEncoding :: NominalDiffTime -> Encoding # toJSONList :: [NominalDiffTime] -> Value # toEncodingList :: [NominalDiffTime] -> Encoding # | |
ToJSON SystemTime | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: SystemTime -> Value # toEncoding :: SystemTime -> Encoding # toJSONList :: [SystemTime] -> Value # toEncodingList :: [SystemTime] -> Encoding # | |
ToJSON UTCTime | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: UTCTime -> Encoding # toJSONList :: [UTCTime] -> Value # toEncodingList :: [UTCTime] -> Encoding # | |
ToJSON CalendarDiffTime | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: CalendarDiffTime -> Value # toEncoding :: CalendarDiffTime -> Encoding # toJSONList :: [CalendarDiffTime] -> Value # toEncodingList :: [CalendarDiffTime] -> Encoding # | |
ToJSON LocalTime | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: LocalTime -> Value # toEncoding :: LocalTime -> Encoding # toJSONList :: [LocalTime] -> Value # toEncodingList :: [LocalTime] -> Encoding # | |
ToJSON TimeOfDay | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: TimeOfDay -> Value # toEncoding :: TimeOfDay -> Encoding # toJSONList :: [TimeOfDay] -> Value # toEncodingList :: [TimeOfDay] -> Encoding # | |
ToJSON ZonedTime | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: ZonedTime -> Value # toEncoding :: ZonedTime -> Encoding # toJSONList :: [ZonedTime] -> Value # toEncodingList :: [ZonedTime] -> Encoding # | |
ToJSON UUID | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: UUID -> Encoding # toJSONList :: [UUID] -> Value # toEncodingList :: [UUID] -> Encoding # | |
ToJSON Integer | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Integer -> Encoding # toJSONList :: [Integer] -> Value # toEncodingList :: [Integer] -> Encoding # | |
ToJSON Natural | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Natural -> Encoding # toJSONList :: [Natural] -> Value # toEncodingList :: [Natural] -> Encoding # | |
ToJSON () | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: () -> Encoding # toJSONList :: [()] -> Value # toEncodingList :: [()] -> Encoding # | |
ToJSON Bool | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Bool -> Encoding # toJSONList :: [Bool] -> Value # toEncodingList :: [Bool] -> Encoding # | |
ToJSON Char | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Char -> Encoding # toJSONList :: [Char] -> Value # toEncodingList :: [Char] -> Encoding # | |
ToJSON Double | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Double -> Encoding # toJSONList :: [Double] -> Value # toEncodingList :: [Double] -> Encoding # | |
ToJSON Float | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Float -> Encoding # toJSONList :: [Float] -> Value # toEncodingList :: [Float] -> Encoding # | |
ToJSON Int | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Int -> Encoding # toJSONList :: [Int] -> Value # toEncodingList :: [Int] -> Encoding # | |
ToJSON Word | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Word -> Encoding # toJSONList :: [Word] -> Value # toEncodingList :: [Word] -> Encoding # | |
ToJSON v => ToJSON (KeyMap v) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: KeyMap v -> Encoding # toJSONList :: [KeyMap v] -> Value # toEncodingList :: [KeyMap v] -> Encoding # | |
ToJSON a => ToJSON (First a) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: First a -> Encoding # toJSONList :: [First a] -> Value # toEncodingList :: [First a] -> Encoding # | |
ToJSON a => ToJSON (Last a) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Last a -> Encoding # toJSONList :: [Last a] -> Value # toEncodingList :: [Last a] -> Encoding # | |
ToJSON a => ToJSON (Max a) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Max a -> Encoding # toJSONList :: [Max a] -> Value # toEncodingList :: [Max a] -> Encoding # | |
ToJSON a => ToJSON (Min a) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Min a -> Encoding # toJSONList :: [Min a] -> Value # toEncodingList :: [Min a] -> Encoding # | |
ToJSON a => ToJSON (WrappedMonoid a) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: WrappedMonoid a -> Value # toEncoding :: WrappedMonoid a -> Encoding # toJSONList :: [WrappedMonoid a] -> Value # toEncodingList :: [WrappedMonoid a] -> Encoding # | |
ToJSON a => ToJSON (IntMap a) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: IntMap a -> Encoding # toJSONList :: [IntMap a] -> Value # toEncodingList :: [IntMap a] -> Encoding # | |
ToJSON a => ToJSON (Seq a) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Seq a -> Encoding # toJSONList :: [Seq a] -> Value # toEncodingList :: [Seq a] -> Encoding # | |
ToJSON a => ToJSON (Set a) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Set a -> Encoding # toJSONList :: [Set a] -> Value # toEncodingList :: [Set a] -> Encoding # | |
ToJSON v => ToJSON (Tree v) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Tree v -> Encoding # toJSONList :: [Tree v] -> Value # toEncodingList :: [Tree v] -> Encoding # | |
ToJSON1 f => ToJSON (Fix f) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Fix f -> Encoding # toJSONList :: [Fix f] -> Value # toEncodingList :: [Fix f] -> Encoding # | |
(ToJSON1 f, Functor f) => ToJSON (Mu f) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Mu f -> Encoding # toJSONList :: [Mu f] -> Value # toEncodingList :: [Mu f] -> Encoding # | |
(ToJSON1 f, Functor f) => ToJSON (Nu f) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Nu f -> Encoding # toJSONList :: [Nu f] -> Value # toEncodingList :: [Nu f] -> Encoding # | |
ToJSON a => ToJSON (DNonEmpty a) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: DNonEmpty a -> Value # toEncoding :: DNonEmpty a -> Encoding # toJSONList :: [DNonEmpty a] -> Value # toEncodingList :: [DNonEmpty a] -> Encoding # | |
ToJSON a => ToJSON (DList a) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: DList a -> Encoding # toJSONList :: [DList a] -> Value # toEncodingList :: [DList a] -> Encoding # | |
ToJSON a => ToJSON (NonEmpty a) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: NonEmpty a -> Value # toEncoding :: NonEmpty a -> Encoding # toJSONList :: [NonEmpty a] -> Value # toEncodingList :: [NonEmpty a] -> Encoding # | |
ToJSON a => ToJSON (Identity a) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: Identity a -> Value # toEncoding :: Identity a -> Encoding # toJSONList :: [Identity a] -> Value # toEncodingList :: [Identity a] -> Encoding # | |
ToJSON a => ToJSON (First a) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: First a -> Encoding # toJSONList :: [First a] -> Value # toEncodingList :: [First a] -> Encoding # | |
ToJSON a => ToJSON (Last a) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Last a -> Encoding # toJSONList :: [Last a] -> Value # toEncodingList :: [Last a] -> Encoding # | |
ToJSON a => ToJSON (Down a) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Down a -> Encoding # toJSONList :: [Down a] -> Value # toEncodingList :: [Down a] -> Encoding # | |
ToJSON a => ToJSON (Dual a) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Dual a -> Encoding # toJSONList :: [Dual a] -> Value # toEncodingList :: [Dual a] -> Encoding # | |
ToJSON a => ToJSON (Product a) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: Product a -> Value # toEncoding :: Product a -> Encoding # toJSONList :: [Product a] -> Value # toEncodingList :: [Product a] -> Encoding # | |
ToJSON a => ToJSON (Sum a) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Sum a -> Encoding # toJSONList :: [Sum a] -> Value # toEncodingList :: [Sum a] -> Encoding # | |
(Generic a, GToJSON' Value Zero (Rep a), GToJSON' Encoding Zero (Rep a)) => ToJSON (Generically a) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: Generically a -> Value # toEncoding :: Generically a -> Encoding # toJSONList :: [Generically a] -> Value # toEncodingList :: [Generically a] -> Encoding # | |
(ToJSON a, Integral a) => ToJSON (Ratio a) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Ratio a -> Encoding # toJSONList :: [Ratio a] -> Value # toEncodingList :: [Ratio a] -> Encoding # | |
ToJSON a => ToJSON (Array a) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Array a -> Encoding # toJSONList :: [Array a] -> Value # toEncodingList :: [Array a] -> Encoding # | |
(Prim a, ToJSON a) => ToJSON (PrimArray a) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: PrimArray a -> Value # toEncoding :: PrimArray a -> Encoding # toJSONList :: [PrimArray a] -> Value # toEncodingList :: [PrimArray a] -> Encoding # | |
ToJSON a => ToJSON (SmallArray a) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: SmallArray a -> Value # toEncoding :: SmallArray a -> Encoding # toJSONList :: [SmallArray a] -> Value # toEncodingList :: [SmallArray a] -> Encoding # | |
ToJSON a => ToJSON (Maybe a) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Maybe a -> Encoding # toJSONList :: [Maybe a] -> Value # toEncodingList :: [Maybe a] -> Encoding # | |
ToJSON a => ToJSON (HashSet a) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: HashSet a -> Value # toEncoding :: HashSet a -> Encoding # toJSONList :: [HashSet a] -> Value # toEncodingList :: [HashSet a] -> Encoding # | |
ToJSON a => ToJSON (Vector a) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Vector a -> Encoding # toJSONList :: [Vector a] -> Value # toEncodingList :: [Vector a] -> Encoding # | |
(Prim a, ToJSON a) => ToJSON (Vector a) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Vector a -> Encoding # toJSONList :: [Vector a] -> Value # toEncodingList :: [Vector a] -> Encoding # | |
(Storable a, ToJSON a) => ToJSON (Vector a) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Vector a -> Encoding # toJSONList :: [Vector a] -> Value # toEncodingList :: [Vector a] -> Encoding # | |
(Vector Vector a, ToJSON a) => ToJSON (Vector a) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Vector a -> Encoding # toJSONList :: [Vector a] -> Value # toEncodingList :: [Vector a] -> Encoding # | |
ToJSON a => ToJSON (Maybe a) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Maybe a -> Encoding # toJSONList :: [Maybe a] -> Value # toEncodingList :: [Maybe a] -> Encoding # | |
ToJSON a => ToJSON (Solo a) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Solo a -> Encoding # toJSONList :: [Solo a] -> Value # toEncodingList :: [Solo a] -> Encoding # | |
ToJSON a => ToJSON [a] | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: [a] -> Encoding # toJSONList :: [[a]] -> Value # toEncodingList :: [[a]] -> Encoding # | |
HasResolution a => ToJSON (Fixed a) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Fixed a -> Encoding # toJSONList :: [Fixed a] -> Value # toEncodingList :: [Fixed a] -> Encoding # | |
(ToJSON v, ToJSONKey k) => ToJSON (Map k v) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Map k v -> Encoding # toJSONList :: [Map k v] -> Value # toEncodingList :: [Map k v] -> Encoding # | |
(ToJSON a, ToJSON b) => ToJSON (Either a b) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: Either a b -> Value # toEncoding :: Either a b -> Encoding # toJSONList :: [Either a b] -> Value # toEncodingList :: [Either a b] -> Encoding # | |
ToJSON (Proxy a) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Proxy a -> Encoding # toJSONList :: [Proxy a] -> Value # toEncodingList :: [Proxy a] -> Encoding # | |
(ToJSON a, ToJSON b) => ToJSON (Either a b) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: Either a b -> Value # toEncoding :: Either a b -> Encoding # toJSONList :: [Either a b] -> Value # toEncodingList :: [Either a b] -> Encoding # | |
(ToJSON a, ToJSON b) => ToJSON (These a b) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: These a b -> Value # toEncoding :: These a b -> Encoding # toJSONList :: [These a b] -> Value # toEncodingList :: [These a b] -> Encoding # | |
(ToJSON a, ToJSON b) => ToJSON (Pair a b) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Pair a b -> Encoding # toJSONList :: [Pair a b] -> Value # toEncodingList :: [Pair a b] -> Encoding # | |
(ToJSON a, ToJSON b) => ToJSON (These a b) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: These a b -> Value # toEncoding :: These a b -> Encoding # toJSONList :: [These a b] -> Value # toEncodingList :: [These a b] -> Encoding # | |
(ToJSON v, ToJSONKey k) => ToJSON (HashMap k v) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: HashMap k v -> Value # toEncoding :: HashMap k v -> Encoding # toJSONList :: [HashMap k v] -> Value # toEncodingList :: [HashMap k v] -> Encoding # | |
(ToJSON a, ToJSON b) => ToJSON (a, b) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: (a, b) -> Encoding # toJSONList :: [(a, b)] -> Value # toEncodingList :: [(a, b)] -> Encoding # | |
ToJSON a => ToJSON (Const a b) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: Const a b -> Value # toEncoding :: Const a b -> Encoding # toJSONList :: [Const a b] -> Value # toEncodingList :: [Const a b] -> Encoding # | |
ToJSON b => ToJSON (Tagged a b) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: Tagged a b -> Value # toEncoding :: Tagged a b -> Encoding # toJSONList :: [Tagged a b] -> Value # toEncodingList :: [Tagged a b] -> Encoding # | |
(ToJSON1 f, ToJSON1 g, ToJSON a) => ToJSON (These1 f g a) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: These1 f g a -> Value # toEncoding :: These1 f g a -> Encoding # toJSONList :: [These1 f g a] -> Value # toEncodingList :: [These1 f g a] -> Encoding # | |
(ToJSON a, ToJSON b, ToJSON c) => ToJSON (a, b, c) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: (a, b, c) -> Value # toEncoding :: (a, b, c) -> Encoding # toJSONList :: [(a, b, c)] -> Value # toEncodingList :: [(a, b, c)] -> Encoding # | |
(ToJSON1 f, ToJSON1 g, ToJSON a) => ToJSON (Product f g a) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: Product f g a -> Value # toEncoding :: Product f g a -> Encoding # toJSONList :: [Product f g a] -> Value # toEncodingList :: [Product f g a] -> Encoding # | |
(ToJSON1 f, ToJSON1 g, ToJSON a) => ToJSON (Sum f g a) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: Sum f g a -> Value # toEncoding :: Sum f g a -> Encoding # toJSONList :: [Sum f g a] -> Value # toEncodingList :: [Sum f g a] -> Encoding # | |
(ToJSON a, ToJSON b, ToJSON c, ToJSON d) => ToJSON (a, b, c, d) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: (a, b, c, d) -> Value # toEncoding :: (a, b, c, d) -> Encoding # toJSONList :: [(a, b, c, d)] -> Value # toEncodingList :: [(a, b, c, d)] -> Encoding # | |
(ToJSON1 f, ToJSON1 g, ToJSON a) => ToJSON (Compose f g a) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: Compose f g a -> Value # toEncoding :: Compose f g a -> Encoding # toJSONList :: [Compose f g a] -> Value # toEncodingList :: [Compose f g a] -> Encoding # | |
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e) => ToJSON (a, b, c, d, e) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: (a, b, c, d, e) -> Value # toEncoding :: (a, b, c, d, e) -> Encoding # toJSONList :: [(a, b, c, d, e)] -> Value # toEncodingList :: [(a, b, c, d, e)] -> Encoding # | |
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f) => ToJSON (a, b, c, d, e, f) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: (a, b, c, d, e, f) -> Value # toEncoding :: (a, b, c, d, e, f) -> Encoding # toJSONList :: [(a, b, c, d, e, f)] -> Value # toEncodingList :: [(a, b, c, d, e, f)] -> Encoding # | |
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g) => ToJSON (a, b, c, d, e, f, g) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: (a, b, c, d, e, f, g) -> Value # toEncoding :: (a, b, c, d, e, f, g) -> Encoding # toJSONList :: [(a, b, c, d, e, f, g)] -> Value # toEncodingList :: [(a, b, c, d, e, f, g)] -> Encoding # | |
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h) => ToJSON (a, b, c, d, e, f, g, h) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: (a, b, c, d, e, f, g, h) -> Value # toEncoding :: (a, b, c, d, e, f, g, h) -> Encoding # toJSONList :: [(a, b, c, d, e, f, g, h)] -> Value # toEncodingList :: [(a, b, c, d, e, f, g, h)] -> Encoding # | |
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i) => ToJSON (a, b, c, d, e, f, g, h, i) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: (a, b, c, d, e, f, g, h, i) -> Value # toEncoding :: (a, b, c, d, e, f, g, h, i) -> Encoding # toJSONList :: [(a, b, c, d, e, f, g, h, i)] -> Value # toEncodingList :: [(a, b, c, d, e, f, g, h, i)] -> Encoding # | |
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j) => ToJSON (a, b, c, d, e, f, g, h, i, j) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: (a, b, c, d, e, f, g, h, i, j) -> Value # toEncoding :: (a, b, c, d, e, f, g, h, i, j) -> Encoding # toJSONList :: [(a, b, c, d, e, f, g, h, i, j)] -> Value # toEncodingList :: [(a, b, c, d, e, f, g, h, i, j)] -> Encoding # | |
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k) => ToJSON (a, b, c, d, e, f, g, h, i, j, k) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: (a, b, c, d, e, f, g, h, i, j, k) -> Value # toEncoding :: (a, b, c, d, e, f, g, h, i, j, k) -> Encoding # toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k)] -> Value # toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k)] -> Encoding # | |
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Value # toEncoding :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Encoding # toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k, l)] -> Value # toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k, l)] -> Encoding # | |
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l, ToJSON m) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l, m) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Value # toEncoding :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Encoding # toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m)] -> Value # toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m)] -> Encoding # omitField :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Bool # | |
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l, ToJSON m, ToJSON n) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Value # toEncoding :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Encoding # toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] -> Value # toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] -> Encoding # omitField :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Bool # | |
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l, ToJSON m, ToJSON n, ToJSON o) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Value # toEncoding :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Encoding # toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)] -> Value # toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)] -> Encoding # omitField :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Bool # |
Minimal complete definition
Nothing
Methods
parseJSON :: Value -> Parser a #
parseJSONList :: Value -> Parser [a] #
omittedField :: Maybe a #
Instances
FromJSON Key | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser Key # parseJSONList :: Value -> Parser [Key] # omittedField :: Maybe Key # | |
FromJSON DotNetTime | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser DotNetTime # parseJSONList :: Value -> Parser [DotNetTime] # omittedField :: Maybe DotNetTime # | |
FromJSON Value | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON IntSet | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser IntSet # parseJSONList :: Value -> Parser [IntSet] # omittedField :: Maybe IntSet # | |
FromJSON Void | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser Void # parseJSONList :: Value -> Parser [Void] # omittedField :: Maybe Void # | |
FromJSON All | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser All # parseJSONList :: Value -> Parser [All] # omittedField :: Maybe All # | |
FromJSON Any | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser Any # parseJSONList :: Value -> Parser [Any] # omittedField :: Maybe Any # | |
FromJSON Version | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser Version # parseJSONList :: Value -> Parser [Version] # omittedField :: Maybe Version # | |
FromJSON CTime | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser CTime # parseJSONList :: Value -> Parser [CTime] # omittedField :: Maybe CTime # | |
FromJSON Int16 | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser Int16 # parseJSONList :: Value -> Parser [Int16] # omittedField :: Maybe Int16 # | |
FromJSON Int32 | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser Int32 # parseJSONList :: Value -> Parser [Int32] # omittedField :: Maybe Int32 # | |
FromJSON Int64 | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser Int64 # parseJSONList :: Value -> Parser [Int64] # omittedField :: Maybe Int64 # | |
FromJSON Int8 | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser Int8 # parseJSONList :: Value -> Parser [Int8] # omittedField :: Maybe Int8 # | |
FromJSON Word16 | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser Word16 # parseJSONList :: Value -> Parser [Word16] # omittedField :: Maybe Word16 # | |
FromJSON Word32 | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser Word32 # parseJSONList :: Value -> Parser [Word32] # omittedField :: Maybe Word32 # | |
FromJSON Word64 | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser Word64 # parseJSONList :: Value -> Parser [Word64] # omittedField :: Maybe Word64 # | |
FromJSON Word8 | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser Word8 # parseJSONList :: Value -> Parser [Word8] # omittedField :: Maybe Word8 # | |
FromJSON Ordering | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser Ordering # parseJSONList :: Value -> Parser [Ordering] # omittedField :: Maybe Ordering # | |
FromJSON URI | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser URI # parseJSONList :: Value -> Parser [URI] # omittedField :: Maybe URI # | |
FromJSON Scientific | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser Scientific # parseJSONList :: Value -> Parser [Scientific] # omittedField :: Maybe Scientific # | |
FromJSON Text | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser Text # parseJSONList :: Value -> Parser [Text] # omittedField :: Maybe Text # | |
FromJSON Text | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser Text # parseJSONList :: Value -> Parser [Text] # omittedField :: Maybe Text # | |
FromJSON ShortText | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser ShortText # parseJSONList :: Value -> Parser [ShortText] # omittedField :: Maybe ShortText # | |
FromJSON CalendarDiffDays | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser CalendarDiffDays # parseJSONList :: Value -> Parser [CalendarDiffDays] # omittedField :: Maybe CalendarDiffDays # | |
FromJSON Day | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser Day # parseJSONList :: Value -> Parser [Day] # omittedField :: Maybe Day # | |
FromJSON Month | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser Month # parseJSONList :: Value -> Parser [Month] # omittedField :: Maybe Month # | |
FromJSON Quarter | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser Quarter # parseJSONList :: Value -> Parser [Quarter] # omittedField :: Maybe Quarter # | |
FromJSON QuarterOfYear | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser QuarterOfYear # parseJSONList :: Value -> Parser [QuarterOfYear] # omittedField :: Maybe QuarterOfYear # | |
FromJSON DayOfWeek | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser DayOfWeek # parseJSONList :: Value -> Parser [DayOfWeek] # omittedField :: Maybe DayOfWeek # | |
FromJSON DiffTime | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser DiffTime # parseJSONList :: Value -> Parser [DiffTime] # omittedField :: Maybe DiffTime # | |
FromJSON NominalDiffTime | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser NominalDiffTime # parseJSONList :: Value -> Parser [NominalDiffTime] # omittedField :: Maybe NominalDiffTime # | |
FromJSON SystemTime | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser SystemTime # parseJSONList :: Value -> Parser [SystemTime] # omittedField :: Maybe SystemTime # | |
FromJSON UTCTime | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser UTCTime # parseJSONList :: Value -> Parser [UTCTime] # omittedField :: Maybe UTCTime # | |
FromJSON CalendarDiffTime | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser CalendarDiffTime # parseJSONList :: Value -> Parser [CalendarDiffTime] # omittedField :: Maybe CalendarDiffTime # | |
FromJSON LocalTime | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser LocalTime # parseJSONList :: Value -> Parser [LocalTime] # omittedField :: Maybe LocalTime # | |
FromJSON TimeOfDay | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser TimeOfDay # parseJSONList :: Value -> Parser [TimeOfDay] # omittedField :: Maybe TimeOfDay # | |
FromJSON ZonedTime | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser ZonedTime # parseJSONList :: Value -> Parser [ZonedTime] # omittedField :: Maybe ZonedTime # | |
FromJSON UUID | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser UUID # parseJSONList :: Value -> Parser [UUID] # omittedField :: Maybe UUID # | |
FromJSON Integer | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser Integer # parseJSONList :: Value -> Parser [Integer] # omittedField :: Maybe Integer # | |
FromJSON Natural | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser Natural # parseJSONList :: Value -> Parser [Natural] # omittedField :: Maybe Natural # | |
FromJSON () | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser () # parseJSONList :: Value -> Parser [()] # omittedField :: Maybe () # | |
FromJSON Bool | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser Bool # parseJSONList :: Value -> Parser [Bool] # omittedField :: Maybe Bool # | |
FromJSON Char | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser Char # parseJSONList :: Value -> Parser [Char] # omittedField :: Maybe Char # | |
FromJSON Double | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser Double # parseJSONList :: Value -> Parser [Double] # omittedField :: Maybe Double # | |
FromJSON Float | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser Float # parseJSONList :: Value -> Parser [Float] # omittedField :: Maybe Float # | |
FromJSON Int | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser Int # parseJSONList :: Value -> Parser [Int] # omittedField :: Maybe Int # | |
FromJSON Word | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser Word # parseJSONList :: Value -> Parser [Word] # omittedField :: Maybe Word # | |
FromJSON v => FromJSON (KeyMap v) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (KeyMap v) # parseJSONList :: Value -> Parser [KeyMap v] # omittedField :: Maybe (KeyMap v) # | |
FromJSON a => FromJSON (First a) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (First a) # parseJSONList :: Value -> Parser [First a] # omittedField :: Maybe (First a) # | |
FromJSON a => FromJSON (Last a) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (Last a) # parseJSONList :: Value -> Parser [Last a] # omittedField :: Maybe (Last a) # | |
FromJSON a => FromJSON (Max a) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (Max a) # parseJSONList :: Value -> Parser [Max a] # omittedField :: Maybe (Max a) # | |
FromJSON a => FromJSON (Min a) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (Min a) # parseJSONList :: Value -> Parser [Min a] # omittedField :: Maybe (Min a) # | |
FromJSON a => FromJSON (WrappedMonoid a) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (WrappedMonoid a) # parseJSONList :: Value -> Parser [WrappedMonoid a] # omittedField :: Maybe (WrappedMonoid a) # | |
FromJSON a => FromJSON (IntMap a) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (IntMap a) # parseJSONList :: Value -> Parser [IntMap a] # omittedField :: Maybe (IntMap a) # | |
FromJSON a => FromJSON (Seq a) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (Seq a) # parseJSONList :: Value -> Parser [Seq a] # omittedField :: Maybe (Seq a) # | |
(Ord a, FromJSON a) => FromJSON (Set a) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (Set a) # parseJSONList :: Value -> Parser [Set a] # omittedField :: Maybe (Set a) # | |
FromJSON v => FromJSON (Tree v) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (Tree v) # parseJSONList :: Value -> Parser [Tree v] # omittedField :: Maybe (Tree v) # | |
FromJSON1 f => FromJSON (Fix f) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (Fix f) # parseJSONList :: Value -> Parser [Fix f] # omittedField :: Maybe (Fix f) # | |
(FromJSON1 f, Functor f) => FromJSON (Mu f) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (Mu f) # parseJSONList :: Value -> Parser [Mu f] # omittedField :: Maybe (Mu f) # | |
(FromJSON1 f, Functor f) => FromJSON (Nu f) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (Nu f) # parseJSONList :: Value -> Parser [Nu f] # omittedField :: Maybe (Nu f) # | |
FromJSON a => FromJSON (DNonEmpty a) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (DNonEmpty a) # parseJSONList :: Value -> Parser [DNonEmpty a] # omittedField :: Maybe (DNonEmpty a) # | |
FromJSON a => FromJSON (DList a) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (DList a) # parseJSONList :: Value -> Parser [DList a] # omittedField :: Maybe (DList a) # | |
FromJSON a => FromJSON (NonEmpty a) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (NonEmpty a) # parseJSONList :: Value -> Parser [NonEmpty a] # omittedField :: Maybe (NonEmpty a) # | |
FromJSON a => FromJSON (Identity a) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (Identity a) # parseJSONList :: Value -> Parser [Identity a] # omittedField :: Maybe (Identity a) # | |
FromJSON a => FromJSON (First a) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (First a) # parseJSONList :: Value -> Parser [First a] # omittedField :: Maybe (First a) # | |
FromJSON a => FromJSON (Last a) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (Last a) # parseJSONList :: Value -> Parser [Last a] # omittedField :: Maybe (Last a) # | |
FromJSON a => FromJSON (Down a) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (Down a) # parseJSONList :: Value -> Parser [Down a] # omittedField :: Maybe (Down a) # | |
FromJSON a => FromJSON (Dual a) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (Dual a) # parseJSONList :: Value -> Parser [Dual a] # omittedField :: Maybe (Dual a) # | |
FromJSON a => FromJSON (Product a) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (Product a) # parseJSONList :: Value -> Parser [Product a] # omittedField :: Maybe (Product a) # | |
FromJSON a => FromJSON (Sum a) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (Sum a) # parseJSONList :: Value -> Parser [Sum a] # omittedField :: Maybe (Sum a) # | |
(Generic a, GFromJSON Zero (Rep a)) => FromJSON (Generically a) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (Generically a) # parseJSONList :: Value -> Parser [Generically a] # omittedField :: Maybe (Generically a) # | |
(FromJSON a, Integral a) => FromJSON (Ratio a) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (Ratio a) # parseJSONList :: Value -> Parser [Ratio a] # omittedField :: Maybe (Ratio a) # | |
FromJSON a => FromJSON (Array a) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (Array a) # parseJSONList :: Value -> Parser [Array a] # omittedField :: Maybe (Array a) # | |
(Prim a, FromJSON a) => FromJSON (PrimArray a) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (PrimArray a) # parseJSONList :: Value -> Parser [PrimArray a] # omittedField :: Maybe (PrimArray a) # | |
FromJSON a => FromJSON (SmallArray a) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (SmallArray a) # parseJSONList :: Value -> Parser [SmallArray a] # omittedField :: Maybe (SmallArray a) # | |
FromJSON a => FromJSON (Maybe a) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (Maybe a) # parseJSONList :: Value -> Parser [Maybe a] # omittedField :: Maybe (Maybe a) # | |
(Eq a, Hashable a, FromJSON a) => FromJSON (HashSet a) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (HashSet a) # parseJSONList :: Value -> Parser [HashSet a] # omittedField :: Maybe (HashSet a) # | |
FromJSON a => FromJSON (Vector a) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (Vector a) # parseJSONList :: Value -> Parser [Vector a] # omittedField :: Maybe (Vector a) # | |
(Prim a, FromJSON a) => FromJSON (Vector a) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (Vector a) # parseJSONList :: Value -> Parser [Vector a] # omittedField :: Maybe (Vector a) # | |
(Storable a, FromJSON a) => FromJSON (Vector a) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (Vector a) # parseJSONList :: Value -> Parser [Vector a] # omittedField :: Maybe (Vector a) # | |
(Vector Vector a, FromJSON a) => FromJSON (Vector a) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (Vector a) # parseJSONList :: Value -> Parser [Vector a] # omittedField :: Maybe (Vector a) # | |
FromJSON a => FromJSON (Maybe a) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (Maybe a) # parseJSONList :: Value -> Parser [Maybe a] # omittedField :: Maybe (Maybe a) # | |
FromJSON a => FromJSON (Solo a) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (Solo a) # parseJSONList :: Value -> Parser [Solo a] # omittedField :: Maybe (Solo a) # | |
FromJSON a => FromJSON [a] | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser [a] # parseJSONList :: Value -> Parser [[a]] # omittedField :: Maybe [a] # | |
HasResolution a => FromJSON (Fixed a) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (Fixed a) # parseJSONList :: Value -> Parser [Fixed a] # omittedField :: Maybe (Fixed a) # | |
(FromJSONKey k, Ord k, FromJSON v) => FromJSON (Map k v) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (Map k v) # parseJSONList :: Value -> Parser [Map k v] # omittedField :: Maybe (Map k v) # | |
(FromJSON a, FromJSON b) => FromJSON (Either a b) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (Either a b) # parseJSONList :: Value -> Parser [Either a b] # omittedField :: Maybe (Either a b) # | |
FromJSON (Proxy a) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (Proxy a) # parseJSONList :: Value -> Parser [Proxy a] # omittedField :: Maybe (Proxy a) # | |
(FromJSON a, FromJSON b) => FromJSON (Either a b) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (Either a b) # parseJSONList :: Value -> Parser [Either a b] # omittedField :: Maybe (Either a b) # | |
(FromJSON a, FromJSON b) => FromJSON (These a b) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (These a b) # parseJSONList :: Value -> Parser [These a b] # omittedField :: Maybe (These a b) # | |
(FromJSON a, FromJSON b) => FromJSON (Pair a b) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (Pair a b) # parseJSONList :: Value -> Parser [Pair a b] # omittedField :: Maybe (Pair a b) # | |
(FromJSON a, FromJSON b) => FromJSON (These a b) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (These a b) # parseJSONList :: Value -> Parser [These a b] # omittedField :: Maybe (These a b) # | |
(FromJSON v, FromJSONKey k, Eq k, Hashable k) => FromJSON (HashMap k v) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (HashMap k v) # parseJSONList :: Value -> Parser [HashMap k v] # omittedField :: Maybe (HashMap k v) # | |
(FromJSON a, FromJSON b) => FromJSON (a, b) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (a, b) # parseJSONList :: Value -> Parser [(a, b)] # omittedField :: Maybe (a, b) # | |
FromJSON a => FromJSON (Const a b) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (Const a b) # parseJSONList :: Value -> Parser [Const a b] # omittedField :: Maybe (Const a b) # | |
FromJSON b => FromJSON (Tagged a b) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (Tagged a b) # parseJSONList :: Value -> Parser [Tagged a b] # omittedField :: Maybe (Tagged a b) # | |
(FromJSON1 f, FromJSON1 g, FromJSON a) => FromJSON (These1 f g a) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (These1 f g a) # parseJSONList :: Value -> Parser [These1 f g a] # omittedField :: Maybe (These1 f g a) # | |
(FromJSON a, FromJSON b, FromJSON c) => FromJSON (a, b, c) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (a, b, c) # parseJSONList :: Value -> Parser [(a, b, c)] # omittedField :: Maybe (a, b, c) # | |
(FromJSON1 f, FromJSON1 g, FromJSON a) => FromJSON (Product f g a) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (Product f g a) # parseJSONList :: Value -> Parser [Product f g a] # omittedField :: Maybe (Product f g a) # | |
(FromJSON1 f, FromJSON1 g, FromJSON a) => FromJSON (Sum f g a) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (Sum f g a) # parseJSONList :: Value -> Parser [Sum f g a] # omittedField :: Maybe (Sum f g a) # | |
(FromJSON a, FromJSON b, FromJSON c, FromJSON d) => FromJSON (a, b, c, d) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (a, b, c, d) # parseJSONList :: Value -> Parser [(a, b, c, d)] # omittedField :: Maybe (a, b, c, d) # | |
(FromJSON1 f, FromJSON1 g, FromJSON a) => FromJSON (Compose f g a) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (Compose f g a) # parseJSONList :: Value -> Parser [Compose f g a] # omittedField :: Maybe (Compose f g a) # | |
(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e) => FromJSON (a, b, c, d, e) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (a, b, c, d, e) # parseJSONList :: Value -> Parser [(a, b, c, d, e)] # omittedField :: Maybe (a, b, c, d, e) # | |
(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f) => FromJSON (a, b, c, d, e, f) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (a, b, c, d, e, f) # parseJSONList :: Value -> Parser [(a, b, c, d, e, f)] # omittedField :: Maybe (a, b, c, d, e, f) # | |
(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g) => FromJSON (a, b, c, d, e, f, g) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (a, b, c, d, e, f, g) # parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g)] # omittedField :: Maybe (a, b, c, d, e, f, g) # | |
(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h) => FromJSON (a, b, c, d, e, f, g, h) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h) # parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h)] # omittedField :: Maybe (a, b, c, d, e, f, g, h) # | |
(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i) => FromJSON (a, b, c, d, e, f, g, h, i) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i) # parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i)] # omittedField :: Maybe (a, b, c, d, e, f, g, h, i) # | |
(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j) => FromJSON (a, b, c, d, e, f, g, h, i, j) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i, j) # parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i, j)] # omittedField :: Maybe (a, b, c, d, e, f, g, h, i, j) # | |
(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k) => FromJSON (a, b, c, d, e, f, g, h, i, j, k) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i, j, k) # parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i, j, k)] # omittedField :: Maybe (a, b, c, d, e, f, g, h, i, j, k) # | |
(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i, j, k, l) # parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i, j, k, l)] # omittedField :: Maybe (a, b, c, d, e, f, g, h, i, j, k, l) # | |
(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l, FromJSON m) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l, m) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i, j, k, l, m) # parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i, j, k, l, m)] # omittedField :: Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m) # | |
(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l, FromJSON m, FromJSON n) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i, j, k, l, m, n) # parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] # omittedField :: Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n) # | |
(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l, FromJSON m, FromJSON n, FromJSON o) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) # parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)] # omittedField :: Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) # |
Custom encoding
isSpecialString :: Text -> Bool Source #
Determine whether a string must be quoted in YAML and can't appear as plain text.
Useful if you want to use setStringStyle
.
Since: 0.10.2.0
data EncodeOptions Source #
Since: 0.10.2.0
defaultEncodeOptions :: EncodeOptions Source #
Since: 0.10.2.0
defaultStringStyle :: StringStyle Source #
Since: 0.11.2.0
setStringStyle :: (Text -> (Tag, Style)) -> EncodeOptions -> EncodeOptions Source #
Set the string style in the encoded YAML. This is a function that decides for each string the type of YAML string to output.
WARNING: You must ensure that special strings (like "yes"
/"no"
/"null"
/"1234"
) are not encoded with the Plain
style, because
then they will be decoded as boolean, null or numeric values. You can use isSpecialString
to detect them.
By default, strings are encoded as follows:
- Any string containing a newline character uses the
Literal
style - Otherwise, any special string (see
isSpecialString
) usesSingleQuoted
- Otherwise, use
Plain
Since: 0.10.2.0
setFormat :: FormatOptions -> EncodeOptions -> EncodeOptions Source #
Set the encoding formatting for the encoded YAML. By default, this is defaultFormatOptions
.
Since: 0.10.2.0
data FormatOptions #
setWidth :: Maybe Int -> FormatOptions -> FormatOptions #
Deprecated
decode :: FromJSON a => ByteString -> Maybe a Source #
Deprecated: Please use decodeEither or decodeThrow, which provide information on how the decode failed
decodeFile :: FromJSON a => FilePath -> IO (Maybe a) Source #
Deprecated: Please use decodeFileEither, which does not confused type-directed and runtime exceptions.
decodeEither :: FromJSON a => ByteString -> Either String a Source #
Deprecated: Please use decodeEither' or decodeThrow, which provide more useful failures