Skip to content

Commit

Permalink
Merge pull request #45 from fullstack-development/backend-integration
Browse files Browse the repository at this point in the history
Backend integration
  • Loading branch information
KateBushueva authored Jul 7, 2023
2 parents 3ff09c3 + c91ddb4 commit a8a14e6
Show file tree
Hide file tree
Showing 12 changed files with 91 additions and 36 deletions.
2 changes: 1 addition & 1 deletion dist/535.index.js

Large diffs are not rendered by default.

5 changes: 0 additions & 5 deletions scripts/alwaysSucceedsValidator.plutus

This file was deleted.

20 changes: 20 additions & 0 deletions src/Ext/Seriaization/Key.purs
Original file line number Diff line number Diff line change
@@ -0,0 +1,20 @@
module Ext.Seriaization.Key where

import Contract.Prelude

import Contract.Monad (liftContractM, Contract)
import Ctl.Internal.Serialization.Hash (ed25519KeyHashToBech32, ed25519KeyHashFromBech32)
import Ctl.Internal.Types.Aliases (Bech32String)
import Ctl.Internal.Types.PubKeyHash (PaymentPubKeyHash(..), PubKeyHash(..))

pkhToBech32 PaymentPubKeyHash Maybe Bech32String
pkhToBech32 pkh = ed25519KeyHashToBech32 "addr_vkh" (unwrap $ unwrap pkh)

pkhFromBech32 Bech32String Maybe PaymentPubKeyHash
pkhFromBech32 pkhStr = (PubKeyHash >>> PaymentPubKeyHash) <$> ed25519KeyHashFromBech32 pkhStr

pkhToBech32M PaymentPubKeyHash Contract Bech32String
pkhToBech32M pkh = liftContractM "Impossible to serialize pkh" $ pkhToBech32 pkh

pkhFromBech32M Bech32String Contract PaymentPubKeyHash
pkhFromBech32M pkhStr = liftContractM "Impossible to deserialize pkh" $ pkhFromBech32 pkhStr
18 changes: 10 additions & 8 deletions src/Fundraising/Create.purs
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,10 @@ import Data.Map (toUnfoldable) as Map
import Data.String (take)
import Effect.Aff (runAff_)
import Effect.Exception (throw, Error, message)
import Fundraising.Datum (PFundraisingDatum(..), descLength)
import Ext.Contract.Time (addTimes)
import Ext.Contract.Value (currencySymbolToString, mkCurrencySymbol)
import Ext.Seriaization.Key (pkhToBech32M)
import Fundraising.Datum (PFundraisingDatum(..), titleLength)
import Fundraising.FundraisingScript (getFundraisingTokenName, fundraisingValidatorScript, getFundraisingValidatorHash)
import Fundraising.Models (Fundraising(..))
import Fundraising.UserData (CreateFundraisingParams(..))
Expand All @@ -42,8 +45,6 @@ import Shared.Duration (durationToMinutes, minutesToPosixTime)
import Shared.MinAda (minAdaValue)
import Shared.TestnetConfig (mkTestnetNamiConfig)
import Shared.Utxo (extractDatumFromUTxO, extractValueFromUTxO, filterNonCollateral)
import Ext.Contract.Value (currencySymbolToString, mkCurrencySymbol)
import Ext.Contract.Time (addTimes)

runCreateFundraising :: (FundraisingInfo -> Effect Unit) -> (String -> Effect Unit) -> ProtocolData -> CreateFundraisingParams -> Effect Unit
runCreateFundraising onComplete onError protocolData params = do
Expand All @@ -55,7 +56,7 @@ runCreateFundraising onComplete onError protocolData params = do
handler (Left err) = onError $ message err

