Skip to content

Commit 6dd9fde

Browse files
committed
Add an endpoint that allows fetching a serialised raw transation.
This endpoint must be enabled by the pcEnableTxEndpoint configuration variable. Change-type: minor
1 parent f3e65b6 commit 6dd9fde

File tree

5 files changed

+190
-6
lines changed

5 files changed

+190
-6
lines changed

bot-plutus-interface.cabal

Lines changed: 13 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -84,8 +84,7 @@ library
8484
BotPlutusInterface.PreBalance
8585
BotPlutusInterface.Types
8686
BotPlutusInterface.UtxoParser
87-
88-
other-modules: BotPlutusInterface.Server
87+
BotPlutusInterface.Server
8988
build-depends:
9089
, aeson ^>=1.5.0.0
9190
, attoparsec >=0.13.2.2
@@ -106,6 +105,7 @@ library
106105
, http-types
107106
, lens
108107
, memory
108+
, mtl
109109
, playground-common
110110
, plutus-chain-index
111111
, plutus-chain-index-core
@@ -145,6 +145,7 @@ test-suite bot-plutus-interface-test
145145
Spec.BotPlutusInterface.Contract
146146
Spec.BotPlutusInterface.PreBalance
147147
Spec.BotPlutusInterface.UtxoParser
148+
Spec.BotPlutusInterface.Server
148149
Spec.MockContract
149150

150151
build-depends:
@@ -161,12 +162,16 @@ test-suite bot-plutus-interface-test
161162
, data-default-class
162163
, either
163164
, extra
165+
, filepath
164166
, freer-extras
165167
, freer-simple
166168
, generic-arbitrary
167169
, hex
170+
, http-client
171+
, http-types
168172
, lens
169173
, neat-interpolation
174+
, playground-common
170175
, plutus-chain-index
171176
, plutus-chain-index-core
172177
, plutus-contract
@@ -181,11 +186,17 @@ test-suite bot-plutus-interface-test
181186
, quickcheck-instances
182187
, row-types
183188
, serialise
189+
, servant
190+
, servant-client
191+
, servant-client-core
184192
, stm
185193
, tasty
186194
, tasty-hunit
187195
, tasty-quickcheck
196+
, temporary
188197
, text ^>=1.2.4.0
189198
, uuid
199+
, utf8-string
200+
, warp
190201

191202
hs-source-dirs: test

src/BotPlutusInterface/Server.hs

Lines changed: 41 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -7,12 +7,13 @@ import BotPlutusInterface.Types (
77
AppState (AppState),
88
ContractEnvironment (..),
99
ContractState (ContractState, csActivity, csObservableState),
10-
PABConfig,
10+
PABConfig (..),
1111
SomeContractState (SomeContractState),
1212
)
1313
import Control.Concurrent (ThreadId, forkIO)
1414
import Control.Concurrent.STM (TVar, atomically, modifyTVar, newTVarIO, readTVar, readTVarIO, retry)
1515
import Control.Monad (forever, guard, unless, void)
16+
import Control.Monad.Error.Class (throwError)
1617
import Control.Monad.IO.Class (liftIO)
1718
import Data.Aeson (FromJSON, ToJSON (toJSON))
1819
import Data.Aeson qualified as JSON
@@ -22,6 +23,8 @@ import Data.Map qualified as Map
2223
import Data.Maybe (catMaybes)
2324
import Data.Proxy (Proxy (Proxy))
2425
import Data.Row (Row)
26+
import Data.Text (Text, unpack)
27+
import Data.Text.IO qualified as Text
2528
import Data.UUID.V4 qualified as UUID
2629
import Network.WebSockets (
2730
Connection,
@@ -45,9 +48,11 @@ import Plutus.PAB.Webserver.Types (
4548
ContractActivationArgs (..),
4649
InstanceStatusToClient (ContractFinished, NewObservableState),
4750
)
48-
import Servant.API (JSON, Post, ReqBody, (:<|>) (..), (:>))
51+
import Servant.API (Capture, Get, JSON, Post, ReqBody, (:<|>) (..), (:>))
4952
import Servant.API.WebSocket (WebSocketPending)
50-
import Servant.Server (Application, Handler, Server, serve)
53+
import Servant.Server (Application, Handler, Server, err404, serve)
54+
import System.Directory (canonicalizePath, doesFileExist, makeAbsolute)
55+
import System.FilePath (replaceExtension, takeDirectory, (</>))
5156
import Wallet.Types (ContractInstanceId (..))
5257
import Prelude
5358

@@ -63,10 +68,16 @@ type API a =
6368
:> ReqBody '[JSON] (ContractActivationArgs a)
6469
:> Post '[JSON] ContractInstanceId -- Start a new instance.
6570
)
71+
:<|> ( "rawTx"
72+
:> Capture "hash" Text
73+
:> Get '[JSON] Text
74+
)
6675

