Skip to content

Commit

Permalink
Added Test.OgmiosDatumCache testing hashing and Aeson roundtrip for P…
Browse files Browse the repository at this point in the history
…lutus Data
  • Loading branch information
bladyjoker committed Jun 6, 2022
1 parent 39b53dd commit 152b128
Show file tree
Hide file tree
Showing 6 changed files with 86 additions and 9 deletions.
1 change: 1 addition & 0 deletions fixtures/test/ogmios-datum-cache/plutus-data-samples.json

Large diffs are not rendered by default.

1 change: 1 addition & 0 deletions spago.dhall
Original file line number Diff line number Diff line change
Expand Up @@ -40,6 +40,7 @@ You can edit this file as you like.
, "node-buffer"
, "node-fs"
, "node-fs-aff"
, "node-path"
, "nonempty"
, "ordered-collections"
, "partial"
Expand Down
1 change: 1 addition & 0 deletions src/Types/PlutusData.purs
Original file line number Diff line number Diff line change
Expand Up @@ -40,6 +40,7 @@ derive instance Generic PlutusData _
instance Show PlutusData where
show x = genericShow x

-- Ogmios Datum Cache Json format
instance DecodeAeson PlutusData where
decodeAeson aeson = decodeConstr
<|> decodeMap
Expand Down
60 changes: 60 additions & 0 deletions test/OgmiosDatumCache.purs
Original file line number Diff line number Diff line change
@@ -0,0 +1,60 @@
module Test.OgmiosDatumCache
( plutusDataToFromAesonTest
, suite
) where

import Prelude

import Aeson (caseAesonArray, decodeAeson, encodeAeson)
import Contract.Address (ByteArray)
import Contract.PlutusData (Datum(..))
import Contract.Prelude (log)
import Control.Monad.Error.Class (class MonadThrow)
import Data.Either (Either(Right, Left))
import Data.Newtype (unwrap)
import Data.Traversable (for_)
import Effect.Class (class MonadEffect)
import Effect.Exception (Error)
import Hashing (datumHash)
import Mote (group, test)
import Test.Spec.Assertions (shouldEqual)
import Test.Utils (errEither, errMaybe, readAeson)
import TestM (TestPlanM)
import Types.PlutusData (PlutusData)

suite :: TestPlanM Unit
suite = group "Ogmios Datum Cache tests" $ do
test "Plutus data samples should satisfy the Aeson roundtrip test"
plutusDataToFromAesonTest
test "Plutus data samples should have a compatible hash" plutusDataHashingTest

readPlutusDataSamples
:: forall (m :: Type -> Type)
. MonadEffect m
=> m (Array { hash :: ByteArray, plutusData :: PlutusData })
readPlutusDataSamples = do
aes <- readAeson "./fixtures/test/ogmios-datum-cache/plutus-data-samples.json"
errEither <<< decodeAeson $ aes

plutusDataToFromAesonTest
(mType -> Type). MonadEffect m => MonadThrow Error m m Unit
plutusDataToFromAesonTest = do
pdsAes <- readAeson
"./fixtures/test/ogmios-datum-cache/plutus-data-samples.json"
aess <- errEither <<< caseAesonArray (Left "Expected a Json array") Right $
pdsAes
for_ aess \aes -> do
(sample :: { hash :: ByteArray, plutusData :: PlutusData }) <- errEither $
decodeAeson aes
let aes' = encodeAeson sample
aes `shouldEqual` aes'

plutusDataHashingTest
(mType -> Type). MonadEffect m => MonadThrow Error m m Unit
plutusDataHashingTest = do
plutusDataSamples <- readPlutusDataSamples
let elems = plutusDataSamples
for_ elems \{ hash, plutusData } -> do
hash' <- errMaybe "Couldn't hash the datum" <<< datumHash $ Datum plutusData
log $ show plutusData
hash `shouldEqual` unwrap hash'
2 changes: 2 additions & 0 deletions test/Unit.purs
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,7 @@ import Test.Serialization.Address as Serialization.Address
import Test.Serialization.Hash as Serialization.Hash
import Test.Transaction as Transaction
import Test.UsedTxOuts as UsedTxOuts
import Test.OgmiosDatumCache as OgmiosDatumCache
import Test.Utils as Utils
import TestM (TestPlanM)

Expand All @@ -46,3 +47,4 @@ testPlan = do
Serialization.Hash.suite
Transaction.suite
UsedTxOuts.suite
OgmiosDatumCache.suite
30 changes: 21 additions & 9 deletions test/Utils.purs
Original file line number Diff line number Diff line change
Expand Up @@ -7,17 +7,11 @@ module Test.Utils
, interpret
, toFromAesonTest
, unsafeCall
, readAeson
) where

import Prelude

import Aeson
( class DecodeAeson
, class EncodeAeson
, JsonDecodeError
, decodeAeson
, encodeAeson
)
import Data.Const (Const)
import Data.Either (Either(Left, Right))
import Data.Foldable (sequence_)
Expand All @@ -27,12 +21,24 @@ import Effect.Aff.Class (liftAff)
import Effect.Class (class MonadEffect, liftEffect)
import Effect.Exception (throwException, throw)
import Mote (Plan, foldPlan, planT, test)
import Node.Path (FilePath)
import Test.Spec (Spec, describe, it)
import Test.Spec.Assertions (shouldEqual)
import Test.Spec.Reporter (consoleReporter)
import Test.Spec.Runner (runSpec)
import TestM (TestPlanM)
import Type.Proxy (Proxy)
import Aeson
( class DecodeAeson
, class EncodeAeson
, Aeson
, JsonDecodeError
, decodeAeson
, encodeAeson
, parseJsonStringToAeson
)
import Node.Encoding (Encoding(UTF8))
import Node.FS.Sync (readTextFile)

foreign import unsafeCall :: forall a b. Proxy b -> String -> a -> b

Expand Down Expand Up @@ -73,10 +79,11 @@ assertTrue_ = assertTrue "Boolean test failed"
errEither
:: forall (m :: Type -> Type) (a :: Type) (e :: Type)
. MonadEffect m
=> Either String a
=> Show e
=> Either e a
-> m a
errEither = case _ of
Left msg -> liftEffect $ throw msg
Left msg -> liftEffect <<< throw <<< show $ msg
Right res -> pure res

errMaybe
Expand Down Expand Up @@ -112,3 +119,8 @@ aesonRoundTrip
=> a
-> Either JsonDecodeError a
aesonRoundTrip = decodeAeson <<< encodeAeson

readAeson :: forall (m :: Type -> Type). MonadEffect m => FilePath -> m Aeson
readAeson fp = do
str <- liftEffect <<< readTextFile UTF8 $ fp
errEither <<< parseJsonStringToAeson $ str

0 comments on commit 152b128

Please sign in to comment.