Skip to content

Commit

Permalink
Merge
Browse files Browse the repository at this point in the history
  • Loading branch information
MaryanaMysak committed Oct 7, 2021
2 parents ac95451 + 66753df commit 820b2f1
Show file tree
Hide file tree
Showing 20 changed files with 270 additions and 345 deletions.
5 changes: 4 additions & 1 deletion eleks/nft/pab/Main.hs
Expand Up @@ -98,9 +98,12 @@ instance HasDefinitions NFTMarketContracts where
NFTStartContract -> Builtin.endpointsToSchemas @NFTMarket.MarketOwnerSchema
NFTUserContract _ -> Builtin.endpointsToSchemas @NFTMarket.MarketUserSchema
getContract = \case
NFTStartContract -> SomeBuiltin (NFTMarket.ownerEndpoint NFTMarket.forgeMarketToken)
NFTStartContract -> SomeBuiltin (NFTMarket.ownerEndpoint NFTMarket.forgeMarketToken nftMarketFee)
NFTUserContract market -> SomeBuiltin (NFTMarket.userEndpoints market)

nftMarketFee :: Integer
nftMarketFee = 500000

handlers :: SimulatorEffectHandlers (Builtin NFTMarketContracts)
handlers =
Simulator.mkSimulatorHandlers def def
Expand Down
23 changes: 16 additions & 7 deletions eleks/nft/src/Contracts/NFT/OffChain.hs
Expand Up @@ -16,6 +16,7 @@
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE NumericUnderscores #-}

-- | Implements a custom currency with a monetary policy that allows
-- the forging of a fixed amount of units.
Expand Down Expand Up @@ -143,14 +144,15 @@ forgeMarketToken tokenName pk = fmap Currency.currencySymbol $
-- | Creates a Marketplace "factory". This factory will keep track of the existing nft tokens
start ::
forall w w' s. (TokenName -> PubKeyHash -> Contract w s Text CurrencySymbol)
-> Integer
-> Contract w s Text NFTMarket
start forgeNft = do
start forgeNft fee = do
pkh <- pubKeyHash <$> ownPubKey
cs <- forgeNft marketplaceTokenName pkh
let c = assetClass cs marketplaceTokenName
nftTokenCur = mkNFTCurrency c
nftTokenMetaCur = mkNFTCurrency c
market = marketplace cs nftTokenCur nftTokenMetaCur
market = marketplace cs nftTokenCur nftTokenMetaCur fee pkh
inst = marketInstance market
tx = mustPayToTheScript (Factory []) $ assetClassValue c 1
ledgerTx <- submitTxConstraints inst tx
Expand Down Expand Up @@ -292,14 +294,17 @@ buy market BuyParams{..} = do
when (PlutusTx.Prelude.isNothing $ nftSeller nftMetadata) $
throwError $ pack $ printf "NFT token is not on sale"
let marketInst = marketInstance market
mOwner = marketOwner market
mFee = marketFee market
mFeeValue = Ada.lovelaceValueOf mFee
nftMetadata' = nftMetadata { nftSeller = Nothing, nftSellPrice = 0 }
nftSeller' = fromMaybe "" $ nftSeller nftMetadata
nftMetadataDatum = NFTMeta nftMetadata'
let mrScript = marketScript market
redeemer = Redeemer $ PlutusTx.toBuiltinData $ Buy pkh
nftValue = getNftValue (nftTokenSymbol nftMetadata) (nftTokenName nftMetadata)
nftMetadataValue = getNftValue (nftMetaTokenSymbol nftMetadata) (nftMetaTokenName nftMetadata)
nftSellPriceValue = Ada.lovelaceValueOf $ nftSellPrice nftMetadata
nftSellPriceValue = Ada.lovelaceValueOf $ (nftSellPrice nftMetadata - mFee)

lookups = Constraints.typedValidatorLookups marketInst
<> Constraints.otherScript mrScript
Expand All @@ -309,6 +314,7 @@ buy market BuyParams{..} = do
<> Constraints.mustSpendScriptOutput oref redeemer
<> Constraints.mustPayToPubKey pkh nftValue
<> Constraints.mustPayToPubKey nftSeller' nftSellPriceValue
<> Constraints.mustPayToPubKey mOwner mFeeValue
ledgerTx <- submitTxConstraintsWith lookups tx
void $ awaitTxConfirmed $ txId ledgerTx
let nftMetaDto = nftMetadataToDto nftMetadata'
Expand All @@ -331,13 +337,15 @@ transfer market TransferParams{..} = do
logInfo $ "transfer NFT: " ++ show nftMetaDto
return nftMetaDto

