2024-07-07 16:59:12 +00:00
|
|
|
{- P2P protocol over HTTP
|
|
|
|
-
|
|
|
|
- https://git-annex.branchable.com/design/p2p_protocol_over_http/
|
|
|
|
-
|
|
|
|
- Copyright 2024 Joey Hess <id@joeyh.name>
|
|
|
|
-
|
|
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
|
|
|
{-# LANGUAGE DataKinds #-}
|
|
|
|
{-# LANGUAGE TypeOperators #-}
|
2024-07-08 01:20:50 +00:00
|
|
|
{-# LANGUAGE TypeFamilies #-}
|
2024-07-07 16:59:12 +00:00
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
|
2024-07-09 01:11:01 +00:00
|
|
|
module P2P.Http (
|
|
|
|
module P2P.Http,
|
|
|
|
module P2P.Http.Types,
|
|
|
|
module P2P.Http.State,
|
|
|
|
) where
|
2024-07-07 16:59:12 +00:00
|
|
|
|
|
|
|
import Annex.Common
|
2024-07-09 01:11:01 +00:00
|
|
|
import P2P.Http.Types
|
|
|
|
import P2P.Http.State
|
2024-07-10 13:13:01 +00:00
|
|
|
import P2P.Protocol hiding (Offset, Bypass, auth)
|
2024-07-09 17:37:55 +00:00
|
|
|
import P2P.IO
|
2024-07-07 16:59:12 +00:00
|
|
|
|
|
|
|
import Servant
|
2024-07-07 20:08:05 +00:00
|
|
|
import Servant.Client.Streaming
|
2024-07-07 18:48:20 +00:00
|
|
|
import qualified Servant.Types.SourceT as S
|
2024-07-07 16:59:12 +00:00
|
|
|
import qualified Data.ByteString as B
|
convert lockcontent api to http long polling
Websockets would work, but the problem with using them for this is that
each lockcontent call is a separate websocket connection. And that's an
actual TCP connection. One TCP connection per file dropped would be too
expensive. With http long polling, regular http pipelining can be used,
so it will reuse a TCP connection.
Unfortunately, at least with servant, bi-directional streams with long
polling don't result in true bidirectional full duplex communication.
Servant processes the whole client body stream before generating the server
body stream. I think it's entirely possible to do full bi-directional
communication over http, but it would need changes to servant.
And, there's no way for the client to tell if the server successfully
locked the content, since the server will keep processing the client
stream no matter what.:
So, added a new api endpoint, keeplocked. lockcontent will lock the key
for 10 minutes with retention lock, and then a call to keeplocked will
keep it locked for as long as needed. This does mean that there will
need to be a Map of locks by key, and I will probably want to add
some kind of lock identifier that lockcontent returns.
2024-07-08 14:40:38 +00:00
|
|
|
import Control.Concurrent.STM
|
2024-07-07 16:59:12 +00:00
|
|
|
|
2024-07-07 18:48:20 +00:00
|
|
|
type P2PHttpAPI
|
2024-07-09 14:12:36 +00:00
|
|
|
= "git-annex" :> PV3 :> "key" :> CaptureKey :> GetAPI
|
|
|
|
:<|> "git-annex" :> PV2 :> "key" :> CaptureKey :> GetAPI
|
|
|
|
:<|> "git-annex" :> PV1 :> "key" :> CaptureKey :> GetAPI
|
|
|
|
:<|> "git-annex" :> PV0 :> "key" :> CaptureKey :> GetAPI
|
|
|
|
:<|> "git-annex" :> PV3 :> "checkpresent" :> CheckPresentAPI
|
|
|
|
:<|> "git-annex" :> PV2 :> "checkpresent" :> CheckPresentAPI
|
|
|
|
:<|> "git-annex" :> PV1 :> "checkpresent" :> CheckPresentAPI
|
|
|
|
:<|> "git-annex" :> PV0 :> "checkpresent" :> CheckPresentAPI
|
|
|
|
:<|> "git-annex" :> PV3 :> "remove" :> RemoveAPI RemoveResultPlus
|
|
|
|
:<|> "git-annex" :> PV2 :> "remove" :> RemoveAPI RemoveResultPlus
|
|
|
|
:<|> "git-annex" :> PV1 :> "remove" :> RemoveAPI RemoveResult
|
|
|
|
:<|> "git-annex" :> PV0 :> "remove" :> RemoveAPI RemoveResult
|
|
|
|
:<|> "git-annex" :> PV3 :> "remove-before" :> RemoveBeforeAPI
|
|
|
|
:<|> "git-annex" :> PV3 :> "gettimestamp" :> GetTimestampAPI
|
|
|
|
:<|> "git-annex" :> PV3 :> "put" :> DataLengthHeader
|
2024-07-07 16:59:12 +00:00
|
|
|
:> PutAPI PutResultPlus
|
2024-07-09 14:12:36 +00:00
|
|
|
:<|> "git-annex" :> PV2 :> "put" :> DataLengthHeader
|
2024-07-07 16:59:12 +00:00
|
|
|
:> PutAPI PutResultPlus
|
2024-07-09 14:12:36 +00:00
|
|
|
:<|> "git-annex" :> PV1 :> "put" :> DataLengthHeader
|
2024-07-07 16:59:12 +00:00
|
|
|
:> PutAPI PutResult
|
2024-07-09 14:12:36 +00:00
|
|
|
:<|> "git-annex" :> PV0 :> "put"
|
2024-07-07 16:59:12 +00:00
|
|
|
:> PutAPI PutResult
|
2024-07-09 14:12:36 +00:00
|
|
|
:<|> "git-annex" :> PV3 :> "putoffset"
|
2024-07-07 16:59:12 +00:00
|
|
|
:> PutOffsetAPI PutOffsetResultPlus
|
2024-07-09 14:12:36 +00:00
|
|
|
:<|> "git-annex" :> PV2 :> "putoffset"
|
2024-07-07 16:59:12 +00:00
|
|
|
:> PutOffsetAPI PutOffsetResultPlus
|
2024-07-09 14:12:36 +00:00
|
|
|
:<|> "git-annex" :> PV1 :> "putoffset"
|
2024-07-07 16:59:12 +00:00
|
|
|
:> PutOffsetAPI PutOffsetResult
|
2024-07-09 14:12:36 +00:00
|
|
|
:<|> "git-annex" :> PV3 :> "lockcontent" :> LockContentAPI
|
|
|
|
:<|> "git-annex" :> PV2 :> "lockcontent" :> LockContentAPI
|
|
|
|
:<|> "git-annex" :> PV1 :> "lockcontent" :> LockContentAPI
|
|
|
|
:<|> "git-annex" :> PV0 :> "lockcontent" :> LockContentAPI
|
|
|
|
:<|> "git-annex" :> PV3 :> "keeplocked" :> KeepLockedAPI
|
|
|
|
:<|> "git-annex" :> PV2 :> "keeplocked" :> KeepLockedAPI
|
|
|
|
:<|> "git-annex" :> PV1 :> "keeplocked" :> KeepLockedAPI
|
|
|
|
:<|> "git-annex" :> PV0 :> "keeplocked" :> KeepLockedAPI
|
2024-07-08 17:26:02 +00:00
|
|
|
:<|> "git-annex" :> "key" :> CaptureKey :> GetGenericAPI
|
2024-07-07 16:59:12 +00:00
|
|
|
|
2024-07-07 18:48:20 +00:00
|
|
|
p2pHttpAPI :: Proxy P2PHttpAPI
|
|
|
|
p2pHttpAPI = Proxy
|
|
|
|
|
2024-07-08 18:00:23 +00:00
|
|
|
p2pHttpApp :: P2PHttpServerState -> Application
|
|
|
|
p2pHttpApp = serve p2pHttpAPI . serveP2pHttp
|
|
|
|
|
|
|
|
serveP2pHttp :: P2PHttpServerState -> Server P2PHttpAPI
|
|
|
|
serveP2pHttp st
|
2024-07-08 18:20:30 +00:00
|
|
|
= serveGet st
|
2024-07-08 18:00:23 +00:00
|
|
|
:<|> serveGet st
|
|
|
|
:<|> serveGet st
|
|
|
|
:<|> serveGet st
|
|
|
|
:<|> serveCheckPresent st
|
|
|
|
:<|> serveCheckPresent st
|
|
|
|
:<|> serveCheckPresent st
|
|
|
|
:<|> serveCheckPresent st
|
|
|
|
:<|> serveRemove st id
|
|
|
|
:<|> serveRemove st id
|
|
|
|
:<|> serveRemove st dePlus
|
|
|
|
:<|> serveRemove st dePlus
|
|
|
|
:<|> serveRemoveBefore st
|
|
|
|
:<|> serveGetTimestamp st
|
|
|
|
:<|> servePut st id
|
|
|
|
:<|> servePut st id
|
|
|
|
:<|> servePut st dePlus
|
2024-07-09 14:12:36 +00:00
|
|
|
:<|> (\v -> servePut st dePlus v Nothing)
|
2024-07-08 18:00:23 +00:00
|
|
|
:<|> servePutOffset st id
|
|
|
|
:<|> servePutOffset st id
|
|
|
|
:<|> servePutOffset st dePlus
|
|
|
|
:<|> serveLockContent st
|
|
|
|
:<|> serveLockContent st
|
|
|
|
:<|> serveLockContent st
|
|
|
|
:<|> serveLockContent st
|
|
|
|
:<|> serveKeepLocked st
|
|
|
|
:<|> serveKeepLocked st
|
|
|
|
:<|> serveKeepLocked st
|
|
|
|
:<|> serveKeepLocked st
|
|
|
|
:<|> serveGetGeneric st
|
2024-07-08 17:26:02 +00:00
|
|
|
|
|
|
|
type GetGenericAPI = StreamGet NoFraming OctetStream (SourceIO B.ByteString)
|
2024-07-07 18:48:20 +00:00
|
|
|
|
2024-07-08 18:00:23 +00:00
|
|
|
serveGetGeneric :: P2PHttpServerState -> B64Key -> Handler (S.SourceT IO B.ByteString)
|
2024-07-08 17:26:02 +00:00
|
|
|
serveGetGeneric = undefined
|
|
|
|
|
|
|
|
type GetAPI
|
2024-07-07 18:48:20 +00:00
|
|
|
= ClientUUID Optional
|
|
|
|
:> ServerUUID Optional
|
|
|
|
:> BypassUUIDs
|
2024-07-07 16:59:12 +00:00
|
|
|
:> AssociatedFileParam
|
|
|
|
:> OffsetParam
|
2024-07-09 21:30:55 +00:00
|
|
|
:> AuthHeader
|
2024-07-07 16:59:12 +00:00
|
|
|
:> StreamGet NoFraming OctetStream
|
2024-07-08 17:26:02 +00:00
|
|
|
(Headers '[DataLengthHeader] (SourceIO B.ByteString))
|
2024-07-07 16:59:12 +00:00
|
|
|
|
2024-07-07 18:48:20 +00:00
|
|
|
serveGet
|
2024-07-09 14:12:36 +00:00
|
|
|
:: APIVersion v
|
|
|
|
=> P2PHttpServerState
|
|
|
|
-> v
|
2024-07-08 18:00:23 +00:00
|
|
|
-> B64Key
|
2024-07-07 18:48:20 +00:00
|
|
|
-> Maybe (B64UUID ClientSide)
|
|
|
|
-> Maybe (B64UUID ServerSide)
|
|
|
|
-> [B64UUID Bypass]
|
|
|
|
-> Maybe B64FilePath
|
|
|
|
-> Maybe Offset
|
2024-07-09 21:30:55 +00:00
|
|
|
-> Maybe Auth
|
2024-07-07 18:48:20 +00:00
|
|
|
-> Handler (Headers '[DataLengthHeader] (S.SourceT IO B.ByteString))
|
|
|
|
serveGet = undefined
|
|
|
|
|
2024-07-07 20:08:05 +00:00
|
|
|
clientGet
|
2024-07-09 17:37:55 +00:00
|
|
|
:: ProtocolVersion
|
2024-07-07 20:08:05 +00:00
|
|
|
-> B64Key
|
|
|
|
-> Maybe (B64UUID ClientSide)
|
|
|
|
-> Maybe (B64UUID ServerSide)
|
|
|
|
-> [B64UUID Bypass]
|
|
|
|
-> Maybe B64FilePath
|
|
|
|
-> Maybe Offset
|
2024-07-09 21:30:55 +00:00
|
|
|
-> Maybe Auth
|
2024-07-07 20:08:05 +00:00
|
|
|
-> ClientM (Headers '[DataLengthHeader] (S.SourceT IO B.ByteString))
|
2024-07-09 17:37:55 +00:00
|
|
|
clientGet (ProtocolVersion ver) = case ver of
|
2024-07-09 14:12:36 +00:00
|
|
|
3 -> v3 V3
|
|
|
|
2 -> v2 V2
|
|
|
|
1 -> v1 V1
|
|
|
|
0 -> v0 V0
|
2024-07-07 20:08:05 +00:00
|
|
|
_ -> error "unsupported protocol version"
|
|
|
|
where
|
2024-07-08 17:26:02 +00:00
|
|
|
v3 :<|> v2 :<|> v1 :<|> v0 :<|> _ = client p2pHttpAPI
|
2024-07-07 20:08:05 +00:00
|
|
|
|
2024-07-07 16:59:12 +00:00
|
|
|
type CheckPresentAPI
|
|
|
|
= KeyParam
|
2024-07-07 18:48:20 +00:00
|
|
|
:> ClientUUID Required
|
|
|
|
:> ServerUUID Required
|
|
|
|
:> BypassUUIDs
|
2024-07-10 03:44:40 +00:00
|
|
|
:> IsSecure
|
2024-07-10 00:52:56 +00:00
|
|
|
:> AuthHeader
|
2024-07-07 16:59:12 +00:00
|
|
|
:> Post '[JSON] CheckPresentResult
|
2024-07-07 18:48:20 +00:00
|
|
|
|
|
|
|
serveCheckPresent
|
2024-07-09 14:12:36 +00:00
|
|
|
:: APIVersion v
|
|
|
|
=> P2PHttpServerState
|
|
|
|
-> v
|
2024-07-08 18:00:23 +00:00
|
|
|
-> B64Key
|
2024-07-07 18:48:20 +00:00
|
|
|
-> B64UUID ClientSide
|
|
|
|
-> B64UUID ServerSide
|
|
|
|
-> [B64UUID Bypass]
|
2024-07-10 03:44:40 +00:00
|
|
|
-> IsSecure
|
2024-07-10 00:52:56 +00:00
|
|
|
-> Maybe Auth
|
2024-07-07 18:48:20 +00:00
|
|
|
-> Handler CheckPresentResult
|
2024-07-10 03:44:40 +00:00
|
|
|
serveCheckPresent st apiver (B64Key k) cu su bypass sec auth = do
|
|
|
|
res <- withP2PConnection apiver st cu su bypass sec auth ReadAction
|
2024-07-10 00:52:56 +00:00
|
|
|
$ \runst conn ->
|
|
|
|
liftIO $ runNetProto runst conn $ checkPresent k
|
2024-07-09 13:08:42 +00:00
|
|
|
case res of
|
2024-07-10 13:13:01 +00:00
|
|
|
Right b -> return (CheckPresentResult b)
|
|
|
|
Left err -> throwError $ err500 { errBody = encodeBL err }
|
2024-07-07 18:48:20 +00:00
|
|
|
|
2024-07-09 17:37:55 +00:00
|
|
|
clientCheckPresent
|
|
|
|
:: ClientEnv
|
|
|
|
-> ProtocolVersion
|
|
|
|
-> B64Key
|
|
|
|
-> B64UUID ClientSide
|
|
|
|
-> B64UUID ServerSide
|
|
|
|
-> [B64UUID Bypass]
|
2024-07-10 00:52:56 +00:00
|
|
|
-> Maybe Auth
|
2024-07-09 17:37:55 +00:00
|
|
|
-> IO Bool
|
2024-07-10 03:44:40 +00:00
|
|
|
clientCheckPresent clientenv (ProtocolVersion ver) key cu su bypass auth =
|
|
|
|
withClientM (cli key cu su bypass auth) clientenv $ \case
|
2024-07-09 17:37:55 +00:00
|
|
|
Left err -> throwM err
|
|
|
|
Right (CheckPresentResult res) -> return res
|
2024-07-10 03:44:40 +00:00
|
|
|
where
|
|
|
|
cli = case ver of
|
|
|
|
3 -> v3 V3
|
|
|
|
2 -> v2 V2
|
|
|
|
1 -> v1 V1
|
|
|
|
0 -> v0 V0
|
|
|
|
_ -> error "unsupported protocol version"
|
|
|
|
|
|
|
|
_ :<|> _ :<|> _ :<|> _ :<|>
|
|
|
|
v3 :<|> v2 :<|> v1 :<|> v0 :<|> _ = client p2pHttpAPI
|
2024-07-09 17:37:55 +00:00
|
|
|
|
2024-07-07 16:59:12 +00:00
|
|
|
type RemoveAPI result
|
|
|
|
= KeyParam
|
2024-07-07 18:48:20 +00:00
|
|
|
:> ClientUUID Required
|
|
|
|
:> ServerUUID Required
|
|
|
|
:> BypassUUIDs
|
2024-07-10 13:13:01 +00:00
|
|
|
:> IsSecure
|
2024-07-10 00:52:56 +00:00
|
|
|
:> AuthHeader
|
2024-07-07 16:59:12 +00:00
|
|
|
:> Post '[JSON] result
|
2024-07-07 18:48:20 +00:00
|
|
|
|
|
|
|
serveRemove
|
2024-07-09 14:12:36 +00:00
|
|
|
:: APIVersion v
|
|
|
|
=> P2PHttpServerState
|
2024-07-08 18:00:23 +00:00
|
|
|
-> (RemoveResultPlus -> t)
|
2024-07-09 14:12:36 +00:00
|
|
|
-> v
|
2024-07-07 18:48:20 +00:00
|
|
|
-> B64Key
|
|
|
|
-> B64UUID ClientSide
|
|
|
|
-> B64UUID ServerSide
|
|
|
|
-> [B64UUID Bypass]
|
2024-07-10 13:13:01 +00:00
|
|
|
-> IsSecure
|
2024-07-10 00:52:56 +00:00
|
|
|
-> Maybe Auth
|
2024-07-07 18:48:20 +00:00
|
|
|
-> Handler t
|
2024-07-10 13:13:01 +00:00
|
|
|
serveRemove st resultmangle apiver (B64Key k) cu su bypass sec auth = do
|
|
|
|
res <- withP2PConnection apiver st cu su bypass sec auth RemoveAction
|
|
|
|
$ \runst conn ->
|
|
|
|
liftIO $ runNetProto runst conn $ remove Nothing k
|
|
|
|
case res of
|
|
|
|
(Right b, plus) -> return $ resultmangle $
|
|
|
|
RemoveResultPlus b (map B64UUID (fromMaybe [] plus))
|
|
|
|
(Left err, _) -> throwError $
|
|
|
|
err500 { errBody = encodeBL err }
|
2024-07-07 20:08:05 +00:00
|
|
|
|
|
|
|
clientRemove
|
2024-07-10 13:19:58 +00:00
|
|
|
:: ClientEnv
|
|
|
|
-> ProtocolVersion
|
2024-07-07 20:08:05 +00:00
|
|
|
-> B64Key
|
|
|
|
-> B64UUID ClientSide
|
|
|
|
-> B64UUID ServerSide
|
|
|
|
-> [B64UUID Bypass]
|
2024-07-10 00:52:56 +00:00
|
|
|
-> Maybe Auth
|
2024-07-10 13:19:58 +00:00
|
|
|
-> IO RemoveResultPlus
|
|
|
|
clientRemove clientenv (ProtocolVersion ver) key cu su bypass auth =
|
|
|
|
withClientM cli clientenv $ \case
|
|
|
|
Left err -> throwM err
|
|
|
|
Right res -> return res
|
2024-07-07 20:08:05 +00:00
|
|
|
where
|
2024-07-10 13:19:58 +00:00
|
|
|
cli = case ver of
|
|
|
|
3 -> v3 V3 key cu su bypass auth
|
|
|
|
2 -> v2 V2 key cu su bypass auth
|
|
|
|
1 -> plus <$> v1 V1 key cu su bypass auth
|
|
|
|
0 -> plus <$> v0 V0 key cu su bypass auth
|
|
|
|
_ -> error "unsupported protocol version"
|
|
|
|
|
2024-07-07 20:08:05 +00:00
|
|
|
_ :<|> _ :<|> _ :<|> _ :<|>
|
|
|
|
_ :<|> _ :<|> _ :<|> _ :<|>
|
|
|
|
v3 :<|> v2 :<|> v1 :<|> v0 :<|> _ = client p2pHttpAPI
|
2024-07-10 13:13:01 +00:00
|
|
|
|
2024-07-07 16:59:12 +00:00
|
|
|
type RemoveBeforeAPI
|
|
|
|
= KeyParam
|
2024-07-07 18:48:20 +00:00
|
|
|
:> ClientUUID Required
|
|
|
|
:> ServerUUID Required
|
|
|
|
:> BypassUUIDs
|
|
|
|
:> QueryParam' '[Required] "timestamp" Timestamp
|
2024-07-07 16:59:12 +00:00
|
|
|
:> Post '[JSON] RemoveResult
|
2024-07-07 18:48:20 +00:00
|
|
|
|
|
|
|
serveRemoveBefore
|
2024-07-09 14:12:36 +00:00
|
|
|
:: APIVersion v
|
|
|
|
=> P2PHttpServerState
|
|
|
|
-> v
|
2024-07-08 18:00:23 +00:00
|
|
|
-> B64Key
|
2024-07-07 18:48:20 +00:00
|
|
|
-> B64UUID ClientSide
|
|
|
|
-> B64UUID ServerSide
|
|
|
|
-> [B64UUID Bypass]
|
|
|
|
-> Timestamp
|
|
|
|
-> Handler RemoveResult
|
|
|
|
serveRemoveBefore = undefined
|
|
|
|
|
2024-07-07 20:08:05 +00:00
|
|
|
clientRemoveBefore
|
2024-07-09 17:37:55 +00:00
|
|
|
:: ProtocolVersion
|
2024-07-07 20:08:05 +00:00
|
|
|
-> B64Key
|
|
|
|
-> B64UUID ClientSide
|
|
|
|
-> B64UUID ServerSide
|
|
|
|
-> [B64UUID Bypass]
|
|
|
|
-> Timestamp
|
|
|
|
-> ClientM RemoveResult
|
2024-07-09 17:37:55 +00:00
|
|
|
clientRemoveBefore (ProtocolVersion ver) = case ver of
|
2024-07-09 14:12:36 +00:00
|
|
|
3 -> v3 V3
|
2024-07-07 20:08:05 +00:00
|
|
|
_ -> error "unsupported protocol version"
|
|
|
|
where
|
|
|
|
_ :<|> _ :<|> _ :<|> _ :<|>
|
|
|
|
_ :<|> _ :<|> _ :<|> _ :<|>
|
|
|
|
_ :<|> _ :<|> _ :<|> _ :<|>
|
|
|
|
v3 :<|> _ = client p2pHttpAPI
|
|
|
|
|
|
|
|
|
2024-07-07 16:59:12 +00:00
|
|
|
type GetTimestampAPI
|
2024-07-07 18:48:20 +00:00
|
|
|
= ClientUUID Required
|
|
|
|
:> ServerUUID Required
|
|
|
|
:> BypassUUIDs
|
2024-07-07 16:59:12 +00:00
|
|
|
:> Post '[JSON] GetTimestampResult
|
2024-07-07 18:48:20 +00:00
|
|
|
|
|
|
|
serveGetTimestamp
|
2024-07-09 14:12:36 +00:00
|
|
|
:: APIVersion v
|
|
|
|
=> P2PHttpServerState
|
|
|
|
-> v
|
2024-07-08 18:00:23 +00:00
|
|
|
-> B64UUID ClientSide
|
2024-07-07 18:48:20 +00:00
|
|
|
-> B64UUID ServerSide
|
|
|
|
-> [B64UUID Bypass]
|
|
|
|
-> Handler GetTimestampResult
|
|
|
|
serveGetTimestamp = undefined
|
|
|
|
|
2024-07-07 20:08:05 +00:00
|
|
|
clientGetTimestamp
|
2024-07-09 17:37:55 +00:00
|
|
|
:: ProtocolVersion
|
2024-07-07 20:08:05 +00:00
|
|
|
-> B64UUID ClientSide
|
|
|
|
-> B64UUID ServerSide
|
|
|
|
-> [B64UUID Bypass]
|
|
|
|
-> ClientM GetTimestampResult
|
2024-07-09 17:37:55 +00:00
|
|
|
clientGetTimestamp (ProtocolVersion ver) = case ver of
|
2024-07-09 14:12:36 +00:00
|
|
|
3 -> v3 V3
|
2024-07-07 20:08:05 +00:00
|
|
|
_ -> error "unsupported protocol version"
|
|
|
|
where
|
|
|
|
_ :<|> _ :<|> _ :<|> _ :<|>
|
|
|
|
_ :<|> _ :<|> _ :<|> _ :<|>
|
|
|
|
_ :<|> _ :<|> _ :<|> _ :<|>
|
|
|
|
_ :<|>
|
|
|
|
v3 :<|> _ = client p2pHttpAPI
|
|
|
|
|
2024-07-07 16:59:12 +00:00
|
|
|
type PutAPI result
|
|
|
|
= KeyParam
|
2024-07-07 18:48:20 +00:00
|
|
|
:> ClientUUID Required
|
|
|
|
:> ServerUUID Required
|
|
|
|
:> BypassUUIDs
|
2024-07-07 16:59:12 +00:00
|
|
|
:> AssociatedFileParam
|
|
|
|
:> OffsetParam
|
|
|
|
:> Header' '[Required] "X-git-annex-data-length" DataLength
|
|
|
|
:> StreamBody NoFraming OctetStream (SourceIO B.ByteString)
|
|
|
|
:> Post '[JSON] result
|
|
|
|
|
2024-07-07 18:48:20 +00:00
|
|
|
servePut
|
2024-07-09 14:12:36 +00:00
|
|
|
:: APIVersion v
|
|
|
|
=> P2PHttpServerState
|
2024-07-08 18:00:23 +00:00
|
|
|
-> (PutResultPlus -> t)
|
2024-07-09 14:12:36 +00:00
|
|
|
-> v
|
2024-07-07 18:48:20 +00:00
|
|
|
-> Maybe Integer
|
|
|
|
-> B64Key
|
|
|
|
-> B64UUID ClientSide
|
|
|
|
-> B64UUID ServerSide
|
|
|
|
-> [B64UUID Bypass]
|
|
|
|
-> Maybe B64FilePath
|
|
|
|
-> Maybe Offset
|
|
|
|
-> DataLength
|
|
|
|
-> S.SourceT IO B.ByteString
|
|
|
|
-> Handler t
|
|
|
|
servePut = undefined
|
|
|
|
|
2024-07-07 20:08:05 +00:00
|
|
|
clientPut
|
2024-07-09 17:37:55 +00:00
|
|
|
:: ProtocolVersion
|
2024-07-07 20:08:05 +00:00
|
|
|
-> Maybe Integer
|
|
|
|
-> B64Key
|
2024-07-07 18:48:20 +00:00
|
|
|
-> B64UUID ClientSide
|
|
|
|
-> B64UUID ServerSide
|
|
|
|
-> [B64UUID Bypass]
|
|
|
|
-> Maybe B64FilePath
|
|
|
|
-> Maybe Offset
|
|
|
|
-> DataLength
|
|
|
|
-> S.SourceT IO B.ByteString
|
2024-07-07 20:08:05 +00:00
|
|
|
-> ClientM PutResultPlus
|
2024-07-09 17:37:55 +00:00
|
|
|
clientPut (ProtocolVersion ver) sz k cu su bypass af o l src = case ver of
|
2024-07-09 14:12:36 +00:00
|
|
|
3 -> v3 V3 sz k cu su bypass af o l src
|
|
|
|
2 -> v2 V2 sz k cu su bypass af o l src
|
|
|
|
1 -> plus <$> v1 V1 sz k cu su bypass af o l src
|
|
|
|
0 -> plus <$> v0 V0 k cu su bypass af o l src
|
2024-07-07 20:08:05 +00:00
|
|
|
_ -> error "unsupported protocol version"
|
|
|
|
where
|
|
|
|
_ :<|> _ :<|> _ :<|> _ :<|>
|
|
|
|
_ :<|> _ :<|> _ :<|> _ :<|>
|
|
|
|
_ :<|> _ :<|> _ :<|> _ :<|>
|
|
|
|
_ :<|>
|
|
|
|
_ :<|>
|
|
|
|
v3 :<|> v2 :<|> v1 :<|> v0 :<|> _ = client p2pHttpAPI
|
2024-07-07 18:48:20 +00:00
|
|
|
|
2024-07-07 16:59:12 +00:00
|
|
|
type PutOffsetAPI result
|
|
|
|
= KeyParam
|
2024-07-07 18:48:20 +00:00
|
|
|
:> ClientUUID Required
|
|
|
|
:> ServerUUID Required
|
|
|
|
:> BypassUUIDs
|
2024-07-07 16:59:12 +00:00
|
|
|
:> Post '[JSON] result
|
|
|
|
|
2024-07-07 18:48:20 +00:00
|
|
|
servePutOffset
|
2024-07-09 14:12:36 +00:00
|
|
|
:: APIVersion v
|
|
|
|
=> P2PHttpServerState
|
2024-07-08 18:00:23 +00:00
|
|
|
-> (PutOffsetResultPlus -> t)
|
2024-07-09 14:12:36 +00:00
|
|
|
-> v
|
2024-07-07 18:48:20 +00:00
|
|
|
-> B64Key
|
|
|
|
-> B64UUID ClientSide
|
|
|
|
-> B64UUID ServerSide
|
|
|
|
-> [B64UUID Bypass]
|
|
|
|
-> Handler t
|
|
|
|
servePutOffset = undefined
|
|
|
|
|
2024-07-07 20:08:05 +00:00
|
|
|
clientPutOffset
|
2024-07-09 17:37:55 +00:00
|
|
|
:: ProtocolVersion
|
2024-07-07 20:08:05 +00:00
|
|
|
-> B64Key
|
|
|
|
-> B64UUID ClientSide
|
|
|
|
-> B64UUID ServerSide
|
|
|
|
-> [B64UUID Bypass]
|
|
|
|
-> ClientM PutOffsetResultPlus
|
2024-07-09 17:37:55 +00:00
|
|
|
clientPutOffset (ProtocolVersion ver) = case ver of
|
2024-07-09 14:12:36 +00:00
|
|
|
3 -> v3 V3
|
|
|
|
2 -> v2 V2
|
2024-07-07 20:08:05 +00:00
|
|
|
_ -> error "unsupported protocol version"
|
|
|
|
where
|
|
|
|
_ :<|> _ :<|> _ :<|> _ :<|>
|
|
|
|
_ :<|> _ :<|> _ :<|> _ :<|>
|
|
|
|
_ :<|> _ :<|> _ :<|> _ :<|>
|
|
|
|
_ :<|>
|
|
|
|
_ :<|>
|
|
|
|
_ :<|> _ :<|> _ :<|> _ :<|>
|
|
|
|
v3 :<|> v2 :<|> _ = client p2pHttpAPI
|
|
|
|
|
2024-07-08 01:20:50 +00:00
|
|
|
type LockContentAPI
|
|
|
|
= KeyParam
|
|
|
|
:> ClientUUID Required
|
|
|
|
:> ServerUUID Required
|
|
|
|
:> BypassUUIDs
|
convert lockcontent api to http long polling
Websockets would work, but the problem with using them for this is that
each lockcontent call is a separate websocket connection. And that's an
actual TCP connection. One TCP connection per file dropped would be too
expensive. With http long polling, regular http pipelining can be used,
so it will reuse a TCP connection.
Unfortunately, at least with servant, bi-directional streams with long
polling don't result in true bidirectional full duplex communication.
Servant processes the whole client body stream before generating the server
body stream. I think it's entirely possible to do full bi-directional
communication over http, but it would need changes to servant.
And, there's no way for the client to tell if the server successfully
locked the content, since the server will keep processing the client
stream no matter what.:
So, added a new api endpoint, keeplocked. lockcontent will lock the key
for 10 minutes with retention lock, and then a call to keeplocked will
keep it locked for as long as needed. This does mean that there will
need to be a Map of locks by key, and I will probably want to add
some kind of lock identifier that lockcontent returns.
2024-07-08 14:40:38 +00:00
|
|
|
:> Post '[JSON] LockResult
|
2024-07-07 20:08:05 +00:00
|
|
|
|
2024-07-08 01:20:50 +00:00
|
|
|
serveLockContent
|
2024-07-09 14:12:36 +00:00
|
|
|
:: APIVersion v
|
|
|
|
=> P2PHttpServerState
|
|
|
|
-> v
|
2024-07-08 18:00:23 +00:00
|
|
|
-> B64Key
|
2024-07-08 01:20:50 +00:00
|
|
|
-> B64UUID ClientSide
|
|
|
|
-> B64UUID ServerSide
|
|
|
|
-> [B64UUID Bypass]
|
convert lockcontent api to http long polling
Websockets would work, but the problem with using them for this is that
each lockcontent call is a separate websocket connection. And that's an
actual TCP connection. One TCP connection per file dropped would be too
expensive. With http long polling, regular http pipelining can be used,
so it will reuse a TCP connection.
Unfortunately, at least with servant, bi-directional streams with long
polling don't result in true bidirectional full duplex communication.
Servant processes the whole client body stream before generating the server
body stream. I think it's entirely possible to do full bi-directional
communication over http, but it would need changes to servant.
And, there's no way for the client to tell if the server successfully
locked the content, since the server will keep processing the client
stream no matter what.:
So, added a new api endpoint, keeplocked. lockcontent will lock the key
for 10 minutes with retention lock, and then a call to keeplocked will
keep it locked for as long as needed. This does mean that there will
need to be a Map of locks by key, and I will probably want to add
some kind of lock identifier that lockcontent returns.
2024-07-08 14:40:38 +00:00
|
|
|
-> Handler LockResult
|
2024-07-08 01:20:50 +00:00
|
|
|
serveLockContent = undefined
|
2024-07-07 18:48:20 +00:00
|
|
|
|
convert lockcontent api to http long polling
Websockets would work, but the problem with using them for this is that
each lockcontent call is a separate websocket connection. And that's an
actual TCP connection. One TCP connection per file dropped would be too
expensive. With http long polling, regular http pipelining can be used,
so it will reuse a TCP connection.
Unfortunately, at least with servant, bi-directional streams with long
polling don't result in true bidirectional full duplex communication.
Servant processes the whole client body stream before generating the server
body stream. I think it's entirely possible to do full bi-directional
communication over http, but it would need changes to servant.
And, there's no way for the client to tell if the server successfully
locked the content, since the server will keep processing the client
stream no matter what.:
So, added a new api endpoint, keeplocked. lockcontent will lock the key
for 10 minutes with retention lock, and then a call to keeplocked will
keep it locked for as long as needed. This does mean that there will
need to be a Map of locks by key, and I will probably want to add
some kind of lock identifier that lockcontent returns.
2024-07-08 14:40:38 +00:00
|
|
|
clientLockContent
|
2024-07-09 17:37:55 +00:00
|
|
|
:: ProtocolVersion
|
convert lockcontent api to http long polling
Websockets would work, but the problem with using them for this is that
each lockcontent call is a separate websocket connection. And that's an
actual TCP connection. One TCP connection per file dropped would be too
expensive. With http long polling, regular http pipelining can be used,
so it will reuse a TCP connection.
Unfortunately, at least with servant, bi-directional streams with long
polling don't result in true bidirectional full duplex communication.
Servant processes the whole client body stream before generating the server
body stream. I think it's entirely possible to do full bi-directional
communication over http, but it would need changes to servant.
And, there's no way for the client to tell if the server successfully
locked the content, since the server will keep processing the client
stream no matter what.:
So, added a new api endpoint, keeplocked. lockcontent will lock the key
for 10 minutes with retention lock, and then a call to keeplocked will
keep it locked for as long as needed. This does mean that there will
need to be a Map of locks by key, and I will probably want to add
some kind of lock identifier that lockcontent returns.
2024-07-08 14:40:38 +00:00
|
|
|
-> B64Key
|
|
|
|
-> B64UUID ClientSide
|
|
|
|
-> B64UUID ServerSide
|
|
|
|
-> [B64UUID Bypass]
|
|
|
|
-> ClientM LockResult
|
2024-07-09 17:37:55 +00:00
|
|
|
clientLockContent (ProtocolVersion ver) = case ver of
|
2024-07-09 14:12:36 +00:00
|
|
|
3 -> v3 V3
|
|
|
|
2 -> v2 V2
|
|
|
|
1 -> v1 V1
|
|
|
|
0 -> v0 V0
|
convert lockcontent api to http long polling
Websockets would work, but the problem with using them for this is that
each lockcontent call is a separate websocket connection. And that's an
actual TCP connection. One TCP connection per file dropped would be too
expensive. With http long polling, regular http pipelining can be used,
so it will reuse a TCP connection.
Unfortunately, at least with servant, bi-directional streams with long
polling don't result in true bidirectional full duplex communication.
Servant processes the whole client body stream before generating the server
body stream. I think it's entirely possible to do full bi-directional
communication over http, but it would need changes to servant.
And, there's no way for the client to tell if the server successfully
locked the content, since the server will keep processing the client
stream no matter what.:
So, added a new api endpoint, keeplocked. lockcontent will lock the key
for 10 minutes with retention lock, and then a call to keeplocked will
keep it locked for as long as needed. This does mean that there will
need to be a Map of locks by key, and I will probably want to add
some kind of lock identifier that lockcontent returns.
2024-07-08 14:40:38 +00:00
|
|
|
_ -> error "unsupported protocol version"
|
|
|
|
where
|
|
|
|
_ :<|> _ :<|> _ :<|> _ :<|>
|
|
|
|
_ :<|> _ :<|> _ :<|> _ :<|>
|
|
|
|
_ :<|> _ :<|> _ :<|> _ :<|>
|
|
|
|
_ :<|>
|
|
|
|
_ :<|>
|
|
|
|
_ :<|> _ :<|> _ :<|> _ :<|>
|
|
|
|
_ :<|> _ :<|> _ :<|>
|
|
|
|
v3 :<|> v2 :<|> v1 :<|> v0 :<|> _ = client p2pHttpAPI
|
2024-07-07 18:48:20 +00:00
|
|
|
|
convert lockcontent api to http long polling
Websockets would work, but the problem with using them for this is that
each lockcontent call is a separate websocket connection. And that's an
actual TCP connection. One TCP connection per file dropped would be too
expensive. With http long polling, regular http pipelining can be used,
so it will reuse a TCP connection.
Unfortunately, at least with servant, bi-directional streams with long
polling don't result in true bidirectional full duplex communication.
Servant processes the whole client body stream before generating the server
body stream. I think it's entirely possible to do full bi-directional
communication over http, but it would need changes to servant.
And, there's no way for the client to tell if the server successfully
locked the content, since the server will keep processing the client
stream no matter what.:
So, added a new api endpoint, keeplocked. lockcontent will lock the key
for 10 minutes with retention lock, and then a call to keeplocked will
keep it locked for as long as needed. This does mean that there will
need to be a Map of locks by key, and I will probably want to add
some kind of lock identifier that lockcontent returns.
2024-07-08 14:40:38 +00:00
|
|
|
type KeepLockedAPI
|
2024-07-09 00:18:55 +00:00
|
|
|
= LockIDParam
|
convert lockcontent api to http long polling
Websockets would work, but the problem with using them for this is that
each lockcontent call is a separate websocket connection. And that's an
actual TCP connection. One TCP connection per file dropped would be too
expensive. With http long polling, regular http pipelining can be used,
so it will reuse a TCP connection.
Unfortunately, at least with servant, bi-directional streams with long
polling don't result in true bidirectional full duplex communication.
Servant processes the whole client body stream before generating the server
body stream. I think it's entirely possible to do full bi-directional
communication over http, but it would need changes to servant.
And, there's no way for the client to tell if the server successfully
locked the content, since the server will keep processing the client
stream no matter what.:
So, added a new api endpoint, keeplocked. lockcontent will lock the key
for 10 minutes with retention lock, and then a call to keeplocked will
keep it locked for as long as needed. This does mean that there will
need to be a Map of locks by key, and I will probably want to add
some kind of lock identifier that lockcontent returns.
2024-07-08 14:40:38 +00:00
|
|
|
:> ClientUUID Required
|
|
|
|
:> ServerUUID Required
|
|
|
|
:> BypassUUIDs
|
|
|
|
:> Header "Connection" ConnectionKeepAlive
|
|
|
|
:> Header "Keep-Alive" KeepAlive
|
|
|
|
:> StreamBody NewlineFraming JSON (SourceIO UnlockRequest)
|
|
|
|
:> Post '[JSON] LockResult
|
2024-07-07 18:48:20 +00:00
|
|
|
|
convert lockcontent api to http long polling
Websockets would work, but the problem with using them for this is that
each lockcontent call is a separate websocket connection. And that's an
actual TCP connection. One TCP connection per file dropped would be too
expensive. With http long polling, regular http pipelining can be used,
so it will reuse a TCP connection.
Unfortunately, at least with servant, bi-directional streams with long
polling don't result in true bidirectional full duplex communication.
Servant processes the whole client body stream before generating the server
body stream. I think it's entirely possible to do full bi-directional
communication over http, but it would need changes to servant.
And, there's no way for the client to tell if the server successfully
locked the content, since the server will keep processing the client
stream no matter what.:
So, added a new api endpoint, keeplocked. lockcontent will lock the key
for 10 minutes with retention lock, and then a call to keeplocked will
keep it locked for as long as needed. This does mean that there will
need to be a Map of locks by key, and I will probably want to add
some kind of lock identifier that lockcontent returns.
2024-07-08 14:40:38 +00:00
|
|
|
serveKeepLocked
|
2024-07-09 14:12:36 +00:00
|
|
|
:: APIVersion v
|
|
|
|
=> P2PHttpServerState
|
|
|
|
-> v
|
2024-07-09 00:18:55 +00:00
|
|
|
-> LockID
|
2024-07-08 01:20:50 +00:00
|
|
|
-> B64UUID ClientSide
|
|
|
|
-> B64UUID ServerSide
|
|
|
|
-> [B64UUID Bypass]
|
convert lockcontent api to http long polling
Websockets would work, but the problem with using them for this is that
each lockcontent call is a separate websocket connection. And that's an
actual TCP connection. One TCP connection per file dropped would be too
expensive. With http long polling, regular http pipelining can be used,
so it will reuse a TCP connection.
Unfortunately, at least with servant, bi-directional streams with long
polling don't result in true bidirectional full duplex communication.
Servant processes the whole client body stream before generating the server
body stream. I think it's entirely possible to do full bi-directional
communication over http, but it would need changes to servant.
And, there's no way for the client to tell if the server successfully
locked the content, since the server will keep processing the client
stream no matter what.:
So, added a new api endpoint, keeplocked. lockcontent will lock the key
for 10 minutes with retention lock, and then a call to keeplocked will
keep it locked for as long as needed. This does mean that there will
need to be a Map of locks by key, and I will probably want to add
some kind of lock identifier that lockcontent returns.
2024-07-08 14:40:38 +00:00
|
|
|
-> Maybe ConnectionKeepAlive
|
|
|
|
-> Maybe KeepAlive
|
|
|
|
-> S.SourceT IO UnlockRequest
|
|
|
|
-> Handler LockResult
|
2024-07-09 14:12:36 +00:00
|
|
|
serveKeepLocked st apiver lckid cu su _ _ _ unlockrequeststream = do
|
convert lockcontent api to http long polling
Websockets would work, but the problem with using them for this is that
each lockcontent call is a separate websocket connection. And that's an
actual TCP connection. One TCP connection per file dropped would be too
expensive. With http long polling, regular http pipelining can be used,
so it will reuse a TCP connection.
Unfortunately, at least with servant, bi-directional streams with long
polling don't result in true bidirectional full duplex communication.
Servant processes the whole client body stream before generating the server
body stream. I think it's entirely possible to do full bi-directional
communication over http, but it would need changes to servant.
And, there's no way for the client to tell if the server successfully
locked the content, since the server will keep processing the client
stream no matter what.:
So, added a new api endpoint, keeplocked. lockcontent will lock the key
for 10 minutes with retention lock, and then a call to keeplocked will
keep it locked for as long as needed. This does mean that there will
need to be a Map of locks by key, and I will probably want to add
some kind of lock identifier that lockcontent returns.
2024-07-08 14:40:38 +00:00
|
|
|
_ <- liftIO $ S.unSourceT unlockrequeststream go
|
2024-07-09 00:18:55 +00:00
|
|
|
return (LockResult False Nothing)
|
convert lockcontent api to http long polling
Websockets would work, but the problem with using them for this is that
each lockcontent call is a separate websocket connection. And that's an
actual TCP connection. One TCP connection per file dropped would be too
expensive. With http long polling, regular http pipelining can be used,
so it will reuse a TCP connection.
Unfortunately, at least with servant, bi-directional streams with long
polling don't result in true bidirectional full duplex communication.
Servant processes the whole client body stream before generating the server
body stream. I think it's entirely possible to do full bi-directional
communication over http, but it would need changes to servant.
And, there's no way for the client to tell if the server successfully
locked the content, since the server will keep processing the client
stream no matter what.:
So, added a new api endpoint, keeplocked. lockcontent will lock the key
for 10 minutes with retention lock, and then a call to keeplocked will
keep it locked for as long as needed. This does mean that there will
need to be a Map of locks by key, and I will probably want to add
some kind of lock identifier that lockcontent returns.
2024-07-08 14:40:38 +00:00
|
|
|
where
|
2024-07-08 18:20:30 +00:00
|
|
|
go S.Stop = dropLock lckid st
|
|
|
|
go (S.Error _err) = dropLock lckid st
|
convert lockcontent api to http long polling
Websockets would work, but the problem with using them for this is that
each lockcontent call is a separate websocket connection. And that's an
actual TCP connection. One TCP connection per file dropped would be too
expensive. With http long polling, regular http pipelining can be used,
so it will reuse a TCP connection.
Unfortunately, at least with servant, bi-directional streams with long
polling don't result in true bidirectional full duplex communication.
Servant processes the whole client body stream before generating the server
body stream. I think it's entirely possible to do full bi-directional
communication over http, but it would need changes to servant.
And, there's no way for the client to tell if the server successfully
locked the content, since the server will keep processing the client
stream no matter what.:
So, added a new api endpoint, keeplocked. lockcontent will lock the key
for 10 minutes with retention lock, and then a call to keeplocked will
keep it locked for as long as needed. This does mean that there will
need to be a Map of locks by key, and I will probably want to add
some kind of lock identifier that lockcontent returns.
2024-07-08 14:40:38 +00:00
|
|
|
go (S.Skip s) = go s
|
|
|
|
go (S.Effect ms) = ms >>= go
|
|
|
|
go (S.Yield (UnlockRequest False) s) = go s
|
2024-07-08 18:20:30 +00:00
|
|
|
go (S.Yield (UnlockRequest True) _) = dropLock lckid st
|
|
|
|
|
2024-07-09 17:37:55 +00:00
|
|
|
clientKeepLocked'
|
|
|
|
:: ProtocolVersion
|
2024-07-09 00:18:55 +00:00
|
|
|
-> LockID
|
convert lockcontent api to http long polling
Websockets would work, but the problem with using them for this is that
each lockcontent call is a separate websocket connection. And that's an
actual TCP connection. One TCP connection per file dropped would be too
expensive. With http long polling, regular http pipelining can be used,
so it will reuse a TCP connection.
Unfortunately, at least with servant, bi-directional streams with long
polling don't result in true bidirectional full duplex communication.
Servant processes the whole client body stream before generating the server
body stream. I think it's entirely possible to do full bi-directional
communication over http, but it would need changes to servant.
And, there's no way for the client to tell if the server successfully
locked the content, since the server will keep processing the client
stream no matter what.:
So, added a new api endpoint, keeplocked. lockcontent will lock the key
for 10 minutes with retention lock, and then a call to keeplocked will
keep it locked for as long as needed. This does mean that there will
need to be a Map of locks by key, and I will probably want to add
some kind of lock identifier that lockcontent returns.
2024-07-08 14:40:38 +00:00
|
|
|
-> B64UUID ClientSide
|
|
|
|
-> B64UUID ServerSide
|
|
|
|
-> [B64UUID Bypass]
|
|
|
|
-> Maybe ConnectionKeepAlive
|
|
|
|
-> Maybe KeepAlive
|
|
|
|
-> S.SourceT IO UnlockRequest
|
|
|
|
-> ClientM LockResult
|
2024-07-09 17:37:55 +00:00
|
|
|
clientKeepLocked' (ProtocolVersion ver) = case ver of
|
2024-07-09 14:12:36 +00:00
|
|
|
3 -> v3 V3
|
|
|
|
2 -> v2 V2
|
|
|
|
1 -> v1 V1
|
|
|
|
0 -> v0 V0
|
convert lockcontent api to http long polling
Websockets would work, but the problem with using them for this is that
each lockcontent call is a separate websocket connection. And that's an
actual TCP connection. One TCP connection per file dropped would be too
expensive. With http long polling, regular http pipelining can be used,
so it will reuse a TCP connection.
Unfortunately, at least with servant, bi-directional streams with long
polling don't result in true bidirectional full duplex communication.
Servant processes the whole client body stream before generating the server
body stream. I think it's entirely possible to do full bi-directional
communication over http, but it would need changes to servant.
And, there's no way for the client to tell if the server successfully
locked the content, since the server will keep processing the client
stream no matter what.:
So, added a new api endpoint, keeplocked. lockcontent will lock the key
for 10 minutes with retention lock, and then a call to keeplocked will
keep it locked for as long as needed. This does mean that there will
need to be a Map of locks by key, and I will probably want to add
some kind of lock identifier that lockcontent returns.
2024-07-08 14:40:38 +00:00
|
|
|
_ -> error "unsupported protocol version"
|
2024-07-08 01:20:50 +00:00
|
|
|
where
|
|
|
|
_ :<|> _ :<|> _ :<|> _ :<|>
|
|
|
|
_ :<|> _ :<|> _ :<|> _ :<|>
|
|
|
|
_ :<|> _ :<|> _ :<|> _ :<|>
|
|
|
|
_ :<|>
|
|
|
|
_ :<|>
|
|
|
|
_ :<|> _ :<|> _ :<|> _ :<|>
|
|
|
|
_ :<|> _ :<|> _ :<|>
|
convert lockcontent api to http long polling
Websockets would work, but the problem with using them for this is that
each lockcontent call is a separate websocket connection. And that's an
actual TCP connection. One TCP connection per file dropped would be too
expensive. With http long polling, regular http pipelining can be used,
so it will reuse a TCP connection.
Unfortunately, at least with servant, bi-directional streams with long
polling don't result in true bidirectional full duplex communication.
Servant processes the whole client body stream before generating the server
body stream. I think it's entirely possible to do full bi-directional
communication over http, but it would need changes to servant.
And, there's no way for the client to tell if the server successfully
locked the content, since the server will keep processing the client
stream no matter what.:
So, added a new api endpoint, keeplocked. lockcontent will lock the key
for 10 minutes with retention lock, and then a call to keeplocked will
keep it locked for as long as needed. This does mean that there will
need to be a Map of locks by key, and I will probably want to add
some kind of lock identifier that lockcontent returns.
2024-07-08 14:40:38 +00:00
|
|
|
_ :<|> _ :<|> _ :<|> _ :<|>
|
|
|
|
v3 :<|> v2 :<|> v1 :<|> v0 :<|> _ = client p2pHttpAPI
|
2024-07-08 01:20:50 +00:00
|
|
|
|
2024-07-09 17:37:55 +00:00
|
|
|
clientKeepLocked
|
convert lockcontent api to http long polling
Websockets would work, but the problem with using them for this is that
each lockcontent call is a separate websocket connection. And that's an
actual TCP connection. One TCP connection per file dropped would be too
expensive. With http long polling, regular http pipelining can be used,
so it will reuse a TCP connection.
Unfortunately, at least with servant, bi-directional streams with long
polling don't result in true bidirectional full duplex communication.
Servant processes the whole client body stream before generating the server
body stream. I think it's entirely possible to do full bi-directional
communication over http, but it would need changes to servant.
And, there's no way for the client to tell if the server successfully
locked the content, since the server will keep processing the client
stream no matter what.:
So, added a new api endpoint, keeplocked. lockcontent will lock the key
for 10 minutes with retention lock, and then a call to keeplocked will
keep it locked for as long as needed. This does mean that there will
need to be a Map of locks by key, and I will probably want to add
some kind of lock identifier that lockcontent returns.
2024-07-08 14:40:38 +00:00
|
|
|
:: ClientEnv
|
2024-07-09 17:37:55 +00:00
|
|
|
-> ProtocolVersion
|
2024-07-09 00:18:55 +00:00
|
|
|
-> LockID
|
convert lockcontent api to http long polling
Websockets would work, but the problem with using them for this is that
each lockcontent call is a separate websocket connection. And that's an
actual TCP connection. One TCP connection per file dropped would be too
expensive. With http long polling, regular http pipelining can be used,
so it will reuse a TCP connection.
Unfortunately, at least with servant, bi-directional streams with long
polling don't result in true bidirectional full duplex communication.
Servant processes the whole client body stream before generating the server
body stream. I think it's entirely possible to do full bi-directional
communication over http, but it would need changes to servant.
And, there's no way for the client to tell if the server successfully
locked the content, since the server will keep processing the client
stream no matter what.:
So, added a new api endpoint, keeplocked. lockcontent will lock the key
for 10 minutes with retention lock, and then a call to keeplocked will
keep it locked for as long as needed. This does mean that there will
need to be a Map of locks by key, and I will probably want to add
some kind of lock identifier that lockcontent returns.
2024-07-08 14:40:38 +00:00
|
|
|
-> B64UUID ClientSide
|
|
|
|
-> B64UUID ServerSide
|
|
|
|
-> [B64UUID Bypass]
|
|
|
|
-> TMVar Bool
|
|
|
|
-> IO ()
|
2024-07-09 17:37:55 +00:00
|
|
|
clientKeepLocked clientenv protover lckid cu su bypass keeplocked = do
|
|
|
|
let cli = clientKeepLocked' protover lckid cu su bypass
|
convert lockcontent api to http long polling
Websockets would work, but the problem with using them for this is that
each lockcontent call is a separate websocket connection. And that's an
actual TCP connection. One TCP connection per file dropped would be too
expensive. With http long polling, regular http pipelining can be used,
so it will reuse a TCP connection.
Unfortunately, at least with servant, bi-directional streams with long
polling don't result in true bidirectional full duplex communication.
Servant processes the whole client body stream before generating the server
body stream. I think it's entirely possible to do full bi-directional
communication over http, but it would need changes to servant.
And, there's no way for the client to tell if the server successfully
locked the content, since the server will keep processing the client
stream no matter what.:
So, added a new api endpoint, keeplocked. lockcontent will lock the key
for 10 minutes with retention lock, and then a call to keeplocked will
keep it locked for as long as needed. This does mean that there will
need to be a Map of locks by key, and I will probably want to add
some kind of lock identifier that lockcontent returns.
2024-07-08 14:40:38 +00:00
|
|
|
(Just connectionKeepAlive) (Just keepAlive)
|
|
|
|
(S.fromStepT unlocksender)
|
|
|
|
withClientM cli clientenv $ \case
|
|
|
|
Left err -> throwM err
|
2024-07-09 00:18:55 +00:00
|
|
|
Right (LockResult _ _) ->
|
convert lockcontent api to http long polling
Websockets would work, but the problem with using them for this is that
each lockcontent call is a separate websocket connection. And that's an
actual TCP connection. One TCP connection per file dropped would be too
expensive. With http long polling, regular http pipelining can be used,
so it will reuse a TCP connection.
Unfortunately, at least with servant, bi-directional streams with long
polling don't result in true bidirectional full duplex communication.
Servant processes the whole client body stream before generating the server
body stream. I think it's entirely possible to do full bi-directional
communication over http, but it would need changes to servant.
And, there's no way for the client to tell if the server successfully
locked the content, since the server will keep processing the client
stream no matter what.:
So, added a new api endpoint, keeplocked. lockcontent will lock the key
for 10 minutes with retention lock, and then a call to keeplocked will
keep it locked for as long as needed. This does mean that there will
need to be a Map of locks by key, and I will probably want to add
some kind of lock identifier that lockcontent returns.
2024-07-08 14:40:38 +00:00
|
|
|
liftIO $ print "end of lock connection to server"
|
|
|
|
where
|
|
|
|
unlocksender =
|
|
|
|
S.Yield (UnlockRequest False) $ S.Effect $ do
|
|
|
|
liftIO $ print "sent keep locked request"
|
|
|
|
return $ S.Effect $ do
|
|
|
|
stilllock <- liftIO $ atomically $ takeTMVar keeplocked
|
|
|
|
if stilllock
|
|
|
|
then return unlocksender
|
|
|
|
else do
|
|
|
|
liftIO $ print "sending unlock request"
|
|
|
|
return $ S.Yield (UnlockRequest True) S.Stop
|
|
|
|
|
2024-07-09 14:12:36 +00:00
|
|
|
type PV3 = Capture "v3" V3
|
|
|
|
|
|
|
|
type PV2 = Capture "v2" V2
|
|
|
|
|
|
|
|
type PV1 = Capture "v1" V1
|
|
|
|
|
|
|
|
type PV0 = Capture "v0" V0
|
|
|
|
|
2024-07-08 01:20:50 +00:00
|
|
|
type ClientUUID req = QueryParam' '[req] "clientuuid" (B64UUID ClientSide)
|
2024-07-07 18:48:20 +00:00
|
|
|
|
2024-07-08 01:20:50 +00:00
|
|
|
type ServerUUID req = QueryParam' '[req] "serveruuid" (B64UUID ServerSide)
|
|
|
|
|
|
|
|
type BypassUUIDs = QueryParams "bypass" (B64UUID Bypass)
|
2024-07-07 16:59:12 +00:00
|
|
|
|
|
|
|
type CaptureKey = Capture "key" B64Key
|
|
|
|
|
2024-07-07 18:48:20 +00:00
|
|
|
type KeyParam = QueryParam' '[Required] "key" B64Key
|
2024-07-07 16:59:12 +00:00
|
|
|
|
|
|
|
type AssociatedFileParam = QueryParam "associatedfile" B64FilePath
|
|
|
|
|
2024-07-07 18:48:20 +00:00
|
|
|
type OffsetParam = QueryParam "offset" Offset
|
2024-07-07 16:59:12 +00:00
|
|
|
|
|
|
|
type DataLengthHeader = Header "X-git-annex-data-length" Integer
|
|
|
|
|
2024-07-09 00:18:55 +00:00
|
|
|
type LockIDParam = QueryParam' '[Required] "lockid" LockID
|
2024-07-09 21:30:55 +00:00
|
|
|
|
|
|
|
type AuthHeader = Header "Authorization" Auth
|