contract :: ProtocolData -> CreateFundraisingParams -> Contract FundraisingInfo
contract protocolData (CreateFundraisingParams { description, amount, duration }) = do
contract protocolData (CreateFundraisingParams { title, amount, duration }) = do
logInfo' "Running Create Fundraising contract"
givenProtocol <- dataToProtocol protocolData
ownHashes <- ownPaymentPubKeysHashes
Expand Down Expand Up @@ -111,13 +112,13 @@ contract protocolData (CreateFundraisingParams { description, amount, duration }

now@(POSIXTime now') <- currentTime
let deadline = addTimes now (minutesToPosixTime frDurationMinutes)
desc <- liftContractM "Impossible to serialize description" $ byteArrayFromAscii (take descLength description)
serializedTitle <- liftContractM "Impossible to serialize a title" $ byteArrayFromAscii (take titleLength title)

let
initialFrDatum = PFundraisingDatum
{ creatorPkh: ownPkh
, tokenOrigin: oref
, frDesc: desc
, frTitle: serializedTitle
, frAmount: targetAmount
, frDeadline: deadline
, frFee: view _protocolFee protocolDatum
Expand Down Expand Up @@ -207,9 +208,10 @@ contract protocolData (CreateFundraisingParams { description, amount, duration }
bech32Address <- addressToBech32 frAddress
logInfo' $ "Current fundraising address: " <> show bech32Address

creatorPkh <- pkhToBech32M ownPkh
pure $ FundraisingInfo
{ creator: ownPkh
, description: description
{ creator: creatorPkh
, title: title
, goal: targetAmount
, raisedAmt: fromInt 0
, deadline: deadline
Expand Down
13 changes: 7 additions & 6 deletions src/Fundraising/Datum.purs
Original file line number Diff line number Diff line change
@@ -1,24 +1,25 @@
module Fundraising.Datum where

import Ctl.Internal.FromData

import Contract.Address (PaymentPubKeyHash)
import Contract.Time (POSIXTime)
import Contract.PlutusData (class HasPlutusSchema, type (:+), type (:=), type (@@), I, PNil, Z, genericToData)
import Contract.Prelude (class Generic, class Show)
import Ctl.Internal.FromData
import Contract.Time (POSIXTime)
import Ctl.Internal.ToData (class ToData)
import Ctl.Internal.Types.ByteArray (ByteArray)
import Ctl.Internal.Types.Transaction (TransactionInput)
import Data.BigInt (BigInt)
import Data.Newtype (class Newtype)
import Prelude (class Eq, class Ord)

descLength :: Int
descLength = 35
titleLength :: Int
titleLength = 35

newtype PFundraisingDatum = PFundraisingDatum
{ creatorPkh :: PaymentPubKeyHash
, tokenOrigin :: TransactionInput
, frDesc :: ByteArray -- descLength is set to limit the description size
, frTitle :: ByteArray -- titleLength is set to limit the title size
, frAmount :: BigInt -- amount to raise in Lovelace
, frDeadline :: POSIXTime
, frFee :: BigInt -- percentage
Expand All @@ -39,7 +40,7 @@ instance
( "creatorPkh" := I PaymentPubKeyHash
:+ "tokenOrigin"
:= I TransactionInput
:+ "frDesc"
:+ "frTitle"
:= I ByteArray
:+ "frAmount"
:= I BigInt
Expand Down
2 changes: 1 addition & 1 deletion src/Fundraising/UserData.purs
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@ import Info.UserData (FundraisingInfo(..))
import Shared.Duration (Duration)

newtype CreateFundraisingParams = CreateFundraisingParams
{ description :: String -- 35 symbols max
{ title :: String -- 35 symbols max
, amount :: Int -- amount to raise in Ada (not Lovelace)
, duration :: Duration
}
Expand Down
24 changes: 13 additions & 11 deletions src/Info/UserData.purs
Original file line number Diff line number Diff line change
Expand Up @@ -2,26 +2,27 @@ module Info.UserData where

import Contract.Prelude

import Contract.Address (PaymentPubKeyHash, Bech32String)
import Contract.Address (Bech32String)
import Contract.Chain (currentTime)
import Contract.Monad (Contract, liftContractM)
import Contract.Time (POSIXTime)
import Contract.Value as Value
import Ctl.Internal.Types.ByteArray (ByteArray(..))
import Ext.Data.Either (eitherContract)
import Data.Array as Array
import Data.BigInt (BigInt)
import Data.TextDecoder (decodeUtf8)
import Ext.Contract.Value (getCurrencyByTokenName, currencySymbolToString)
import Ext.Data.Either (eitherContract)
import Ext.Seriaization.Key (pkhToBech32M)
import Fundraising.Datum (PFundraisingDatum(..))
import Fundraising.FundraisingScript (getFundraisingTokenName)
import Protocol.UserData (ProtocolConfigParams)
import Shared.Utxo (UtxoTuple, extractDatumFromUTxO, extractValueFromUTxO)
import Ext.Contract.Value (getCurrencyByTokenName, currencySymbolToString)
import Shared.MinAda (minAdaValue)
import Shared.Utxo (UtxoTuple, extractDatumFromUTxO, extractValueFromUTxO)

newtype FundraisingInfo = FundraisingInfo
{ creator :: PaymentPubKeyHash
, description :: String
{ creator :: Bech32String
, title :: String
, goal :: BigInt -- Goal in lovelaces
, raisedAmt :: BigInt -- Raised amount in lovelaces
, deadline :: POSIXTime
Expand All @@ -39,15 +40,16 @@ mapToFundraisingInfo utxo = do
PFundraisingDatum currentDatum <- liftContractM "Impossible to extract datum from UTxO" $ extractDatumFromUTxO utxo
let frVal = extractValueFromUTxO utxo
let currentFunds = Value.valueToCoin' frVal - Value.valueToCoin' minAdaValue - Value.valueToCoin' minAdaValue
let ByteArray unwrappedDesc = currentDatum.frDesc
desc <- eitherContract "Description decoding failed: " $ decodeUtf8 unwrappedDesc
let ByteArray unwrappedTitle = currentDatum.frTitle
title <- eitherContract "Title decoding failed: " $ decodeUtf8 unwrappedTitle
frTokenName <- getFundraisingTokenName
cs <- liftContractM "Impossible to get currency by token name" $ getCurrencyByTokenName frVal frTokenName
let pathStr = currencySymbolToString cs
now <- currentTime
creator <- pkhToBech32M currentDatum.creatorPkh
pure $ FundraisingInfo
{ creator: currentDatum.creatorPkh
, description: desc
{ creator: creator
, title: title
, goal: currentDatum.frAmount
, raisedAmt: currentFunds
, deadline: currentDatum.frDeadline
Expand All @@ -57,7 +59,7 @@ mapToFundraisingInfo utxo = do
, isCompleted: now > currentDatum.frDeadline || currentFunds >= currentDatum.frAmount
}

filterByPkh :: PaymentPubKeyHash -> Array FundraisingInfo -> Array FundraisingInfo
filterByPkh :: Bech32String -> Array FundraisingInfo -> Array FundraisingInfo
filterByPkh pkh = Array.filter belongsToUser
where
belongsToUser (FundraisingInfo frInfo) = frInfo.creator == pkh
Expand Down
4 changes: 3 additions & 1 deletion src/Info/UserRelatedFundraisings.purs
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,7 @@ import Contract.Monad (Contract, liftContractM, runContract)
import Data.Array as Array
import Effect.Aff (runAff_)
import Effect.Exception (Error, message)
import Ext.Seriaization.Key (pkhToBech32M)
import Info.AllFundraisings (getAllFundraisings)
import Info.UserData (FundraisingInfo, filterByPkh)
import Protocol.UserData (ProtocolData)
Expand All @@ -28,6 +29,7 @@ getUserRelatedFundraisings protocolData = do
ownHashes <- ownPaymentPubKeysHashes
ownPkh <- liftContractM "Impossible to get own PaymentPubkeyHash" $ Array.head ownHashes
logInfo' $ "Own Payment pkh is: " <> show ownPkh
let userFrs = filterByPkh ownPkh allFrs
pkh <- pkhToBech32M ownPkh
let userFrs = filterByPkh pkh allFrs
logInfo' $ "Discovered items: " <> show userFrs
pure userFrs
2 changes: 1 addition & 1 deletion test/Plutip/Contracts/CreateFundraising.purs
Original file line number Diff line number Diff line change
Expand Up @@ -108,7 +108,7 @@ suite = do

mkFundraisingParams :: Int -> Duration -> CreateFundraisingParams
mkFundraisingParams amt dur = CreateFundraisingParams
{ description: "Donate to feed stray cats"
{ title: "Donate to feed stray cats"
, amount: amt
, duration: dur
}
Expand Down
31 changes: 31 additions & 0 deletions test/Unit/Serialization.purs
Original file line number Diff line number Diff line change
@@ -0,0 +1,31 @@
module Test.Unit.Serialization (suite) where

import Prelude

import Ctl.Internal.Serialization.Hash (Ed25519KeyHash, ed25519KeyHashFromBytes)
import Ctl.Internal.Test.TestPlanM (TestPlanM)
import Ctl.Internal.Types.ByteArray (hexToByteArrayUnsafe)
import Ctl.Internal.Types.PubKeyHash (PaymentPubKeyHash(..), PubKeyHash(..))
import Effect.Aff (Aff)
import Mote (test)
import Partial.Unsafe (unsafePartial)
import Test.Spec.Assertions (shouldEqual)
import Data.Maybe (fromJust, maybe)
import Effect.Class (liftEffect)
import Effect.Exception (throw)
import Ext.Seriaization.Key (pkhFromBech32, pkhToBech32)

pk :: Ed25519KeyHash
pk = unsafePartial $ fromJust $ ed25519KeyHashFromBytes $
hexToByteArrayUnsafe
"49d49d1715768d0b9fb498e60a7515e390c744330b91f4a1f6329afa"

pkh PaymentPubKeyHash
pkh = PaymentPubKeyHash $ PubKeyHash pk

suite :: TestPlanM (Aff Unit) Unit
suite =
test "Pkh serialization tests" do
bech32Pkh <- maybe (liftEffect $ throw "Can't serialize pkh to Bech32") pure $ pkhToBech32 pkh
resultPkh <- maybe (liftEffect $ throw "Can't deserialize pkh from Bech32") pure $ pkhFromBech32 bech32Pkh
resultPkh `shouldEqual` pkh
2 changes: 2 additions & 0 deletions test/UnitTests.purs
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,7 @@ import Effect (Effect)
import Effect.Aff (Aff, cancelWith, effectCanceler, launchAff)
import Test.Spec.Runner (defaultConfig)
import Test.Unit.CalcFee as CalcFee
import Test.Unit.Serialization as Serialization

-- Run with `spago test --main Test.UnitTests`
main :: Effect Unit
Expand All @@ -23,3 +24,4 @@ main = interruptOnSignal SIGINT =<< launchAff do
testPlan :: TestPlanM (Aff Unit) Unit
testPlan = do
CalcFee.suite
Serialization.suite
4 changes: 2 additions & 2 deletions ui/index.tsx
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ const root = ReactDOM.createRoot(document.getElementById('root')!);
const App = () => {

const protocolData = {
protocolCurrency: "965eb584a53eb856210865238a9ef1bfc7a5f00efa895da519185364",
protocolCurrency: "6697f44bf023bba314bf77affe384d2ac73e028861c1a1e5ec58d090",
protocolTokenName: "DonatPoolProtocol"
}

Expand All @@ -20,7 +20,7 @@ const App = () => {
};

const createFundraisingParams = {
description: 'Donate to feed stray cats',
title: 'Donate to feed stray cats',
amount: 200,
duration: fundraisingDuration
};
Expand Down

0 comments on commit a8a14e6

Please sign in to comment.