marketplace :: CurrencySymbol -> NFTCurrency -> NFTCurrency -> NFTMarket
marketplace cs tokenCur metaTokenCur =
marketplace :: CurrencySymbol -> NFTCurrency -> NFTCurrency -> Integer -> PubKeyHash -> NFTMarket
marketplace cs tokenCur metaTokenCur fee pkh =
NFTMarket{
marketId = assetClass cs marketplaceTokenName
, marketTokenSymbol = nftCurrencySymbol tokenCur
, marketTokenMetaSymbol = nftCurrencySymbol metaTokenCur
, marketTokenMetaNameSuffix = toBuiltin . B.pack $ metadataTokenNamePrefix
, marketFee = fee
, marketOwner = pkh
}

getNFTMarketDatum :: TxOutTx -> Contract w s Text NFTMarketDatum
Expand Down Expand Up @@ -469,9 +477,10 @@ ownerEndpoint ::
-> PubKeyHash
-> Contract (Last (Either Text NFTMarket)) MarketOwnerSchema Text CurrencySymbol
)
-> Integer
-> Contract (Last (Either Text NFTMarket)) MarketOwnerSchema ContractError ()
ownerEndpoint forgeNft = do
e <- mapError absurd $ runError $ start forgeNft
ownerEndpoint forgeNft fee = do
e <- mapError absurd $ runError $ start forgeNft fee
void $ waitNSlots 1
tell $ Last $ Just e

Expand Down
12 changes: 7 additions & 5 deletions eleks/nft/src/Contracts/NFT/OnChain.hs
Expand Up @@ -182,11 +182,13 @@ validateBuy ::
-> ScriptContext
-> Bool
validateBuy NFTMarket{..} nftMeta@NFTMetadata{nftMetaTokenSymbol, nftMetaTokenName, nftTokenSymbol, nftTokenName} buyer ctx =
traceIfFalse "nft metadata token missing from input" $ isNftToken inVal nftMetaTokenSymbol nftMetaTokenName &&
traceIfFalse "ouptut nftMetadata should be same" (nftMeta == outDatum) &&
traceIfFalse "expected seller to get money" (addressGetValue (nftSeller nftMeta) $ Ada.lovelaceValueOf (nftSellPrice nftMeta)) &&
traceIfFalse "expected buyer to get NFT token" (addressGetValue (Just buyer) $ getNftValue nftTokenSymbol nftTokenName) &&
traceIfFalse "price should be grater 0" (nftSellPrice outDatum == 0) &&
traceIfFalse "nft metadata token missing from input" $ isNftToken inVal nftMetaTokenSymbol nftMetaTokenName &&
traceIfFalse "ouptut nftMetadata should be same" (nftMeta == outDatum) &&
traceIfFalse "expected seller to get money" (addressGetValue (nftSeller nftMeta) $ Ada.lovelaceValueOf (nftSellPrice nftMeta - marketFee)) &&
traceIfFalse "expected buyer to get NFT token" (addressGetValue (Just buyer) $ getNftValue nftTokenSymbol nftTokenName) &&
traceIfFalse "expected market owner to get fee" (addressGetValue (Just marketOwner) $ Ada.lovelaceValueOf marketFee) &&
traceIfFalse "price should be grater 0" (nftSellPrice outDatum == 0) &&
traceIfFalse "fee should be grater 0" (marketFee > 0) &&
traceIfFalse "seller should be emptied" (PlutusTx.Prelude.isNothing $ nftSeller outDatum)
where
info :: TxInfo
Expand Down
2 changes: 2 additions & 0 deletions eleks/nft/src/Contracts/NFT/Types.hs
Expand Up @@ -36,6 +36,8 @@ data NFTMarket = NFTMarket
, marketTokenSymbol :: CurrencySymbol
, marketTokenMetaSymbol :: CurrencySymbol
, marketTokenMetaNameSuffix:: BuiltinByteString
, marketFee :: Integer
, marketOwner :: PubKeyHash
} deriving (Show, Generic, ToJSON, FromJSON, ToSchema, Prelude.Eq, Prelude.Ord)

