Skip to content

Commit

Permalink
optimize test performance
Browse files Browse the repository at this point in the history
  • Loading branch information
bjornkihlberg committed Mar 27, 2023
1 parent b7acb2b commit d1ea5d5
Show file tree
Hide file tree
Showing 2 changed files with 25 additions and 110 deletions.
132 changes: 23 additions & 109 deletions marlowe-runtime/test/Language/Marlowe/Runtime/Transaction/ApiSpec.hs
Expand Up @@ -27,7 +27,7 @@ import qualified Data.Vector as Vector
import Language.Marlowe.Runtime.ChainSync.Api (PolicyId(PolicyId), TokenName(TokenName))
import qualified Network.URI as Network (URI(..), URIAuth(..))
import qualified Network.URI hiding (URI(..), URIAuth(..))
import Test.Hspec (Spec, it, shouldBe, shouldSatisfy)
import Test.Hspec (Spec, shouldBe, shouldSatisfy)
import qualified Test.Hspec as Hspec
import Test.Hspec.QuickCheck (prop)
import Test.QuickCheck (Gen)
Expand Down Expand Up @@ -58,12 +58,12 @@ cip25MetadataCompletenessTests :: Gen.Property
cip25MetadataCompletenessTests = Gen.checkCoverage $
Gen.forAll cip25MetadataJSONRelationGen \(md@(CIP25Metadata policies), json) ->
Gen.cover 1.0 (Maybe.isJust $ find null policies) "some policy with no token" $
Gen.cover 60.0 (Maybe.isJust $ find (not . null) policies) "some policy with some token" $
Gen.cover 60.0 (not $ null policies) "some policies" $
Gen.cover 40.0 (Maybe.isJust $ find (not . null) policies) "some policy with some token" $
Gen.cover 40.0 (not $ null policies) "some policies" $
Gen.cover 1.0 (null policies) "no policies" do
let document = Aeson.encode json
Aeson.encode md `shouldBe` document
-- fmap show (Aeson.decode @CIP25Metadata document) `shouldBe` Just (show md)
fmap show (Aeson.decode @CIP25Metadata document) `shouldBe` Just (show md)
where
cip25MetadataJSONRelationGen :: Gen (CIP25Metadata, Aeson.Value)
cip25MetadataJSONRelationGen = do
Expand All @@ -75,7 +75,7 @@ cip25MetadataCompletenessTests = Gen.checkCoverage $
(tokenMetadata, tokenMetadataJSON) <- tokenMetadataJSONRelationGen
pure ((policyId, tokenMetadata), (policyIdJSON, tokenMetadataJSON))
(Map.fromList -> metadata, Aeson.Object . Aeson.KeyMap.fromList -> json) <-
unzip <$> Gen.frequency [(1, emptyGen), (9, nonemptyGen)]
unzip <$> Gen.frequency [(1, emptyGen), (4, nonemptyGen)]
pure (CIP25Metadata metadata, Aeson.Object [("721", json)])

tokenMetadataJSONRelationGen :: Gen (Map TokenName CIP25MetadataDetails, Aeson.Value)
Expand All @@ -88,7 +88,7 @@ cip25MetadataCompletenessTests = Gen.checkCoverage $
(metadataDetails, metadataDetailsJSON) <- cip25MetadataDetailsJSONRelationGen
pure ((tokenName, metadataDetails), (tokenNameJSON, metadataDetailsJSON))
(Map.fromList *** Aeson.Object . Aeson.KeyMap.fromList) .
unzip <$> Gen.frequency [(1, emptyGen),(9, nonEmptyGen)]
unzip <$> Gen.frequency [(1, emptyGen),(4, nonEmptyGen)]

policyIdJSONKeyRelationGen :: Gen (PolicyId, Aeson.Key)
policyIdJSONKeyRelationGen =
Expand Down Expand Up @@ -147,17 +147,21 @@ cip25MetadataFileDetailsCompletenessTests = Gen.checkCoverage $

