Skip to content

Commit aa0238f

Browse files
committed
Crudely disable API server history
1 parent a48146b commit aa0238f

File tree

2 files changed

+34
-38
lines changed

2 files changed

+34
-38
lines changed

hydra-node/src/Hydra/API/Server.hs

Lines changed: 15 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,7 @@ import Hydra.Prelude hiding (TVar, readTVar, seq)
77
import Cardano.Ledger.Core (PParams)
88
import Control.Concurrent.MVar (newEmptyMVar, putMVar, takeMVar)
99
import Control.Concurrent.STM.TChan (newBroadcastTChanIO, writeTChan)
10-
import Control.Concurrent.STM.TVar (modifyTVar', newTVarIO)
10+
import Control.Concurrent.STM.TVar (modifyTVar', newTVar, newTVarIO, readTVar)
1111
import Control.Exception (IOException)
1212
import Hydra.API.APIServerLog (APIServerLog (..))
1313
import Hydra.API.ClientInput (ClientInput)
@@ -79,17 +79,19 @@ withAPIServer ::
7979
withAPIServer config party persistence tracer chain pparams callback action =
8080
handle onIOException $ do
8181
responseChannel <- newBroadcastTChanIO
82+
-- Intialize our read models from stored events
83+
-- NOTE: we do not keep the stored events around in memory
8284
timedOutputEvents <- loadAll
83-
84-
-- Intialize our read model from stored events
8585
headStatusP <- mkProjection Idle (output <$> timedOutputEvents) projectHeadStatus
8686
snapshotUtxoP <- mkProjection Nothing (output <$> timedOutputEvents) projectSnapshotUtxo
8787
headIdP <- mkProjection Nothing (output <$> timedOutputEvents) projectInitializingHeadId
8888

89-
-- NOTE: we need to reverse the list because we store history in a reversed
90-
-- list in memory but in order on disk
91-
-- FIXME: always growing
92-
history <- newTVarIO (reverse timedOutputEvents)
89+
nextSeqVar <- newTVarIO 0
90+
let nextSeq = atomically $ do
91+
seq <- readTVar nextSeqVar
92+
modifyTVar' nextSeqVar (+ 1)
93+
pure seq
94+
9395
(notifyServerRunning, waitForServerRunning) <- setupServerNotification
9496

9597
let serverSettings =
@@ -106,15 +108,15 @@ withAPIServer config party persistence tracer chain pparams callback action =
106108
. simpleCors
107109
$ websocketsOr
108110
defaultConnectionOptions
109-
(wsApp party tracer history callback headStatusP snapshotUtxoP responseChannel)
111+
(wsApp party tracer nextSeq callback headStatusP snapshotUtxoP responseChannel)
110112
(httpApp tracer chain pparams (atomically $ getLatest headIdP) (atomically $ getLatest snapshotUtxoP) callback)
111113
)
112114
( do
113115
waitForServerRunning
114116
action $
115117
Server
116118
{ sendOutput = \output -> do
117-
timedOutput <- appendToHistory history output
119+
timedOutput <- persistOutput nextSeq output
118120
atomically $ do
119121
update headStatusP output
120122
update snapshotUtxoP output
@@ -125,7 +127,7 @@ withAPIServer config party persistence tracer chain pparams callback action =
125127
where
126128
APIServerConfig{host, port, tlsCertPath, tlsKeyPath} = config
127129

128-
PersistenceIncremental{loadAll, append} = persistence
130+
PersistenceIncremental{loadAll} = persistence
129131

130132
startServer settings app =
131133
case (tlsCertPath, tlsKeyPath) of
@@ -139,13 +141,11 @@ withAPIServer config party persistence tracer chain pparams callback action =
139141
_ ->
140142
runSettings settings app
141143

142-
appendToHistory history output = do
144+
persistOutput nextSeq output = do
143145
time <- getCurrentTime
144146
timedOutput <- atomically $ do
145-
seq <- nextSequenceNumber history
146-
let timedOutput = TimedServerOutput{output, time, seq}
147-
modifyTVar' history (timedOutput :)
148-
pure timedOutput
147+
seq <- nextSeq
148+
pure TimedServerOutput{output, time, seq}
149149
append timedOutput
150150
pure timedOutput
151151

hydra-node/src/Hydra/API/WSServer.hs

Lines changed: 19 additions & 23 deletions
Original file line numberDiff line numberDiff line change
@@ -49,7 +49,8 @@ wsApp ::
4949
IsChainState tx =>
5050
Party ->
5151
Tracer IO APIServerLog ->
52-
TVar [TimedServerOutput tx] ->
52+
-- | Get next sequence number.
53+
STM IO Natural ->
5354
(ClientInput tx -> IO ()) ->
5455
-- | Read model to enhance 'Greetings' messages with 'HeadStatus'.
5556
Projection STM.STM (ServerOutput tx) HeadStatus ->
@@ -58,18 +59,19 @@ wsApp ::
5859
TChan (TimedServerOutput tx) ->
5960
PendingConnection ->
6061
IO ()
61-
wsApp party tracer history callback headStatusP snapshotUtxoP responseChannel pending = do
62+
wsApp party tracer nextSeq callback headStatusP snapshotUtxoP responseChannel pending = do
6263
traceWith tracer NewAPIConnection
6364
let path = requestPath $ pendingRequest pending
6465
queryParams <- uriQuery <$> mkURIBs path
6566
con <- acceptRequest pending
6667
chan <- STM.atomically $ dupTChan responseChannel
6768

69+
-- FIXME: No support of history forwarding anymore (disabled because of memory growing too much)
6870
-- api client can decide if they want to see the past history of server outputs
69-
unless (shouldNotServeHistory queryParams) $
70-
forwardHistory con
71+
-- unless (shouldNotServeHistory queryParams) $
72+
-- forwardHistory con
7173

72-
forwardGreetingOnly con
74+
sendGreetings con
7375

7476
let outConfig = mkServerOutputConfig queryParams
7577

@@ -79,8 +81,8 @@ wsApp party tracer history callback headStatusP snapshotUtxoP responseChannel pe
7981
-- NOTE: We will add a 'Greetings' message on each API server start. This is
8082
-- important to make sure the latest configured 'party' is reaching the
8183
-- client.
82-
forwardGreetingOnly con = do
83-
seq <- atomically $ nextSequenceNumber history
84+
sendGreetings con = do
85+
seq <- atomically nextSeq
8486
headStatus <- atomically getLatestHeadStatus
8587
snapshotUtxo <- atomically getLatestSnapshotUtxo
8688
time <- getCurrentTime
@@ -114,11 +116,11 @@ wsApp party tracer history callback headStatusP snapshotUtxoP responseChannel pe
114116
queryP = QueryParam k v
115117
in if queryP `elem` qp then WithoutUTxO else WithUTxO
116118

117-
shouldNotServeHistory qp =
118-
flip any qp $ \case
119-
(QueryParam key val)
120-
| key == [queryKey|history|] -> val == [queryValue|no|]
121-
_other -> False
119+
-- shouldNotServeHistory qp =
120+
-- flip any qp $ \case
121+
-- (QueryParam key val)
122+
-- | key == [queryKey|history|] -> val == [queryValue|no|]
123+
-- _other -> False
122124

123125
sendOutputs chan con outConfig = forever $ do
124126
response <- STM.atomically $ readTChan chan
@@ -139,18 +141,12 @@ wsApp party tracer history callback headStatusP snapshotUtxoP responseChannel pe
139141
-- message to memory
140142
let clientInput = decodeUtf8With lenientDecode $ toStrict msg
141143
time <- getCurrentTime
142-
seq <- atomically $ nextSequenceNumber history
144+
seq <- atomically nextSeq
143145
let timedOutput = TimedServerOutput{output = InvalidInput @tx e clientInput, time, seq}
144146
sendTextData con $ Aeson.encode timedOutput
145147
traceWith tracer (APIInvalidInput e clientInput)
146148

147-
forwardHistory con = do
148-
hist <- STM.atomically (readTVar history)
149-
let encodeAndReverse xs serverOutput = Aeson.encode serverOutput : xs
150-
sendTextDatas con $ foldl' encodeAndReverse [] hist
151-
152-
nextSequenceNumber :: TVar [TimedServerOutput tx] -> STM.STM Natural
153-
nextSequenceNumber historyList =
154-
STM.readTVar historyList >>= \case
155-
[] -> pure 0
156-
(TimedServerOutput{seq} : _) -> pure (seq + 1)
149+
-- forwardHistory con = do
150+
-- hist <- STM.atomically (readTVar history)
151+
-- let encodeAndReverse xs serverOutput = Aeson.encode serverOutput : xs
152+
-- sendTextDatas con $ foldl' encodeAndReverse [] hist

0 commit comments

Comments
 (0)