PlutusTx.makeLift ''NFTMarket
Expand Down
13 changes: 11 additions & 2 deletions eleks/nft/src/test/Spec/Helper.hs
@@ -1,4 +1,5 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NumericUnderscores #-}

module Spec.Helper
where
Expand All @@ -15,7 +16,10 @@ import Ledger (PubKeyHash, pubKeyHash)
import Ledger.Value (CurrencySymbol(..), TokenName (..), AssetClass(..), toString)
import qualified Plutus.Trace.Emulator as Trace
import PlutusTx.Prelude (toBuiltin)
import Wallet.Emulator (Wallet, walletPubKey)
import Wallet.Emulator (Wallet(..), walletPubKey)

ownerWallet' :: Wallet
ownerWallet' = Wallet 5

mockMarketId :: AssetClass
mockMarketId = createMarketTokenMock NFTMarket.marketplaceTokenName
Expand All @@ -29,6 +33,8 @@ nftMarketMock = NFTMarket
, marketTokenSymbol = nftCurrencySymbol mockNftCurrency
, marketTokenMetaSymbol = nftCurrencySymbol mockNftCurrency
, marketTokenMetaNameSuffix = toBuiltin . B.pack $ metadataTokenNamePrefix
, marketFee = 500000
, marketOwner = pubKeyHash $ walletPubKey ownerWallet'
}

data TestTokenMeta = TestTokenMeta
Expand Down Expand Up @@ -83,7 +89,10 @@ createMarketTokenMock:: TokenName -> AssetClass
createMarketTokenMock tokenName = AssetClass (getMarketTokenSymbol tokenName, tokenName)

nftMaketSellPrice:: Integer
nftMaketSellPrice = 1000
nftMaketSellPrice = 2000000

nftMarketFee :: Integer
nftMarketFee = marketFee nftMarketMock

toMetaDto:: TestTokenMeta -> NFTMetadataDto
toMetaDto = nftMetadataToDto . createNftMeta
Expand Down
8 changes: 5 additions & 3 deletions eleks/nft/src/test/Spec/NFT.hs
Expand Up @@ -50,7 +50,8 @@ t1 = Trace.walletInstanceTag w1
t2 = Trace.walletInstanceTag w2

ownerContract :: Contract (Last (Either Text NFTMarket)) MarketOwnerSchema ContractError ()
ownerContract = NFTMarket.ownerEndpoint forgeMockNftToken
ownerContract = NFTMarket.ownerEndpoint forgeMockNftToken $ marketFee nftMarketMock

userContract :: Promise (Last (Either Text MarketContractState)) MarketUserSchema Void ()
userContract = NFTMarket.userEndpoints nftMarketMock

Expand Down Expand Up @@ -161,8 +162,9 @@ tests = testGroup "nft"
.&&. valueAtAddress (marketAddress nftMarketMock)
(== (assetClassValue (testTokenMetaClass testToken1) 1
<> assetClassValue (marketId nftMarketMock) 1))
.&&. walletFundsChange w1 (Ada.lovelaceValueOf nftMaketSellPrice)
  .&&. walletFundsChange w2 (Ada.lovelaceValueOf (negate nftMaketSellPrice) <> assetClassValue (testTokenClass testToken1) 1)
.&&. walletFundsChange w1 (Ada.lovelaceValueOf (nftMaketSellPrice - nftMarketFee))
  .&&. walletFundsChange w2 (Ada.lovelaceValueOf (negate (nftMaketSellPrice)) <> assetClassValue (testTokenClass testToken1) 1)
.&&. walletFundsChange ownerWallet (Ada.lovelaceValueOf nftMarketFee)
.&&. assertAccumState userContract t2
(\case Last (Just (Right (NFTMarket.Buyed meta))) -> meta == testToken1MetaDto; _ -> False)
"should create buy NFT state"
Expand Down
27 changes: 19 additions & 8 deletions eleks/oracle/README.md
Expand Up @@ -70,6 +70,13 @@ NS - "Not Started",
LIVE - "In Progress",
FT - "Match Finished"
CANC - "Match Cancelled"

switch to live
curl -v -X PUT -H "Content-Type: application/json" \
-d '{"ugpSatus": "LIVE", "ugpWinnerTeamId": 0}' \
http://localhost:8081/games/1

