Skip to content

Commit

Permalink
add initial price
Browse files Browse the repository at this point in the history
  • Loading branch information
olgaklimenko committed Oct 20, 2021
1 parent 5740369 commit 25e1b66
Show file tree
Hide file tree
Showing 7 changed files with 24 additions and 16 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -28,8 +28,8 @@ import Ledger
import qualified Ledger.Typed.Scripts as Scripts
import Ledger.Typed.Tx
import Ledger.Value
import Plutus.Abstract.ContractResponse (withRemoteDataResponse)
import Plutus.Abstract.RemoteData (RemoteData)
import Plutus.Abstract.ContractResponse (withRemoteDataResponse)
import Plutus.Abstract.RemoteData (RemoteData)
import Plutus.Contract
import Plutus.Contract.StateMachine
import Plutus.Contracts.Currency as Currency
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -190,8 +190,9 @@ closeSale marketplace CloseLotParams {..} = do

data StartAnAuctionParams =
StartAnAuctionParams {
saapItemId :: UserItemId,
saapDuration :: Integer --- TODO: use DiffMilliSeconds here, when it will be possible
saapItemId :: UserItemId,
saapInitialPrice :: Ada,
saapDuration :: Integer --- TODO: use DiffMilliSeconds here, when it will be possible
}
deriving stock (Haskell.Eq, Haskell.Show, Haskell.Generic)
deriving anyclass (J.ToJSON, J.FromJSON, Schema.ToSchema)
Expand All @@ -215,6 +216,7 @@ startAnAuction marketplace@Core.Marketplace{..} StartAnAuctionParams {..} = do
let startAuctionParams = Auction.StartAuctionParams {
sapOwner = self,
sapAsset = auctionValue,
sapInitialPrice = saapInitialPrice,
sapEndTime = endTime,
sapAuctionFee = Just $ Auction.AuctionFee marketplaceOperator marketplaceSaleFee
}
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -56,9 +56,10 @@ Lens.makeClassy_ ''AuctionFee
data Auction
= Auction
{ aProtocolToken :: !ThreadToken
, aOwner :: !PubKeyHash -- ^ Current owner of the asset. This is where the proceeds of the auction will be sent.
, aAsset :: !Value -- ^ The asset itself. This value is going to be locked by the auction script output.
, aEndTime :: !Ledger.POSIXTime -- ^ When the time window for bidding ends.
, aOwner :: !PubKeyHash
, aAsset :: !Value
, aInitialPrice :: !Ada
, aEndTime :: !Ledger.POSIXTime
, aAuctionFee :: Maybe AuctionFee
}
deriving stock (Haskell.Eq, Haskell.Show, Generic)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -51,10 +51,11 @@ import qualified Schema


data StartAuctionParams = StartAuctionParams {
sapOwner :: !PubKeyHash,
sapAsset :: !Value,
sapEndTime :: !Ledger.POSIXTime,
sapAuctionFee :: Maybe AuctionFee
sapOwner :: !PubKeyHash,
sapAsset :: !Value,
sapInitialPrice :: !Ada,
sapEndTime :: !Ledger.POSIXTime,
sapAuctionFee :: Maybe AuctionFee
}
deriving stock (Haskell.Eq, Haskell.Show, Generic)
deriving anyclass (J.ToJSON, J.FromJSON, Schema.ToSchema)
Expand All @@ -71,6 +72,7 @@ startAuction StartAuctionParams{..} = do
aProtocolToken = threadToken,
aOwner = sapOwner,
aAsset = sapAsset,
aInitialPrice = sapInitialPrice,
aEndTime = sapEndTime,
aAuctionFee = sapAuctionFee
}
Expand Down
5 changes: 3 additions & 2 deletions MetaLamp/nft-marketplace/src/Plutus/PAB/Simulation.hs
Original file line number Diff line number Diff line change
Expand Up @@ -211,7 +211,8 @@ runNftMarketplace = void $ Simulator.runSimulationWith handlers $ do

let auction = Marketplace.StartAnAuctionParams {
saapItemId = Marketplace.UserNftId photoTokenIpfsCid,
saapDuration = 25 * 1000
saapDuration = 25 * 1000,
saapInitialPrice = fromInteger $ 5 * oneAdaInLovelace
}
_ <-
Simulator.callEndpointOnInstance userCid "startAnAuction" auction
Expand All @@ -223,7 +224,7 @@ runNftMarketplace = void $ Simulator.runSimulationWith handlers $ do
_ <-
Simulator.callEndpointOnInstance buyerCid "bidOnAuction" Marketplace.BidOnAuctionParams {
boapItemId = Marketplace.UserNftId photoTokenIpfsCid,
boapBid = fromInteger $ 15*oneAdaInLovelace
boapBid = fromInteger $ 15 * oneAdaInLovelace
}
_ <- flip Simulator.waitForState buyerCid $ \json -> case (J.fromJSON json :: J.Result (RemoteData Text Marketplace.UserContractState)) of
J.Success (Success Marketplace.BidSubmitted) -> Just ()
Expand Down
6 changes: 4 additions & 2 deletions MetaLamp/nft-marketplace/test/Marketplace/Spec/Auction.hs
Original file line number Diff line number Diff line change
Expand Up @@ -121,7 +121,8 @@ startAnAuctionParams :: Marketplace.StartAnAuctionParams
startAnAuctionParams = Marketplace.StartAnAuctionParams
{
Marketplace.saapItemId = Marketplace.UserNftId Fixtures.catTokenIpfsCid,
Marketplace.saapDuration = 155 * 1000
Marketplace.saapDuration = 155 * 1000,
Marketplace.saapInitialPrice = fromInteger $ 5 * Fixtures.oneAdaInLovelace
}

closeLotParams :: Marketplace.CloseLotParams
Expand Down Expand Up @@ -257,7 +258,8 @@ startAnAuctionParamsB :: Marketplace.StartAnAuctionParams
startAnAuctionParamsB = Marketplace.StartAnAuctionParams
{
Marketplace.saapItemId = Marketplace.UserBundleId Fixtures.cids,
Marketplace.saapDuration = 142 * 1000
Marketplace.saapDuration = 142 * 1000,
Marketplace.saapInitialPrice = fromInteger $ 15 * Fixtures.oneAdaInLovelace
}

closeLotParamsB :: Marketplace.CloseLotParams
Expand Down
2 changes: 1 addition & 1 deletion MetaLamp/nft-marketplace/test/Utils/Trace.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,10 +10,10 @@ import Control.Lens ((^?))
import Data.Maybe (isJust)
import GHC.TypeLits (KnownSymbol)
import Plutus.Abstract.RemoteData (RemoteData (..))
import qualified Plutus.Abstract.RemoteData as RD
import qualified Plutus.Contract as C
import Plutus.Contract.Test (TracePredicate, assertAccumState)
import qualified Plutus.Trace.Emulator as Trace
import qualified Plutus.Abstract.RemoteData as RD

assertRDError :: forall contract e r s err a proxy l. (Show r, Show e, C.IsContract contract, KnownSymbol l) =>
proxy l ->
Expand Down

0 comments on commit 25e1b66

Please sign in to comment.