6776
server :: HasDefinitions t => PABConfig -> AppState -> Server (API t)
6877
server pabConfig state =
69-
websocketHandler state :<|> activateContractHandler pabConfig state
78+
websocketHandler state
79+
:<|> activateContractHandler pabConfig state
80+
:<|> rawTxHandler pabConfig
7081

7182
apiProxy :: forall (t :: Type). Proxy (API t)
7283
apiProxy = Proxy
@@ -206,3 +217,29 @@ handleContract pabConf state@(AppState st) contract = liftIO $ do
206217
let maybeError = toJSON <$> leftToMaybe result
207218
broadcastContractResult @w state contractInstanceID maybeError
208219
pure contractInstanceID
220+
221+
-- | This handler will allow to retrieve raw transactions from the pcTxFileDir if pcEnableTxEndpoint is True
222+
rawTxHandler :: PABConfig -> Text -> Handler Text
223+
rawTxHandler config hash = do
224+
-- Check that endpoint is enabled
225+
assert (pcEnableTxEndpoint config)
226+
-- Absolute path to pcTxFileDir that is specified in the config
227+
txFolderPath <- liftIO $ makeAbsolute (unpack $ pcTxFileDir config)
228+
229+
-- Add/Set .raw extension on path
230+
let suppliedPath :: FilePath
231+
suppliedPath = replaceExtension (txFolderPath </> "tx-" <> unpack hash) ".raw"
232+
-- Resolve path indirections
233+
path <- liftIO $ canonicalizePath suppliedPath
234+
-- ensure it does not try to escape txFolderPath
235+
assert (takeDirectory path == txFolderPath)
236+
-- ensure file exists
237+
fileExists <- liftIO $ doesFileExist path
238+
assert fileExists
239+
240+
-- Read contents of path
241+
liftIO $ Text.readFile path
242+
where
243+
assert :: Bool -> Handler ()
244+
assert True = pure ()
245+
assert False = throwError err404

src/BotPlutusInterface/Types.hs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -52,6 +52,7 @@ data PABConfig = PABConfig
5252
, pcLogLevel :: !LogLevel
5353
, pcOwnPubKeyHash :: PubKeyHash
5454
, pcPort :: !Port
55+
, pcEnableTxEndpoint :: !Bool
5556
}
5657
deriving stock (Show, Eq)
5758

@@ -100,4 +101,5 @@ instance Default PABConfig where
100101
, pcLogLevel = Info
101102
, pcOwnPubKeyHash = ""
102103
, pcPort = 9080
104+
, pcEnableTxEndpoint = False
103105
}

test/Spec.hs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@ module Main (main) where
33
import Spec.BotPlutusInterface.Contract qualified
44
import Spec.BotPlutusInterface.PreBalance qualified
55
import Spec.BotPlutusInterface.UtxoParser qualified
6+
import Spec.BotPlutusInterface.Server qualified
67
import Test.Tasty (TestTree, defaultMain, testGroup)
78
import Prelude
89

