Skip to content

Commit

Permalink
added basic spammer loop
Browse files Browse the repository at this point in the history
  • Loading branch information
sadMaxim committed Nov 28, 2023
1 parent d9d6740 commit 97f796f
Show file tree
Hide file tree
Showing 7 changed files with 92 additions and 53 deletions.
19 changes: 7 additions & 12 deletions spammer/spammer/exe/Main.purs
Original file line number Diff line number Diff line change
Expand Up @@ -5,34 +5,29 @@ module Main (main) where
import Contract.Prelude

import Aeson (class DecodeAeson, class EncodeAeson, JsonDecodeError, decodeJsonString, getField)
import Contract.Monad (launchAff_, runContract)
import Contract.Monad (launchAff_, runContract, throwContractError)
import Contract.Wallet (getWalletUtxos, ownPaymentPubKeyHashes, withKeyWallet)
import Data.Argonaut (Json, decodeJson, jsonParser, parseJson, toObject)
import Data.Array as Data.Array
import Effect.Aff (error)
import Effect.Aff (error, try)
import Effect.Exception (throw)
import Node.Encoding (Encoding(..))
import Node.FS.Sync (readFile, readTextFile)
import Spammer.Config (config)
import Spammer.Contracts (loopPayWalletFromPubKey, payFromWalletToPubKey)
import Spammer.Db (executeQuery)
import Spammer.Query.PubKeys (getPubKeyHash)
import Spammer.Query.Wallet (getWallet')
import Spammer.Query.PubKeys (getPubKey)
import Spammer.Start (startSpammer)



main :: Effect Unit
main = do
-- startSpammer
launchAff_ do
keyWallet <- getWallet'
runContract config $ withKeyWallet keyWallet do
pubKeyToPay <- getPubKey
mutxos <- getWalletUtxos
pkeyhashes <- ownPaymentPubKeyHashes
log $ show $ pkeyhashes
log $ show $ mutxos
log $ show $ pubKeyToPay
runContract config do
loopPayWalletFromPubKey Nothing




Expand Down
54 changes: 25 additions & 29 deletions spammer/spammer/src/Contracts.purs
Original file line number Diff line number Diff line change
Expand Up @@ -2,41 +2,37 @@ module Spammer.Contracts where

import Contract.Prelude

import Contract.Address (NetworkId(..), PaymentPubKey(..), scriptHashAddress)
import Contract.Config (ContractParams, ContractSynchronizationParams, ContractTimeParams, PrivatePaymentKeySource(..), WalletSpec(..), defaultKupoServerConfig, defaultOgmiosWsConfig, emptyHooks)
import Contract.Monad (Contract, launchAff_, runContract)
import Contract.PlutusData (unitDatum, unitRedeemer)
import Contract.ScriptLookups (ScriptLookups, ownPaymentPubKeyHash, unspentOutputs, validator)
import Contract.Scripts (Validator(..), validatorHash)
import Contract.TextEnvelope (decodeTextEnvelope, plutusScriptV2FromEnvelope)
import Contract.Monad (Contract, throwContractError)
import Contract.ScriptLookups (unspentOutputs)
import Contract.Transaction (submitTxFromConstraints)
import Contract.TxConstraints (DatumPresence(..), TxConstraints, mustPayToPubKey, mustPayToScript, mustSpendScriptOutput)
import Contract.Utxos (utxosAt)
import Contract.TxConstraints (mustPayToPubKey)
import Contract.Value (lovelaceValueOf)
import Contract.Wallet (Wallet, getWalletUtxos, ownStakePubKeyHashes)
import Contract.Wallet (KeyWallet, getWalletUtxos, withKeyWallet)
import Control.Monad.Error.Class (liftMaybe)
import Ctl.Internal.Contract.QueryBackend (QueryBackendParams(..))
import Ctl.Internal.Contract.Wallet (withWallet)
import Ctl.Internal.Types.PubKeyHash (PaymentPubKeyHash)
import Data.BigInt as BInt
import Data.Map (findMax)
import Data.Maybe (Maybe(..))
import Data.Number (infinity)
import Data.Time.Duration (Milliseconds(..), Seconds(..))
import Data.UInt (fromInt)
import Effect.Aff (try)
import Effect.Exception (error)
import Ctl.Internal.Types.PubKeyHash (PaymentPubKeyHash)
import Spammer.Query.PubKeys (getPubKeyHash)
import Spammer.Query.Wallet (getWallet')

loopPayWalletFromPubKey :: Maybe KeyWallet -> Contract Unit
loopPayWalletFromPubKey previousWalletWithError = do
keyWallet <- getWallet' previousWalletWithError
pubKeyHashToPay <- getPubKeyHash
res <- try $ payFromWalletToPubKey keyWallet pubKeyHashToPay
case res of
Left _ -> loopPayWalletFromPubKey (Just keyWallet)
Right _ -> loopPayWalletFromPubKey Nothing

payFromWalletToPubKey :: Wallet -> PaymentPubKeyHash -> Contract Unit
payFromWalletToPubKey wallet pubKey = withWallet \wallet -> do
payFromWalletToPubKey :: KeyWallet -> PaymentPubKeyHash -> Contract Unit
payFromWalletToPubKey wallet pubKeyHash = withKeyWallet wallet do
mUtxos <- getWalletUtxos
keyHashes <- ownStakePubKeyHashes
utxos <- liftMaybe (error "no utxos") mUtxos
log $ show $ keyHashes
-- let
-- value = lovelaceValueOf (BInt.fromInt 2_000_000)
-- lookups = unspentOutputs utxos
-- constraints = mustPayToPubKey (validatorHash val) unitDatum DatumWitness value
-- txId <- submitTxFromConstraints lookups constraints
-- log $ show $ txId
log "Successfully submitted"
let
value = lovelaceValueOf (BInt.fromInt 2_000_000)
lookups = unspentOutputs utxos
constraints = mustPayToPubKey pubKeyHash value
_ <- submitTxFromConstraints lookups constraints
pure unit

6 changes: 5 additions & 1 deletion spammer/spammer/src/Query/Db.js
Original file line number Diff line number Diff line change
Expand Up @@ -14,8 +14,12 @@ exports._executeQuery = function (queryString) {
return client.query(queryString);
})
.then(result => {
console.log(result.rows);
if (Array.isArray(result)) {
L = result.length
onSuccess(result[L-1].rows)
} else {
onSuccess(result.rows)
}
})
.catch(err => {
console.error('Error query:', err);
Expand Down
4 changes: 2 additions & 2 deletions spammer/spammer/src/Query/PubKeys.purs
Original file line number Diff line number Diff line change
Expand Up @@ -13,8 +13,8 @@ import Spammer.Utils (liftJsonDecodeError)

type Result = Array { pubkey :: String }

getPubKey :: Contract PaymentPubKeyHash
getPubKey = liftContractAffM
getPubKeyHash :: Contract PaymentPubKeyHash
getPubKeyHash = liftContractAffM
"failed to get PublicKey for utxo out"
do
json <- executeQuery "SELECT pubkey FROM pkeys ORDER BY balance LIMIT 1;"
Expand Down
53 changes: 44 additions & 9 deletions spammer/spammer/src/Query/Wallet.purs
Original file line number Diff line number Diff line change
@@ -1,27 +1,62 @@
module Spammer.Query.Wallet where
module Spammer.Query.Wallet (getWallet', updateWalletBalanceDb) where

import Contract.Prelude

import Contract.Monad (Contract, liftContractAffM)
import Contract.Wallet (KeyWallet, PrivatePaymentKey(..), privateKeysToKeyWallet)
import Contract.Wallet.Key (keyWalletPrivatePaymentKey)
import Control.Monad.Error.Class (liftMaybe)
import Data.Argonaut (decodeJson)
import Data.Array (head)
import Effect.Exception (error)
import Spammer.Db (executeQuery)
import Spammer.Keys (getPrivateKeyFromHex)
import Spammer.Utils (liftJsonDecodeError)
import Spammer.Keys (genPrivateKey, getPrivateKeyFromHex, getPrivateKeyHex, getPubKeyHex)
import Spammer.Utils (liftJsonDecodeError, quotes)

type Result = Array
type PrivKeyQueryResult = Array
{ pkey :: String
}

getWallet' :: Aff KeyWallet
getWallet' = do
json <- executeQuery "SELECT pkey FROM pkeys LIMIT 1;"
result :: Result <- liftEffect $ liftJsonDecodeError (decodeJson json)
getWallet' :: Maybe KeyWallet -> Contract KeyWallet
getWallet' previousWalletWithError = liftContractAffM "cannot get keyWallet" do
query' <- query previousWalletWithError
json <- executeQuery query'
result :: PrivKeyQueryResult <- liftEffect $ liftJsonDecodeError (decodeJson json)
res <- liftMaybe (error "empty array in getWallet'") $ head result
let
pkey = PrivatePaymentKey (getPrivateKeyFromHex res.pkey)
keyWallet = privateKeysToKeyWallet pkey Nothing
pure keyWallet
pure <<< pure $ keyWallet

query :: Maybe KeyWallet -> Aff String
query previousWalletWithError = liftEffect do
case previousWalletWithError of
Just keyWallet -> do
newPrivKey <- genPrivateKey
let
newPrivKeyHex = getPrivateKeyHex newPrivKey
newPubKeyHex = getPubKeyHex newPrivKey
prevPrivateKey = unwrap $ keyWalletPrivatePaymentKey keyWallet
prevPrivateKeyHex = getPrivateKeyHex prevPrivateKey

insertNewKeyDb = "INSERT INTO pkeys (pkey, pubkey, balance) VALUES "
<> "( "
<> quotes newPrivKeyHex
<> ","
<> quotes newPubKeyHex
<> ",0); "

selectKey = "SELECT pkey FROM pkeys "
<> " WHERE pkey != "
<>
quotes prevPrivateKeyHex
<>
" ORDER BY balance DESC LIMIT 1;"

pure $ insertNewKeyDb <> selectKey

Nothing -> pure $ "SELECT pkey FROM pkeys ORDER BY balance DESC LIMIT 1;"

updateWalletBalanceDb :: KeyWallet -> Contract Unit
updateWalletBalanceDb keyWallet = do
pure unit
2 changes: 2 additions & 0 deletions spammer/spammer/src/Utils.purs
Original file line number Diff line number Diff line change
Expand Up @@ -11,3 +11,5 @@ liftJsonDecodeError eitherErrA = do
Left e -> throw $ printJsonDecodeError e
Right x -> pure x

quotes :: String -> String
quotes x = "'" <> x <> "'"
7 changes: 7 additions & 0 deletions start.sh
Original file line number Diff line number Diff line change
@@ -0,0 +1,7 @@
#!/bin/sh
nix run .#runnet start
sleep 1
nix run .#first-transaction
ogmios --host 0.0.0.0 --node-socket cardano-conf/sockets/node-relay-1-socket/node.socket --node-config cardano-conf/configuration.yaml


0 comments on commit 97f796f

Please sign in to comment.