Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
6 changes: 4 additions & 2 deletions src/BotPlutusInterface/Balance.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@ module BotPlutusInterface.Balance (
) where

import BotPlutusInterface.CardanoCLI qualified as CardanoCLI
import BotPlutusInterface.Effects (PABEffect, createDirectoryIfMissing, printLog)
import BotPlutusInterface.Effects (PABEffect, createDirectoryIfMissingCLI, printLog)
import BotPlutusInterface.Files (DummyPrivKey, unDummyPrivateKey)
import BotPlutusInterface.Files qualified as Files
import BotPlutusInterface.Types (LogLevel (Debug), PABConfig)
Expand Down Expand Up @@ -82,6 +82,9 @@ balanceTxIO pabConf ownPkh unbalancedTx =

lift $ printLog @w Debug $ show utxoIndex

-- We need this folder on the CLI machine, which may not be the local machine
lift $ createDirectoryIfMissingCLI @w False (Text.unpack pabConf.pcTxFileDir)

-- Adds required collaterals, only needs to happen once
-- Also adds signatures for fee calculation
preBalancedTx <- hoistEither $ addTxCollaterals utxoIndex tx >>= addSignatories ownPkh privKeys requiredSigs
Expand Down Expand Up @@ -125,7 +128,6 @@ balanceTxIO pabConf ownPkh unbalancedTx =
txWithoutFees <-
hoistEither $ balanceTxStep minUtxos utxoIndex ownPkh $ tx `withFee` 0

lift $ createDirectoryIfMissing @w False (Text.unpack pabConf.pcTxFileDir)
newEitherT $ CardanoCLI.buildTx @w pabConf privKeys txWithoutFees
fees <- newEitherT $ CardanoCLI.calculateMinFee @w pabConf txWithoutFees

Expand Down
16 changes: 1 addition & 15 deletions src/BotPlutusInterface/CardanoCLI.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,15 +7,14 @@ module BotPlutusInterface.CardanoCLI (
calculateMinFee,
buildTx,
signTx,
uploadFiles,
validatorScriptFilePath,
unsafeSerialiseAddress,
policyScriptFilePath,
utxosAt,
queryTip,
) where

