{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
module Test.Syd.Autodocodec
(
goldenYamlSchemaFileVia,
pureGoldenYamlSchemaFileVia,
pureGoldenYamlSchemaFileViaCodec,
)
where
import Autodocodec
import Autodocodec.Yaml
import Data.Text (Text)
import Test.Syd
goldenYamlSchemaFileVia :: FilePath -> IO (ValueCodec input output) -> GoldenTest Text
goldenYamlSchemaFileVia :: forall input output.
FilePath -> IO (ValueCodec input output) -> GoldenTest Text
goldenYamlSchemaFileVia FilePath
fp IO (ValueCodec input output)
produceCodec = FilePath -> IO Text -> GoldenTest Text
goldenTextFile FilePath
fp (forall input output. ValueCodec input output -> Text
renderColouredSchemaVia forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO (ValueCodec input output)
produceCodec)
pureGoldenYamlSchemaFileVia :: FilePath -> ValueCodec input output -> GoldenTest Text
pureGoldenYamlSchemaFileVia :: forall input output.
FilePath -> ValueCodec input output -> GoldenTest Text
pureGoldenYamlSchemaFileVia FilePath
fp ValueCodec input output
c = forall input output.
FilePath -> IO (ValueCodec input output) -> GoldenTest Text
goldenYamlSchemaFileVia FilePath
fp forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a. Applicative f => a -> f a
pure ValueCodec input output
c
pureGoldenYamlSchemaFileViaCodec :: forall a. HasCodec a => FilePath -> GoldenTest Text
pureGoldenYamlSchemaFileViaCodec :: forall a. HasCodec a => FilePath -> GoldenTest Text
pureGoldenYamlSchemaFileViaCodec FilePath
fp = forall input output.
FilePath -> ValueCodec input output -> GoldenTest Text
pureGoldenYamlSchemaFileVia FilePath
fp (forall value. HasCodec value => JSONCodec value
codec @a)