Safe Haskell | Safe-Inferred |
---|---|
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 { }
- | 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 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
- class FromJSON a where
- 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 | |
FromString Encoding | |
Defined in Data.Aeson.Types.ToJSON Methods fromString :: String -> Encoding | |
FromString Value | |
Defined in Data.Aeson.Types.ToJSON Methods fromString :: String -> Value | |
KeyValue Object | |
Defined in Data.Aeson.Types.ToJSON | |
KeyValue Pair | |
Defined in Data.Aeson.Types.ToJSON | |
ToJSON Value | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Value -> Encoding # toJSONList :: [Value] -> Value # toEncodingList :: [Value] -> Encoding # | |
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 | |
Read Value | |
Defined in Data.Aeson.Types.Internal | |
Show Value | |
NFData Value | |
Defined in Data.Aeson.Types.Internal | |
Eq Value | |
Ord Value | |
Hashable Value | |
Defined in Data.Aeson.Types.Internal | |
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 LiftedRep -> Type) | |
Defined in Data.Aeson.Types.ToJSON Methods gToJSON :: Options -> ToArgs Encoding arity a -> U1 a -> Encoding | |
GToJSON' Value arity (U1 :: TYPE LiftedRep -> Type) | |
Defined in Data.Aeson.Types.ToJSON | |
GToJSON' Value arity (V1 :: TYPE LiftedRep -> 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 LiftedRep -> 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 LiftedRep -> 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 | |
v ~ Value => KeyValuePair v (DList Pair) | |
Defined in Data.Aeson.Types.ToJSON Methods pair :: Key -> v -> DList Pair | |
type Rep Value | |
Defined in Data.Aeson.Types.Internal type Rep Value = D1 ('MetaData "Value" "Data.Aeson.Types.Internal" "aeson-2.0.3.0-4oevyETfuymIgvSNtKIv18" '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 | |
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 Source #
Constructors
YamlException String | |
YamlParseException | problem, context, index, position line, position column |
Fields
|
Instances
Exception YamlException | |
Defined in Text.Libyaml Methods toException :: YamlException -> SomeException fromException :: SomeException -> Maybe YamlException displayException :: YamlException -> String | |
Show YamlException | |
Defined in Text.Libyaml Methods showsPrec :: Int -> YamlException -> ShowS show :: YamlException -> String showList :: [YamlException] -> ShowS |
The pointer position
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 Methods toEncoding :: Value -> Encoding # toJSONList :: [Value] -> Value # toEncodingList :: [Value] -> Encoding # | |
ToJSON Number | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Number -> Encoding # toJSONList :: [Number] -> Value # toEncodingList :: [Number] -> Encoding # | |
ToJSON Version | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Version -> Encoding # toJSONList :: [Version] -> Value # toEncodingList :: [Version] -> Encoding # | |
ToJSON Void | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Void -> Encoding # toJSONList :: [Void] -> Value # toEncodingList :: [Void] -> 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 IntSet | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: IntSet -> Encoding # toJSONList :: [IntSet] -> Value # toEncodingList :: [IntSet] -> Encoding # | |
ToJSON Ordering | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Ordering -> Encoding # toJSONList :: [Ordering] -> Value # toEncodingList :: [Ordering] -> 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 (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 (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 (Dual a) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Dual a -> Encoding # toJSONList :: [Dual a] -> Value # toEncodingList :: [Dual 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 (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 (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 (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 (Maybe a) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Maybe a -> Encoding # toJSONList :: [Maybe a] -> Value # toEncodingList :: [Maybe a] -> Encoding # | |
ToJSON a => ToJSON (a) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: (a) -> Encoding # toJSONList :: [(a)] -> Value # toEncodingList :: [(a)] -> Encoding # | |
ToJSON a => ToJSON [a] | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: [a] -> Encoding # toJSONList :: [[a]] -> Value # toEncodingList :: [[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 # | |
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 (Proxy a) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Proxy a -> Encoding # toJSONList :: [Proxy a] -> Value # toEncodingList :: [Proxy 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 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 # | |
(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 # | |
(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 # |
Minimal complete definition
Nothing
Instances
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 Source #
Contains options relating to the formatting (indendation, width) of the YAML output.
Since: libyaml-0.10.2.0
defaultFormatOptions :: FormatOptions Source #
Since: libyaml-0.10.2.0
setWidth :: Maybe Int -> FormatOptions -> FormatOptions Source #
Set the maximum number of columns in the YAML output, or Nothing
for infinite. By default, the limit is 80 characters.
Since: libyaml-0.10.2.0
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