Copyright | (c) Daniel Firth 2018 |
---|---|
License | BSD3 |
Maintainer | locallycompact@gmail.com |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
This file defines yaml pretty printers with additional MonadThrow helpers and RIO display functionality.
- module Data.Yaml
- module Data.Yaml.Pretty
- class ToJSON a => ToPrettyYaml a where
- encodeFilePretty :: MonadIO m => ToPrettyYaml a => FilePath -> a -> m ()
- displayPrettyYaml :: ToPrettyYaml a => a -> Utf8Builder
- decodeFileThrowLogged :: (MonadReader env m, MonadIO m, HasLogFunc env, FromJSON b, ToPrettyYaml b, Typeable b) => FilePath -> m b
- encodeFilePrettyLogged :: (MonadReader env m, MonadIO m, HasLogFunc env, ToPrettyYaml b, Typeable b) => FilePath -> b -> m ()
- transformFile :: (MonadIO m, FromJSON a1, ToPrettyYaml a2) => FilePath -> FilePath -> (a1 -> a2) -> m a2
- inplace :: (FilePath -> FilePath -> a) -> FilePath -> a
- sanitizeFile :: (MonadIO m, FromJSON a, ToPrettyYaml a) => FilePath -> m a
- overFile :: (MonadIO m, FromJSON a1, ToPrettyYaml a2) => FilePath -> FilePath -> ASetter a1 a2 a b -> (a -> b) -> m a2
- traverseOfFile :: (MonadIO m, FromJSON a1, ToPrettyYaml a2) => FilePath -> FilePath -> LensLike m a1 a2 b1 b2 -> (b1 -> m b2) -> m a2
Documentation
module Data.Yaml
module Data.Yaml.Pretty
Yaml Pretty Printers
class ToJSON a => ToPrettyYaml a where Source #
Augments ToJSON by allowing specification of a fieldOrder for printing.
data Person = { name :: Text, age :: Int, job :: Text } deriving (Eq, FromJSON, Generic, Show, ToJSON) instance ToPrettyYaml Person where fieldOrder = const ["name", "age", "job"]
fieldOrder :: a -> [Text] Source #
The order that detected fields should be printed in, fields that aren't found in this function will be printed non-deterministically.
dropNull :: a -> Bool Source #
Whether to drop null elements on this type.
toPrettyYaml :: a -> ByteString Source #
Prints a Yaml ByteString according to specified fieldOrder.
encodeFilePretty :: MonadIO m => ToPrettyYaml a => FilePath -> a -> m () Source #
A version of Data.Yaml's encodeFile using toPrettyYaml
instead of toJSON
RIO Helpers (Codecs and Logging)
displayPrettyYaml :: ToPrettyYaml a => a -> Utf8Builder Source #
Displays a ToPrettyYaml instance as Utf8, for use with RIO log functions
decodeFileThrowLogged :: (MonadReader env m, MonadIO m, HasLogFunc env, FromJSON b, ToPrettyYaml b, Typeable b) => FilePath -> m b Source #
decodeFileThrow with info logging, reports what was parsed via RIO's logInfo
encodeFilePrettyLogged :: (MonadReader env m, MonadIO m, HasLogFunc env, ToPrettyYaml b, Typeable b) => FilePath -> b -> m () Source #
encodeFilePretty with info logging, reports what was saved to disk via RIO's logInfo
transformFile :: (MonadIO m, FromJSON a1, ToPrettyYaml a2) => FilePath -> FilePath -> (a1 -> a2) -> m a2 Source #
Run a function over a decoded file f and save the result to g, passthrough the new value.
sanitizeFile :: (MonadIO m, FromJSON a, ToPrettyYaml a) => FilePath -> m a Source #
Perform a roundtrip decode/encode on a file to rearrange field order. Doesn't change the type.
overFile :: (MonadIO m, FromJSON a1, ToPrettyYaml a2) => FilePath -> FilePath -> ASetter a1 a2 a b -> (a -> b) -> m a2 Source #
Uses a lens over to modify a file, passthrough the new value.
traverseOfFile :: (MonadIO m, FromJSON a1, ToPrettyYaml a2) => FilePath -> FilePath -> LensLike m a1 a2 b1 b2 -> (b1 -> m b2) -> m a2 Source #
Use a lens traverseOf to modify a file, passthrough the new value.