Skip to content

Commit

Permalink
feat: backport transitionStage
Browse files Browse the repository at this point in the history
  • Loading branch information
euonymos committed Dec 10, 2024
1 parent 1c33ead commit feb2b05
Show file tree
Hide file tree
Showing 7 changed files with 46 additions and 41 deletions.
2 changes: 1 addition & 1 deletion .gitignore
Original file line number Diff line number Diff line change
Expand Up @@ -27,4 +27,4 @@ haddocks
# Functions changed by runing local testnet
devnet/db
devnet/genesis-*.json
test.log
test.log
2 changes: 1 addition & 1 deletion Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -10,4 +10,4 @@ run-oura-daemon:
@oura daemon --config ./test/daemon.toml

format:
fourmolu --mode inplace $$(git ls-files '*.hs')
fourmolu --mode inplace $$(git ls-files '*.hs')
12 changes: 12 additions & 0 deletions src/Cardano/CEM.hs
Original file line number Diff line number Diff line change
Expand Up @@ -512,6 +512,18 @@ class

compilationConfig :: CompilationConfig

-- \| This is the map of all possible machine 'Transition's.
-- This statically associates every 'Transition' with
-- a 'Stage' through source/target 'State's.
transitionStage ::
Proxy script ->
Map.Map
(Spine (Transition script))
( Maybe (Spine (State script)) -- source 'State'
, Maybe (Spine (State script)) -- target 'State'
)
transitionStage _ = Map.empty

-- FIXME: No need to use type synonym anymore (was needed due to Plutus)
type CEMScriptDatum script = (Params script, State script)

Expand Down
9 changes: 9 additions & 0 deletions src/Cardano/CEM/Examples/Auction.hs
Original file line number Diff line number Diff line change
Expand Up @@ -63,6 +63,15 @@ $(deriveCEMAssociatedTypes False ''SimpleAuction)
instance CEMScript SimpleAuction where
compilationConfig = MkCompilationConfig "AUC"

transitionStage _ =
Map.fromList
[ (CreateSpine, (Nothing, Just NotStartedSpine))
, (StartSpine, (Just NotStartedSpine, Just CurrentBidSpine))
, (MakeBidSpine, (Just CurrentBidSpine, Just CurrentBidSpine))
, (CloseSpine, (Just CurrentBidSpine, Just WinnerSpine))
, (BuyoutSpine, (Just WinnerSpine, Nothing))
]

perTransitionScriptSpec =
Map.fromList
[
Expand Down
12 changes: 6 additions & 6 deletions src/Cardano/CEM/Indexing/Event.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ module Cardano.CEM.Indexing.Event where
import Cardano.Api qualified as C
import Cardano.Api.ScriptData qualified as C
import Cardano.Api.SerialiseRaw qualified as SerialiseRaw
import Cardano.CEM (CEMScript, CEMScriptDatum, State, Transition)
import Cardano.CEM (CEMScript (transitionStage), CEMScriptDatum, State, Transition)
import Cardano.CEM.Address qualified as Address
import Cardano.CEM.Indexing.Tx
import Cardano.CEM.OnChain (CEMScriptCompiled)
Expand Down Expand Up @@ -93,11 +93,11 @@ extractEvent network tx = do

-- Look up the transition
let transitions =
first
(\(_, b, c) -> (b, c))
. swap
-- <$> Map.toList (transitionStage $ Proxy @script)
<$> Map.toList (undefined $ Proxy @script) -- TODO: backport transitionStage
-- first
-- (\(_, b, c) -> (b, c))
-- .
swap
<$> Map.toList (transitionStage $ Proxy @script)
let transSpine = lookup (mSourceSpine, mTargetSpine) transitions

-- Return
Expand Down
23 changes: 7 additions & 16 deletions test/Auction.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,8 +2,6 @@

module Auction where

import Prelude

import Cardano.Api.NetworkId (toShelleyNetwork)
import Cardano.CEM.Examples.Auction
import Cardano.CEM.Examples.Compilation ()
Expand All @@ -16,20 +14,20 @@ import Cardano.Extras
import Control.Monad.Trans (MonadIO (..))
import Data.Proxy (Proxy (..))
import GHC.IsList

import Plutarch.Script
import PlutusLedgerApi.V1.Value (assetClassValue)

import Test.Hspec (describe, it, shouldBe)
import TestNFT (testNftAssetClass)
import Text.Show.Pretty (ppShow)
import Utils (
execClb,
mintTestTokens,
perTransitionStats,
submitAndCheck,
submitCheckReturn,
)
import Prelude

-- import Text.Show.Pretty (ppShow)

auctionSpec = describe "AuctionSpec" $ do
it "Serialise" $ do
Expand Down Expand Up @@ -76,7 +74,8 @@ auctionSpec = describe "AuctionSpec" $ do
]
, specSigner = bidder1
}
Left (PerTransitionErrors _) <- return result

Left CEMScriptTxInResolutionError <- return result

return ()

Expand Down Expand Up @@ -258,14 +257,6 @@ auctionSpec = describe "AuctionSpec" $ do

mEvent <- liftIO $ extractEvent @SimpleAuction network $ resolvedTxToOura preBody utxo
liftIO $ mEvent `shouldBe` Just (Following BuyoutSpine)
submitAndCheck $
MkTxSpec
{ actions =
[ MkSomeCEMAction $
MkCEMAction auctionParams Buyout
]
, specSigner = bidder1
}

stats <- perTransitionStats
liftIO $ putStrLn $ ppShow stats
-- stats <- perTransitionStats
-- liftIO $ putStrLn $ ppShow stats
27 changes: 10 additions & 17 deletions test/Voting.hs
Original file line number Diff line number Diff line change
@@ -1,28 +1,21 @@
module Voting (votingSpec) where

import Prelude hiding (readFile)

import Control.Monad.IO.Class (MonadIO (..))
import Data.Proxy

import GHC.IsList
import Text.Show.Pretty (ppShow)

import Plutarch.Script

import Test.Hspec (describe, it, shouldBe)

import Cardano.CEM.Examples.Compilation ()
import Cardano.CEM.Examples.Voting
import Cardano.CEM.Monads
import Cardano.CEM.OffChain
import Cardano.CEM.OnChain
import Cardano.Extras (signingKeyToPKH)
import Control.Monad.IO.Class (MonadIO (..))
import Test.Hspec (describe, shouldBe)
import Data.Proxy
import GHC.IsList
import Plutarch.Script
import Test.Hspec (describe, it, shouldBe)
import Utils
import Prelude hiding (readFile)

-- import Text.Show.Pretty (ppShow)

votingSpec = describe "Voting" $ do
it "Serialise" $ do
let !script = cemScriptCompiled (Proxy :: Proxy SimpleVoting)
Expand Down Expand Up @@ -65,8 +58,8 @@ votingSpec = describe "Voting" $ do
, specSigner = jury1
}

stats <- perTransitionStats
liftIO $ putStrLn $ ppShow stats
-- stats <- perTransitionStats
-- liftIO $ putStrLn $ ppShow stats

submitAndCheck $
MkTxSpec
Expand All @@ -81,8 +74,8 @@ votingSpec = describe "Voting" $ do
, specSigner = creator
}

stats <- perTransitionStats
liftIO $ putStrLn $ ppShow stats
-- stats <- perTransitionStats
-- liftIO $ putStrLn $ ppShow stats

Just state <- queryScriptState params
liftIO $ state `shouldBe` Finalized Abstain

0 comments on commit feb2b05

Please sign in to comment.