cip25MetadataFileDetailsJSONRelationGen :: Gen ([CIP25MetadataFileDetails], Aeson.Value)
cip25MetadataFileDetailsJSONRelationGen = do
(x, y) <- unzip <$> Gen.listOf do
name <- fromString <$> Gen.arbitrary
mediaType <- fromString <$> Gen.arbitrary
(src, srcJSON) <- uriJSONRelationGen
let json = Aeson.Object
[ ("name", Aeson.String name)
, ("mediaType", Aeson.String mediaType)
, ("src", srcJSON)
]
pure (CIP25MetadataFileDetails {..}, json)
pure (x, Aeson.Array $ Vector.fromList y)
let emptyGen = pure []
nonEmptyGen = do
n <- Gen.chooseInt (1, 10)
Gen.vectorOf n do
name <- Gen.oneof [pure "" ,fromString <$> Gen.listOf1 Gen.arbitrary]
mediaType <- Gen.oneof [pure "" ,fromString <$> Gen.listOf1 Gen.arbitrary]
(src, srcJSON) <- uriJSONRelationGen
let json = Aeson.Object
[ ("name", Aeson.String name)
, ("mediaType", Aeson.String mediaType)
, ("src", srcJSON)
]
pure (CIP25MetadataFileDetails {..}, json)
(cip25MetadataFileDetails, json) <- unzip <$> Gen.frequency [(1, emptyGen), (9, nonEmptyGen)]
pure (cip25MetadataFileDetails, Aeson.Array $ Vector.fromList json)

uriJSONRelationGen :: Gen (Network.URI, Aeson.Value)
uriJSONRelationGen = (id &&& Aeson.String . fromString . show) <$> uriGen
Expand Down Expand Up @@ -217,7 +221,7 @@ uriGen = do
charNumberGen = Gen.elements ['0' .. '9']