@@ -21,4 +22,5 @@ tests =
2122
[ Spec.BotPlutusInterface.Contract.tests
2223
, Spec.BotPlutusInterface.UtxoParser.tests
2324
, Spec.BotPlutusInterface.PreBalance.tests
25+
, Spec.BotPlutusInterface.Server.tests
2426
]
Lines changed: 132 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,132 @@
1+
module Spec.BotPlutusInterface.Server (tests) where
2+
3+
import BotPlutusInterface.Server (app, initState)
4+
import BotPlutusInterface.Types (
5+
HasDefinitions (..),
6+
PABConfig (..),
7+
SomeBuiltin (..),
8+
)
9+
10+
import Playground.Types (FunctionSchema)
11+
import Schema (FormSchema)
12+
13+
import Test.Tasty (TestTree, testGroup)
14+
import Test.Tasty.HUnit (testCase, (@?=))
15+
16+
import Network.HTTP.Client (defaultManagerSettings, newManager)
17+
import Network.HTTP.Types.Status (status404)
18+
import Network.Wai.Handler.Warp (testWithApplication)
19+
import Servant.API (Capture, Get, JSON, (:>))
20+
import Servant.Client (ClientEnv, ClientError (..), client, mkClientEnv, responseStatusCode, runClientM)
21+
import Servant.Client.Core.BaseUrl (BaseUrl (..), parseBaseUrl)
22+
23+
import Data.Aeson (FromJSON, ToJSON)
24+
import Data.Default (def)
25+
import Data.Proxy (Proxy (..))
26+
import Data.Text (Text, pack, unpack)
27+
import Data.Void (Void, absurd)
28+
import System.FilePath ((</>))
29+
import System.IO.Temp (withSystemTempDirectory)
30+
import Prelude
31+
32+
type RawTxEndpointResponse = Either ClientError Text
33+
type RawTxTest a = (Text -> IO RawTxEndpointResponse) -> IO a
34+
35+
tests :: TestTree
36+
tests =
37+
testGroup
38+
"Server"
39+
[ rawTxTests
40+
]
41+
42+
rawTxTests :: TestTree
43+
rawTxTests =
44+
testGroup
45+
"rawTx"
46+
[ testCase "Can fetch valid tx file" fetchTx
47+
, testCase "If an extension is supplied, it is replaced by .raw" fetchSignedTx
48+
, testCase "Unable to fetch outside tx folder" fetchOutsideTxFolder
49+
, testCase "Returns 404 for valid request when the endpoint is disabled" fetchWithDefaultConfig
50+
]
51+
where
52+
fetchTx :: IO ()
53+
fetchTx = do
54+
initServerAndClient enableTxEndpointConfig $ \runRawTxClient -> do
55+
result <- runRawTxClient txHash
56+
result @?= Right (pack txFileContents)
57+
58+
fetchSignedTx :: IO ()
59+
fetchSignedTx = do
60+
initServerAndClient enableTxEndpointConfig $ \runRawTxClient -> do
61+
result <- runRawTxClient $ txHash <> ".signed"
62+
result @?= Right (pack txFileContents)
63+
64+
fetchOutsideTxFolder :: IO ()
65+
fetchOutsideTxFolder = do
66+
initServerAndClient enableTxEndpointConfig $ \runRawTxClient -> do
67+
Left (FailureResponse _ res) <- runRawTxClient "../somefile"
68+
responseStatusCode res @?= status404
69+
70+
fetchWithDefaultConfig :: IO ()
71+
fetchWithDefaultConfig = do
72+
initServerAndClient def $ \runRawTxClient -> do
73+
Left (FailureResponse _ res) <- runRawTxClient txHash
74+
responseStatusCode res @?= status404
75+
76+
-- Ideally we would reuse the API type definition from BotPlutusInterface.Server but servant-client
77+
-- can not generate a client for the websocket endpoint.
78+
txProxy ::
79+
Proxy
80+
( "rawTx"
81+
:> Capture "hash" Text
82+
:> Get '[JSON] Text
83+
)
84+
txProxy = Proxy
85+
86+
initServerAndClient :: PABConfig -> RawTxTest a -> IO a
87+
initServerAndClient config test = do
88+
withSystemTempDirectory "tx" $ \path -> do
89+
let pabConfig :: PABConfig
90+
pabConfig = config {pcTxFileDir = pack path}
91+
state <- initState
92+
writeFile (path </> txFileName) txFileContents
93+
testWithApplication (pure $ app @EmptyContract pabConfig state) (initClientOnPort test)
94+
where
95+
initClientOnPort :: RawTxTest a -> Int -> IO a
96+
initClientOnPort testToRun port = do
97+
baseUrl <- parseBaseUrl "http://localhost"
98+
manager <- newManager defaultManagerSettings
99+
100+
let clientEnv :: ClientEnv
101+
clientEnv = mkClientEnv manager $ baseUrl {baseUrlPort = port}
102+
103+
runRawTxClient :: Text -> IO RawTxEndpointResponse
104+
runRawTxClient hash = runClientM (client txProxy hash) clientEnv
105+
106+
testToRun runRawTxClient
107+
108+
txHash :: Text
109+
txHash = "aaaa"
110+
111+
txFileName :: FilePath
112+
txFileName = "tx-" <> unpack txHash <> ".raw"
113+
114+
txFileContents :: String
115+
txFileContents = "test"
116+
117+
enableTxEndpointConfig :: PABConfig
118+
enableTxEndpointConfig = def {pcEnableTxEndpoint = True}
119+
120+
-- Since we are not testing the contract endpoints we just use a newtype around Void as a Contract
121+
newtype EmptyContract = EmptyContract {unEmptyContract :: Void}
122+
deriving newtype (FromJSON, ToJSON)
123+
124+
instance HasDefinitions EmptyContract where
125+
getDefinitions :: [EmptyContract]
126+
getDefinitions = []
127+
128+
getSchema :: EmptyContract -> [FunctionSchema FormSchema]
129+
getSchema = absurd . unEmptyContract
130+
131+
getContract :: (EmptyContract -> SomeBuiltin)
132+
getContract = absurd . unEmptyContract

0 commit comments

Comments
 (0)