import BotPlutusInterface.Effects (PABEffect, ShellArgs (..), callCommand, uploadDir)
import BotPlutusInterface.Effects (PABEffect, ShellArgs (..), callCommand)
import BotPlutusInterface.Files (
DummyPrivKey (FromSKey, FromVKey),
datumJsonFilePath,
Expand Down Expand Up @@ -93,19 +92,6 @@ import Plutus.V1.Ledger.Api qualified as Plutus
import PlutusTx.Builtins (fromBuiltin)
import Prelude

-- | Upload script files to remote server
uploadFiles ::
forall (w :: Type) (effs :: [Type -> Type]).
Member (PABEffect w) effs =>
PABConfig ->
Eff effs ()
uploadFiles pabConf =
mapM_
(uploadDir @w)
[ pabConf.pcScriptFileDir
, pabConf.pcSigningKeyFileDir
]

-- | Getting information of the latest block
queryTip ::
forall (w :: Type) (effs :: [Type -> Type]).
Expand Down
12 changes: 8 additions & 4 deletions src/BotPlutusInterface/Contract.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,7 @@ import BotPlutusInterface.Effects (
printLog,
queryChainIndex,
threadDelay,
uploadDir,
)
import BotPlutusInterface.Files (DummyPrivKey (FromSKey, FromVKey))
import BotPlutusInterface.Files qualified as Files
Expand Down Expand Up @@ -170,10 +171,12 @@ balanceTx ::
UnbalancedTx ->
Eff effs BalanceTxResponse
balanceTx contractEnv unbalancedTx = do
let pabConf = contractEnv.cePABConfig
uploadDir @w pabConf.pcSigningKeyFileDir
eitherPreBalancedTx <-
PreBalance.balanceTxIO @w
contractEnv.cePABConfig
(contractEnv.cePABConfig.pcOwnPubKeyHash)
pabConf
pabConf.pcOwnPubKeyHash
unbalancedTx

pure $ either (BalanceTxFailed . InsufficientFunds) (BalanceTxSuccess . Right) eitherPreBalancedTx
Expand All @@ -188,18 +191,19 @@ writeBalancedTx ::
writeBalancedTx _ (Left _) = error "Cannot handle cardano api tx"
writeBalancedTx contractEnv (Right tx) = do
let pabConf = contractEnv.cePABConfig
uploadDir @w pabConf.pcSigningKeyFileDir
createDirectoryIfMissing @w False (Text.unpack pabConf.pcScriptFileDir)

eitherT (pure . WriteBalancedTxFailed . OtherError) (pure . WriteBalancedTxSuccess . Right) $ do
void $ firstEitherT (Text.pack . show) $ newEitherT $ Files.writeAll @w pabConf tx
lift $ uploadDir @w pabConf.pcScriptFileDir

privKeys <- newEitherT $ Files.readPrivateKeys @w pabConf

let requiredSigners = Map.keys $ tx ^. Tx.signatures
skeys = Map.filter (\case FromSKey _ -> True; FromVKey _ -> False) privKeys
signable = all ((`Map.member` skeys) . Ledger.pubKeyHash) requiredSigners

lift $ CardanoCLI.uploadFiles @w pabConf

newEitherT $ CardanoCLI.buildTx @w pabConf privKeys tx

if signable
Expand Down
28 changes: 26 additions & 2 deletions src/BotPlutusInterface/Effects.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,7 @@ module BotPlutusInterface.Effects (
ShellArgs (..),
handlePABEffect,
createDirectoryIfMissing,
createDirectoryIfMissingCLI,
queryChainIndex,
listDirectory,
threadDelay,
Expand Down Expand Up @@ -37,6 +38,8 @@ import Data.Aeson (ToJSON)
import Data.Aeson qualified as JSON
import Data.Bifunctor (second)
import Data.Kind (Type)
import Data.Maybe (catMaybes)
import Data.String (IsString, fromString)
import Data.Text (Text)
import Data.Text qualified as Text
import Plutus.Contract.Effects (ChainIndexQuery, ChainIndexResponse)
Expand All @@ -58,6 +61,8 @@ instance Show (ShellArgs a) where
data PABEffect (w :: Type) (r :: Type) where
CallCommand :: ShellArgs a -> PABEffect w (Either Text a)
CreateDirectoryIfMissing :: Bool -> FilePath -> PABEffect w ()
-- Same as above but creates folder on the CLI machine, be that local or remote.
CreateDirectoryIfMissingCLI :: Bool -> FilePath -> PABEffect w ()
PrintLog :: LogLevel -> String -> PABEffect w ()
UpdateInstanceState :: Activity -> PABEffect w ()
LogToContract :: (ToJSON w, Monoid w) => w -> PABEffect w ()
Expand Down Expand Up @@ -93,6 +98,10 @@ handlePABEffect contractEnv =
Remote ipAddr -> callRemoteCommand ipAddr shellArgs
CreateDirectoryIfMissing createParents filePath ->
Directory.createDirectoryIfMissing createParents filePath
CreateDirectoryIfMissingCLI createParents filePath ->
case contractEnv.cePABConfig.pcCliLocation of
Local -> Directory.createDirectoryIfMissing createParents filePath
Remote ipAddr -> createDirectoryIfMissingRemote ipAddr createParents filePath
PrintLog logLevel txt -> printLog' contractEnv.cePABConfig.pcLogLevel logLevel txt
UpdateInstanceState s -> do
atomically $
Expand Down Expand Up @@ -132,8 +141,15 @@ callRemoteCommand ipAddr ShellArgs {cmdName, cmdArgs, cmdOutParser} =
"ssh"
(map Text.unpack [ipAddr, Text.unwords $ "source ~/.bash_profile;" : cmdName : map quotes cmdArgs])

quotes :: Text -> Text
quotes str = "\"" <> str <> "\""
createDirectoryIfMissingRemote :: Text -> Bool -> FilePath -> IO ()
createDirectoryIfMissingRemote ipAddr createParents path =
void $ readProcessEither "ssh" $ catMaybes [Just $ Text.unpack ipAddr, Just "mkdir", pFlag, Just $ quotes path]
where
pFlag :: Maybe String
pFlag = if createParents then Just "-p" else Nothing

quotes :: forall (a :: Type). (IsString a, Semigroup a) => a -> a
quotes str = fromString "\"" <> str <> fromString "\""

readProcessEither :: FilePath -> [String] -> IO (Either Text String)
readProcessEither path args =
Expand Down Expand Up @@ -162,6 +178,14 @@ createDirectoryIfMissing ::
Eff effs ()
createDirectoryIfMissing createParents path = send @(PABEffect w) $ CreateDirectoryIfMissing createParents path

createDirectoryIfMissingCLI ::
forall (w :: Type) (effs :: [Type -> Type]).
Member (PABEffect w) effs =>
Bool ->
FilePath ->
Eff effs ()
createDirectoryIfMissingCLI createParents path = send @(PABEffect w) $ CreateDirectoryIfMissingCLI createParents path

printLog ::
forall (w :: Type) (effs :: [Type -> Type]).
Member (PABEffect w) effs =>
Expand Down
2 changes: 2 additions & 0 deletions test/Spec/MockContract.hs
Original file line number Diff line number Diff line change
Expand Up @@ -279,6 +279,8 @@ runPABEffectPure initState req =
go (CallCommand args) = mockCallCommand args
go (CreateDirectoryIfMissing createParents filePath) =
mockCreateDirectoryIfMissing createParents filePath
go (CreateDirectoryIfMissingCLI createParents filePath) =
mockCreateDirectoryIfMissing createParents filePath
go (PrintLog logLevel msg) = mockPrintLog logLevel msg
go (UpdateInstanceState msg) = mockUpdateInstanceState msg
go (LogToContract msg) = mockLogToContract msg
Expand Down