mirror of
https://github.com/NorfairKing/autodocodec.git
synced 2024-12-02 09:52:01 +03:00
golden test for the show output
This commit is contained in:
parent
e69903fa9e
commit
26bafc1696
@ -52,6 +52,7 @@ test-suite autodocodec-api-usage-test
|
||||
other-modules:
|
||||
Autodocodec.Aeson.SchemaSpec
|
||||
Autodocodec.AesonSpec
|
||||
Autodocodec.ShowSpec
|
||||
Autodocodec.SwaggerSpec
|
||||
Autodocodec.Yaml.DocumentSpec
|
||||
Paths_autodocodec_api_usage
|
||||
|
61
autodocodec-api-usage/test/Autodocodec/ShowSpec.hs
Normal file
61
autodocodec-api-usage/test/Autodocodec/ShowSpec.hs
Normal file
@ -0,0 +1,61 @@
|
||||
{-# LANGUAGE AllowAmbiguousTypes #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
{-# LANGUAGE TypeApplications #-}
|
||||
|
||||
module Autodocodec.ShowSpec (spec) where
|
||||
|
||||
import Autodocodec
|
||||
import Autodocodec.Aeson
|
||||
import Autodocodec.Usage
|
||||
import Data.Aeson (FromJSON (..), ToJSON (..))
|
||||
import qualified Data.Aeson as JSON
|
||||
import qualified Data.Aeson.Types as JSON
|
||||
import Data.Data
|
||||
import Data.GenValidity
|
||||
import Data.GenValidity.Aeson ()
|
||||
import Data.GenValidity.Scientific ()
|
||||
import Data.GenValidity.Text ()
|
||||
import Data.Int
|
||||
import Data.Scientific
|
||||
import Data.Text (Text)
|
||||
import qualified Data.Text.Lazy as LT
|
||||
import Data.Word
|
||||
import Test.Syd
|
||||
import Test.Syd.Validity
|
||||
import Test.Syd.Validity.Utils
|
||||
|
||||
spec :: Spec
|
||||
spec = do
|
||||
showCodecSpec @Bool "bool"
|
||||
showCodecSpec @Ordering "ordering"
|
||||
showCodecSpec @Char "char"
|
||||
showCodecSpec @Text "text"
|
||||
showCodecSpec @LT.Text "lazy-text"
|
||||
showCodecSpec @String "string"
|
||||
showCodecSpec @Scientific "scientific"
|
||||
showCodecSpec @JSON.Value "value"
|
||||
showCodecSpec @Int "int"
|
||||
showCodecSpec @Int8 "int8"
|
||||
showCodecSpec @Int16 "int16"
|
||||
showCodecSpec @Int32 "int32"
|
||||
showCodecSpec @Int64 "int64"
|
||||
showCodecSpec @Word "word"
|
||||
showCodecSpec @Word8 "word8"
|
||||
showCodecSpec @Word16 "word16"
|
||||
showCodecSpec @Word32 "word32"
|
||||
showCodecSpec @Word64 "word64"
|
||||
showCodecSpec @(Maybe Text) "maybe-text"
|
||||
showCodecSpec @(Either Bool Text) "either-bool-text"
|
||||
showCodecSpec @(Either (Either Bool Scientific) Text) "either-either-bool-scientific-text"
|
||||
showCodecSpec @[Text] "list-text"
|
||||
showCodecSpec @Fruit "fruit"
|
||||
showCodecSpec @Example "example"
|
||||
showCodecSpec @Recursive "recursive"
|
||||
showCodecSpec @Via "via"
|
||||
|
||||
showCodecSpec :: forall a. (Show a, Eq a, Typeable a, GenValid a, HasCodec a) => FilePath -> Spec
|
||||
showCodecSpec filePath =
|
||||
describe ("showCodecSpec " <> nameOf @a) $
|
||||
it "outputs the same shown codec information as before" $
|
||||
pureGoldenStringFile ("test_resources/show-codec/" <> filePath <> ".txt") (showCodecABit (codec @a))
|
1
autodocodec-api-usage/test_resources/show-codec/bool.txt
Normal file
1
autodocodec-api-usage/test_resources/show-codec/bool.txt
Normal file
@ -0,0 +1 @@
|
||||
BoolCodec Nothing
|
1
autodocodec-api-usage/test_resources/show-codec/char.txt
Normal file
1
autodocodec-api-usage/test_resources/show-codec/char.txt
Normal file
@ -0,0 +1 @@
|
||||
MapCodec (MapCodec (StringCodec Nothing))
|
@ -0,0 +1 @@
|
||||
EitherCodec (ObjectOfCodec Nothing (RequiredKeyCodec "Left" Nothing (BoolCodec Nothing))) (ObjectOfCodec Nothing (RequiredKeyCodec "Right" Nothing (StringCodec Nothing)))
|
@ -0,0 +1 @@
|
||||
EitherCodec (ObjectOfCodec Nothing (RequiredKeyCodec "Left" Nothing (EitherCodec (ObjectOfCodec Nothing (RequiredKeyCodec "Left" Nothing (BoolCodec Nothing))) (ObjectOfCodec Nothing (RequiredKeyCodec "Right" Nothing (NumberCodec Nothing)))))) (ObjectOfCodec Nothing (RequiredKeyCodec "Right" Nothing (StringCodec Nothing)))
|
@ -0,0 +1 @@
|
||||
ObjectOfCodec Just "Example" (ApCodec (ApCodec (ApCodec (ApCodec (ApCodec (ApCodec (MapCodec (MapCodec (RequiredKeyCodec "text" (Just "a text") (StringCodec Nothing)))) (MapCodec (RequiredKeyCodec "bool" (Just "a bool") (BoolCodec Nothing)))) (MapCodec (RequiredKeyCodec "maybe" (Just "a maybe text") (MapCodec (EitherCodec NullCodec (StringCodec Nothing)))))) (MapCodec (OptionalKeyCodec "optional" (Just "an optional text") (StringCodec Nothing)))) (MapCodec (MapCodec (OptionalKeyCodec "optional-or-null" (Just "an optional-or-null text") (MapCodec (EitherCodec NullCodec (StringCodec Nothing))))))) (MapCodec (OptionalKeyWithDefaultCodec "optional-with-default" (StringCodec Nothing) (Just "an optional text with a default")))) (MapCodec (RequiredKeyCodec "fruit" (Just "fruit!!") (MapCodec (EitherCodec (MapCodec (EqCodec "Apple" (StringCodec Nothing))) (MapCodec (EitherCodec (MapCodec (EqCodec "Orange" (StringCodec Nothing))) (MapCodec (EitherCodec (MapCodec (EqCodec "Banana" (StringCodec Nothing))) (MapCodec (EqCodec "Melon" (StringCodec Nothing))))))))))))
|
@ -0,0 +1 @@
|
||||
MapCodec (EitherCodec (MapCodec (EqCodec "Apple" (StringCodec Nothing))) (MapCodec (EitherCodec (MapCodec (EqCodec "Orange" (StringCodec Nothing))) (MapCodec (EitherCodec (MapCodec (EqCodec "Banana" (StringCodec Nothing))) (MapCodec (EqCodec "Melon" (StringCodec Nothing))))))))
|
1
autodocodec-api-usage/test_resources/show-codec/int.txt
Normal file
1
autodocodec-api-usage/test_resources/show-codec/int.txt
Normal file
@ -0,0 +1 @@
|
||||
CommentCodec "Int" (MapCodec (NumberCodec Nothing))
|
@ -0,0 +1 @@
|
||||
CommentCodec "Int16" (MapCodec (NumberCodec Nothing))
|
@ -0,0 +1 @@
|
||||
CommentCodec "Int32" (MapCodec (NumberCodec Nothing))
|
@ -0,0 +1 @@
|
||||
CommentCodec "Int64" (MapCodec (NumberCodec Nothing))
|
1
autodocodec-api-usage/test_resources/show-codec/int8.txt
Normal file
1
autodocodec-api-usage/test_resources/show-codec/int8.txt
Normal file
@ -0,0 +1 @@
|
||||
CommentCodec "Int8" (MapCodec (NumberCodec Nothing))
|
@ -0,0 +1 @@
|
||||
MapCodec (StringCodec Nothing)
|
@ -0,0 +1 @@
|
||||
MapCodec (ArrayOfCodec Nothing (StringCodec Nothing))
|
@ -0,0 +1 @@
|
||||
MapCodec (EitherCodec NullCodec (StringCodec Nothing))
|
@ -0,0 +1 @@
|
||||
MapCodec (EitherCodec (MapCodec (EqCodec "LT" (StringCodec Nothing))) (MapCodec (EitherCodec (MapCodec (EqCodec "EQ" (StringCodec Nothing))) (MapCodec (EqCodec "GT" (StringCodec Nothing))))))
|
@ -0,0 +1 @@
|
||||
ReferenceCodec "recursive" MapCodec (EitherCodec (CommentCodec "base case" (CommentCodec "Int" (MapCodec (NumberCodec Nothing)))) (ObjectOfCodec (Just "Recurse") (RequiredKeyCodec "recurse" (Just "recursive case") (ReferenceCodec "recursive"))))
|
@ -0,0 +1 @@
|
||||
NumberCodec Nothing
|
@ -0,0 +1 @@
|
||||
MapCodec (StringCodec Nothing)
|
1
autodocodec-api-usage/test_resources/show-codec/text.txt
Normal file
1
autodocodec-api-usage/test_resources/show-codec/text.txt
Normal file
@ -0,0 +1 @@
|
||||
StringCodec Nothing
|
@ -0,0 +1 @@
|
||||
ValueCodec
|
1
autodocodec-api-usage/test_resources/show-codec/via.txt
Normal file
1
autodocodec-api-usage/test_resources/show-codec/via.txt
Normal file
@ -0,0 +1 @@
|
||||
ObjectOfCodec Just "Via" (ApCodec (MapCodec (MapCodec (RequiredKeyCodec "one" (Just "first field") (StringCodec Nothing)))) (MapCodec (RequiredKeyCodec "two" (Just "second field") (StringCodec Nothing))))
|
1
autodocodec-api-usage/test_resources/show-codec/word.txt
Normal file
1
autodocodec-api-usage/test_resources/show-codec/word.txt
Normal file
@ -0,0 +1 @@
|
||||
CommentCodec "Word" (MapCodec (NumberCodec Nothing))
|
@ -0,0 +1 @@
|
||||
CommentCodec "Word16" (MapCodec (NumberCodec Nothing))
|
@ -0,0 +1 @@
|
||||
CommentCodec "Word32" (MapCodec (NumberCodec Nothing))
|
@ -0,0 +1 @@
|
||||
CommentCodec "Word64" (MapCodec (NumberCodec Nothing))
|
@ -0,0 +1 @@
|
||||
CommentCodec "Word8" (MapCodec (NumberCodec Nothing))
|
Loading…
Reference in New Issue
Block a user