Skip to content

Commit 9958c8a

Browse files
committed
Merge branch 'master' of github.com:mlabs-haskell/bot-plutus-interface into gergely/raw-bytestring-tokennames
2 parents 1e784d1 + ec22060 commit 9958c8a

File tree

3 files changed

+16
-10
lines changed

3 files changed

+16
-10
lines changed

src/BotPlutusInterface/Files.hs

Lines changed: 6 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,7 @@ module BotPlutusInterface.Files (
88
readPrivateKeys,
99
signingKeyFilePath,
1010
txFilePath,
11+
txFileName,
1112
writeAll,
1213
writePolicyScriptFile,
1314
redeemerJsonFilePath,
@@ -83,7 +84,7 @@ import Plutus.V1.Ledger.Api (
8384
)
8485
import PlutusTx (ToData, toData)
8586
import PlutusTx.Builtins (fromBuiltin)
86-
import System.FilePath (takeExtension, (</>))
87+
import System.FilePath (replaceExtension, takeExtension, (</>))
8788
import Prelude
8889

8990
-- | Filename of a minting policy script
@@ -116,7 +117,10 @@ signingKeyFilePath pabConf (PubKeyHash pubKeyHash) =
116117
txFilePath :: PABConfig -> Text -> Tx.Tx -> Text
117118
txFilePath pabConf ext tx =
118119
let txId = encodeByteString $ fromBuiltin $ TxId.getTxId $ Tx.txId tx
119-
in pabConf.pcTxFileDir <> "/tx-" <> txId <> "." <> ext
120+
in pabConf.pcTxFileDir <> "/" <> txFileName txId ext
121+
122+
txFileName :: Text -> Text -> Text
123+
txFileName name ext = Text.pack $ replaceExtension ("tx-" <> Text.unpack name) (Text.unpack ext)
120124

121125
-- | Compiles and writes a script file under the given folder
122126
writePolicyScriptFile ::

src/BotPlutusInterface/Server.hs

Lines changed: 6 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -9,6 +9,7 @@ module BotPlutusInterface.Server (
99
) where
1010

1111
import BotPlutusInterface.Contract (runContract)
12+
import BotPlutusInterface.Files (txFileName)
1213
import BotPlutusInterface.Types (
1314
AppState (AppState),
1415
ContractEnvironment (..),
@@ -59,7 +60,7 @@ import Servant.API (Capture, Get, JSON, Post, ReqBody, (:<|>) (..), (:>))
5960
import Servant.API.WebSocket (WebSocketPending)
6061
import Servant.Server (Application, Handler, Server, err404, serve)
6162
import System.Directory (canonicalizePath, doesFileExist, makeAbsolute)
62-
import System.FilePath (replaceExtension, takeDirectory, (</>))
63+
import System.FilePath (takeDirectory, (</>))
6364
import Wallet.Types (ContractInstanceId (..))
6465
import Prelude
6566

@@ -83,8 +84,8 @@ type ActivateContractEndpoint a =
8384
:> Post '[JSON] ContractInstanceId -- Start a new instance.
8485

8586
type RawTxEndpoint =
86-
"rawTx"
87-
:> Capture "hash" Text
87+
"raw-tx"
88+
:> Capture "txId" Text
8889
:> Get '[JSON] RawTx
8990

9091
server :: HasDefinitions t => PABConfig -> AppState -> Server (API t)
@@ -234,15 +235,15 @@ handleContract pabConf state@(AppState st) contract = liftIO $ do
234235

235236
-- | This handler will allow to retrieve raw transactions from the pcTxFileDir if pcEnableTxEndpoint is True
236237
rawTxHandler :: PABConfig -> Text -> Handler RawTx
237-
rawTxHandler config hash = do
238+
rawTxHandler config txId = do
238239
-- Check that endpoint is enabled
239240
assert config.pcEnableTxEndpoint
240241
-- Absolute path to pcTxFileDir that is specified in the config
241242
txFolderPath <- liftIO $ makeAbsolute (unpack config.pcTxFileDir)
242243

243244
-- Add/Set .raw extension on path
244245
let suppliedPath :: FilePath
245-
suppliedPath = replaceExtension (txFolderPath </> "tx-" <> unpack hash) ".raw"
246+
suppliedPath = txFolderPath </> unpack (txFileName txId ".raw")
246247
-- Resolve path indirections
247248
path <- liftIO $ canonicalizePath suppliedPath
248249
-- ensure it does not try to escape txFolderPath

test/Spec/BotPlutusInterface/Server.hs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
module Spec.BotPlutusInterface.Server (tests) where
22

3+
import BotPlutusInterface.Files (txFileName)
34
import BotPlutusInterface.Server (RawTxEndpoint, app, initState)
45
import BotPlutusInterface.Types (
56
HasDefinitions (..),
@@ -83,7 +84,7 @@ initServerAndClient config test = do
8384
let pabConfig :: PABConfig
8485
pabConfig = config {pcTxFileDir = pack path}
8586
state <- initState
86-
LBS.writeFile (path </> txFileName) txFileContents
87+
LBS.writeFile (path </> testTxFileName) txFileContents
8788
testWithApplication (pure $ app @EmptyContract pabConfig state) (initClientOnPort test)
8889
where
8990
initClientOnPort :: RawTxTest a -> Int -> IO a
@@ -102,8 +103,8 @@ initServerAndClient config test = do
102103
txHash :: Text
103104
txHash = "test"
104105

105-
txFileName :: FilePath
106-
txFileName = "tx-" <> unpack txHash <> ".raw"
106+
testTxFileName :: FilePath
107+
testTxFileName = unpack $ txFileName txHash ".raw"
107108

108109
rawTx :: RawTx
109110
rawTx =

0 commit comments

Comments
 (0)