yaml-pretty-extras-0.0.2.2: Extra functionality for pretty printing Yaml documents.

Copyright(c) Daniel Firth 2018
LicenseBSD3
Maintainerlocallycompact@gmail.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Data.Yaml.Pretty.Extras

Contents

Description

This file defines yaml pretty printers with additional MonadThrow helpers and RIO display functionality.

Synopsis

Documentation

module Data.Yaml

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

Minimal complete definition

fieldOrder

Methods

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.

inplace :: (FilePath -> FilePath -> a) -> FilePath -> a Source #

Performs a file operation in place

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.