finish with winner
curl -v -X PUT -H "Content-Type: application/json" \
-d '{"ugpSatus": "FT", "ugpWinnerTeamId": 55}' \
http://localhost:8081/games/1
Expand All @@ -85,9 +92,9 @@ cabal build mutualbetserver
cabal exec -- mutualbetserver
```

### game server API
### mutual bet server API

1. Wallet info
1. Wallet info (WalletId, PubKey)
curl -s http://localhost:8082/wallet/1

## The Plutus Application Backend (PAB) example
Expand Down Expand Up @@ -115,20 +122,24 @@ cabal exec -- bet-pab
export INSTANCE_ID=...
curl -s http://localhost:9080/api/new/contract/instance/$INSTANCE_ID/status | jq

2. Running mutual bat contract info and instance id
curl -s http://localhost:9080/api/contract/instances/wallet/1 | jq '.[] | select(.cicDefinition.tag=="MutualBetBettorContract") | .cicDefinition, .cicContract.unContractInstanceId'
2. Get all contract ids and wallet ids
curl -s http://localhost:9080/api/contract/instances/ | jq '.[] | select(.cicDefinition.tag=="MutualBetBettorContract") | .cicDefinition, .cicContract, .cicWallet'

3. Running mutual bat contract info and instance id
export WALLET_ID=76d5e1291d51f16eb442267faccd0ab51a3b0c4a21eb6b8f72d5f0a4ca467189ac5f70a018c6df3f632b48fd8ead1b68f39a44de06f5a5de42a6a131af0f085d44becd56fa30041efea5ff2637205181837dffd03545d3db1c11e6dcbbd3415ce8f85aad41776b99eb62a797b8c5abbe82061e1634efc4c7d5ac6fff3ca94d7f
curl -s http://localhost:9080/api/contract/instances/wallet/$WALLET_ID | jq '.[] | select(.cicDefinition.tag=="MutualBetBettorContract") | .cicDefinition, .cicContract'

curl -s http://localhost:9080/api/contract/instances/wallet/1 | jq '.[] | .cicDefinition, .cicContract.unContractInstanceId'
### Pab transactions
1. Make a bet
export INSTANCE_ID=...
export INSTANCE_ID=c2affd9b-3269-414e-9919-891150611639
curl -H "Content-Type: application/json" \
--request POST \
--data '{"nbpAmount":1500000, "nbpWinnerId": 55}' \
--data '{"nbpAmount":3000000, "nbpWinnerId": 55}' \
http://localhost:9080/api/contract/instance/$INSTANCE_ID/endpoint/bet

2. Get contract state
curl -H "Content-Type: application/json" \
--request GET \
http://localhost:9080/api/contract/instance/$INSTANCE_ID/status | jq '.cicCurrentState.observableState'
http://localhost:9080/api/contract/instance/$INSTANCE_ID/status | jq '.cicCurrentState.observableState'

76d5e1291d51f16eb442267faccd0ab51a3b0c4a21eb6b8f72d5f0a4ca467189ac5f70a018c6df3f632b48fd8ead1b68f39a44de06f5a5de42a6a131af0f085d44becd56fa30041efea5ff2637205181837dffd03545d3db1c11e6dcbbd3415ce8f85aad41776b99eb62a797b8c5abbe82061e1634efc4c7d5ac6fff3ca94d7f
64 changes: 45 additions & 19 deletions eleks/oracle/cabal.project
Expand Up @@ -28,7 +28,8 @@ source-repository-package
prettyprinter-configurable
quickcheck-dynamic
word-array
tag: 8c83c4abe211b4bbcaca3cdf1b2c0e38d0eb683f
tag: 1426912c3f8c29e7ca8754dafae81eaf281e1ee6
--tag: 8c83c4abe211b4bbcaca3cdf1b2c0e38d0eb683f

-- We never, ever, want this.
write-ghc-environment-files: never
Expand Down Expand Up @@ -74,28 +75,23 @@ package ouroboros-consensus-cardano
package cardano-api
optimization: False

-- Turn off the tests for a while
package plutus-metatheory
tests: False

-- https://github.com/Quid2/flat/pull/22 fixes a potential exception
-- when decoding invalid (e.g. malicious) text literals.
source-repository-package
type: git
-- location: https://github.com/Quid2/flat.git
location: https://github.com/michaelpj/flat.git
location: https://github.com/Quid2/flat.git
tag: ee59880f47ab835dbd73bea0847dab7869fc20d8

-- Needs some patches, but upstream seems to be fairly dead (no activity in > 1 year)
source-repository-package
type: git
location: https://github.com/shmish111/purescript-bridge.git
location: https://github.com/input-output-hk/purescript-bridge.git
tag: 6a92d7853ea514be8b70bab5e72077bf5a510596

source-repository-package
type: git
location: https://github.com/shmish111/servant-purescript.git
tag: a76104490499aa72d40c2790d10e9383e0dbde63
location: https://github.com/input-output-hk/servant-purescript.git
tag: a0c7c7e37c95564061247461aef4be505a853538

source-repository-package
type: git
Expand All @@ -105,17 +101,17 @@ source-repository-package
source-repository-package
type: git
location: https://github.com/input-output-hk/cardano-base
tag: cb0f19c85e5bb5299839ad4ed66af6fa61322cc4
tag: 592aa61d657ad5935a33bace1243abce3728b643
subdir:
base-deriving-via
binary
binary/test
measures
orphans-deriving-via
slotting
cardano-crypto-class
cardano-crypto-praos
cardano-crypto-tests
measures
orphans-deriving-via
slotting
strict-containers

source-repository-package
Expand All @@ -126,10 +122,28 @@ source-repository-package
cardano-prelude
cardano-prelude-test

source-repository-package
type: git
location: https://github.com/input-output-hk/cardano-addresses
tag: d2f86caa085402a953920c6714a0de6a50b655ec
subdir:
core

source-repository-package
type: git
location: https://github.com/input-output-hk/cardano-wallet
tag: ae7569293e94241ef6829139ec02bd91abd069df
subdir:
lib/text-class
lib/strict-non-empty-containers
lib/core
lib/test-utils
lib/numeric

source-repository-package
type: git
location: https://github.com/input-output-hk/ouroboros-network
tag: f149c1c1e4e4bb5bab51fa055e9e3a7084ddc30e
tag: 5d37a927046bc7da2887830d8e35cf604622ce09
subdir:
monoidal-synchronisation
typed-protocols
Expand All @@ -144,11 +158,22 @@ source-repository-package
io-sim
io-classes
network-mux
ntp-client

source-repository-package
type: git
location: https://github.com/input-output-hk/iohk-monitoring-framework
tag: 808724ff8a19a33d0ed06f9ef59fbd900b08553c
-- Important Note: Read below, before changing this!
tag: 46f994e216a1f8b36fe4669b47b2a7011b0e153c
-- Are you thinking of updating this tag to some other commit? Please
-- ensure that the commit you are about to use is the latest one from
-- the *develop* branch of this repo:
-- * <https://github.com/input-output-hk/iohk-monitoring-framework/commits/develop>
-- (not master!)
--
-- In particular we rely on the code from this PR:
-- * <https://github.com/input-output-hk/iohk-monitoring-framework/pull/622>
-- being merged.
subdir:
iohk-monitoring
tracer-transformers
Expand All @@ -161,8 +186,8 @@ source-repository-package

source-repository-package
type: git
location: https://github.com/input-output-hk/cardano-ledger-specs
tag: 12a0ef69d64a55e737fbf4e846bd8ed9fb30a956
location: https://github.com/raduom/cardano-ledger-specs
tag: ef6bb99782d61316da55470620c7da994cc352b2
subdir:
byron/chain/executable-spec
byron/crypto
Expand All @@ -171,6 +196,7 @@ source-repository-package
byron/ledger/impl
byron/ledger/impl/test
semantics/executable-spec
cardano-protocol-tpraos
semantics/small-steps-test
shelley/chain-and-ledger/dependencies/non-integer
shelley/chain-and-ledger/executable-spec
Expand All @@ -185,7 +211,7 @@ source-repository-package
source-repository-package
type: git
location: https://github.com/input-output-hk/cardano-node.git
tag: 3a56ac245c83d3345f81123ec3bb496bb23477a3
tag: ed7fdbf65f40f8e194850b87dd8c631fe26154e6
subdir:
cardano-api
cardano-node
Expand Down

0 comments on commit 820b2f1

Please sign in to comment.