{-# OPTIONS_GHC -fno-warn-dodgy-exports -fno-warn-duplicate-exports #-}
module Autodocodec.Yaml
(
encodeYamlViaCodec,
eitherDecodeYamlViaCodec,
readYamlConfigFile,
readFirstYamlConfigFile,
renderColouredSchemaViaCodec,
renderColouredSchemaVia,
renderPlainSchemaViaCodec,
renderPlainSchemaVia,
schemaChunksViaCodec,
schemaChunksVia,
jsonSchemaChunks,
jsonSchemaChunkLines,
toYamlViaCodec,
toYamlVia,
module Autodocodec.Yaml.Schema,
module Autodocodec.Yaml.IO,
module Autodocodec.Yaml.Encode,
)
where
import Autodocodec
import Autodocodec.Yaml.Encode
import Autodocodec.Yaml.IO
import Autodocodec.Yaml.Schema
import Data.ByteString
import qualified Data.Yaml as Yaml
import qualified Data.Yaml.Builder as Yaml
encodeYamlViaCodec :: (HasCodec a) => a -> ByteString
encodeYamlViaCodec :: forall a. HasCodec a => a -> ByteString
encodeYamlViaCodec = Autodocodec a -> ByteString
forall a. ToYaml a => a -> ByteString
Yaml.toByteString (Autodocodec a -> ByteString)
-> (a -> Autodocodec a) -> a -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Autodocodec a
forall a. a -> Autodocodec a
Autodocodec
eitherDecodeYamlViaCodec :: (HasCodec a) => ByteString -> Either Yaml.ParseException a
eitherDecodeYamlViaCodec :: forall a. HasCodec a => ByteString -> Either ParseException a
eitherDecodeYamlViaCodec = (Autodocodec a -> a)
-> Either ParseException (Autodocodec a) -> Either ParseException a
forall a b.
(a -> b) -> Either ParseException a -> Either ParseException b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Autodocodec a -> a
forall a. Autodocodec a -> a
unAutodocodec (Either ParseException (Autodocodec a) -> Either ParseException a)
-> (ByteString -> Either ParseException (Autodocodec a))
-> ByteString
-> Either ParseException a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either ParseException (Autodocodec a)
forall a. FromJSON a => ByteString -> Either ParseException a
Yaml.decodeEither'