spec :: Spec
spec = do
spec = Hspec.focus do
Hspec.describe "uriGen" do
prop "completeness" uriGenCompletenessTests
prop "soundness" Hspec.pending
Expand All @@ -227,96 +231,6 @@ spec = do
Hspec.describe "CIP25MetadataDetails" do
prop "completeness" cip25MetadataDetailsCompletenessTests
prop "soundness" Hspec.pending
Hspec.fdescribe "CIP-25 Metadata" do
Hspec.describe "CIP-25 Metadata" do
prop "completeness" cip25MetadataCompletenessTests
prop "soundness" Hspec.pending
-- Hspec.describe "version 1" do
-- prop "deserialization is not supported" do
-- version1 <- Gen.elements [Nothing, Just (1 :: Int)]
-- n <- Gen.chooseInt (0, 64)
-- (mkKey -> key) <- base16EncodedTextGen n
-- let input :: BL.ByteString
-- input = Aeson.encode $
-- Aeson.Object [("721", Aeson.Object
-- if Maybe.isJust version1
-- then [(key, Aeson.Object []), ("version", Aeson.Number 1)]
-- else [(key, Aeson.Object [])])]
-- actual :: Either String CIP25Metadata
-- actual = Aeson.eitherDecode' input
-- expected :: Either String CIP25Metadata
-- expected = Left "Error in $['721']: CIP-25 version 1 is not supported!"
-- pure $ actual `shouldBe` expected
-- prop "serialization is not supported" do
-- version1 <- Gen.elements [Nothing, Just (1 :: Int)]
-- n <- Gen.chooseInt (0, 64)
-- (mkPolicyId -> policyId) <- base16EncodedTextGen n
-- let input :: CIP25Metadata
-- input = CIP25Metadata $ CIP25MetadataLabel [(policyId, [])] version1
-- actual :: IO ()
-- actual = let !_ = Aeson.encode input in pure ()
-- pure $ actual `shouldThrow` Hspec.anyErrorCall
Hspec.describe "version 2" do
prop "Parses PolicyId as raw byte string" Hspec.pending -- do
-- ((* 2) -> n) <- Gen.chooseInt (0, 32)
-- (key, policyId) <- (mkKey &&& mkPolicyId) <$> base16EncodedTextGen n
-- let input :: BL.ByteString
-- input = Aeson.encode $
-- Aeson.Object [("721", Aeson.Object
-- [ (key, Aeson.Object [])
-- , ("version", Aeson.Number 2)
-- ])]
-- actual :: Either String CIP25Metadata
-- actual = Aeson.eitherDecode' input
-- expected :: Either String CIP25Metadata
-- expected = Right $ CIP25Metadata $ CIP25MetadataLabel [(policyId, [])] (Just 2)
-- pure $ actual `shouldBe` expected
prop "Serializes PolicyId as raw byte string" Hspec.pending -- do
-- ((* 2) -> n) <- Gen.chooseInt (0, 32)
-- (key, policyId) <- (mkKey &&& mkPolicyId) <$> base16EncodedTextGen n
-- let input :: CIP25Metadata
-- input = CIP25Metadata $ CIP25MetadataLabel [(policyId, [])] (Just 2)
-- actual :: BL.ByteString
-- actual = Aeson.encode input
-- expected :: BL.ByteString
-- expected = Aeson.encode $
-- Aeson.Object [("721", Aeson.Object
-- [ (key, Aeson.Object [])
-- , ("version", Aeson.Number 2)
-- ])]
-- pure $ actual `shouldBe` expected
prop "Parses TokenName as raw byte string" Hspec.pending -- do
-- ((* 2) -> n) <- Gen.chooseInt (0, 32)
-- (policyIdKey, policyId) <- (mkKey &&& mkPolicyId) <$> base16EncodedTextGen n
-- (tokenDetails, tokenDetailsJSON) <- tokenDetailsJSONRelationGen
-- let actual :: Either String CIP25Metadata
-- actual = Aeson.eitherDecode' $ Aeson.encode $
-- Aeson.Object [("721", Aeson.Object
-- [ (policyIdKey, tokenDetailsJSON)
-- , ("version", Aeson.Number 2)
-- ])]
-- expected :: Either String CIP25Metadata
-- expected = Right $ CIP25Metadata $ CIP25MetadataLabel
-- [(policyId, tokenDetails)] (Just 2)
-- pure $ actual `shouldBe` expected
it "Serializes TokenName as raw byte string" Hspec.pending
it "Rejects PolicyId longer than 64 bytes" Hspec.pending
it "Rejects TokenName longer than 64 bytes" Hspec.pending
Hspec.describe "version 1 & 2 common" do
it "rejects invalid image identifiers" Hspec.pending
it "Ignores <other_properties>" Hspec.pending
it "Reorganizes strings into maximum 64 length strings" Hspec.pending
it "Rejects invalid version values" Hspec.pending
it "Rejects when missing meta_details properties" Hspec.pending
it "Rejects when missing files_details properties" Hspec.pending
it "Serializes 0 files_details.src into [] representation" Hspec.pending
it "Serializes 1 files_details.src into 1 representation" Hspec.pending
it "Serializes * files_details.src into [*] representation" Hspec.pending
it "Serializes 0 metadata_details.image into [] representation" Hspec.pending
it "Serializes 1 metadata_details.image into 1 representation" Hspec.pending
it "Serializes * metadata_details.image into [*] representation" Hspec.pending
it "Serializes 0 metadata_details.description into no representation" Hspec.pending
it "Serializes 1 metadata_details.description into 1 compact representation" Hspec.pending
it "Serializes * metadata_details.description into * compact representation" Hspec.pending
it "Serializes 0 metadata_details.files into compact no representation" Hspec.pending
it "Serializes 1 metadata_details.files into compact 1 representation" Hspec.pending
it "Serializes * metadata_details.files into compact * representation" Hspec.pending
Expand Up @@ -156,7 +156,8 @@ instance Aeson.ToJSON CIP25Metadata where
toJSON (CIP25Metadata x) = Aeson.Object [("721", toJSON x)]

instance Aeson.FromJSON CIP25Metadata where
parseJSON = undefined
parseJSON = Aeson.withObject "CIP25Metadata" \x ->
CIP25Metadata <$> x .: "721"

-- CIP-25 metadata
newtype NFTMetadata = NFTMetadata { unNFTMetadata :: Metadata }
Expand Down

0 comments on commit d1ea5d5

Please sign in to comment.