Newer
Older
{- | Functionality related to acting as a client for the Great Black Swamp
protocol.
-}
module Tahoe.Download.Internal.Client where
import Control.Monad.IO.Class
import qualified Data.ByteString as B
import qualified Data.ByteString.Base64 as Base64
import qualified Data.Text as T
import Data.Text.Encoding
import Network.Connection
import Network.HTTP.Client (Manager, ManagerSettings (managerModifyRequest), Request (requestHeaders))
import Network.HTTP.Types (ByteRange)
import Network.URI (uriToString)
import Tahoe.Announcement
import Tahoe.CHK.Server (
import TahoeLAFS.Storage.API (CBORSet (CBORSet), ShareNumber (ShareNumber))
import TahoeLAFS.Storage.Client (NURL, parseNURL, runGBS)
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
-- | Make an HTTPS URL.
https :: String -> Int -> BaseUrl
https host port =
BaseUrl
{ baseUrlScheme = Https
, baseUrlHost = host
, baseUrlPort = port
, baseUrlPath = ""
}
{- | Make an HTTPS manager for the given SPKI hash and swissnum.
The SPKI hash is _not_ used to authenticate the server! See
https://whetstone.private.storage/privatestorage/tahoe-great-black-swamp/-/issues/27
-}
managerSettingsForService :: T.Text -> T.Text -> ManagerSettings
managerSettingsForService _ swissnum =
(mkManagerSettings tlsSettings sockSettings){managerModifyRequest = pure . authorize}
where
tlsSettings = TLSSettingsSimple True True True
sockSettings = Nothing
swissnumBytes = encodeUtf8 swissnum
swissnumBase64 = Base64.encode swissnumBytes
headerCompleteBytes = B.concat ["Tahoe-LAFS ", swissnumBase64]
authorize req =
req
{ requestHeaders =
( "Authorization"
, headerCompleteBytes
) :
requestHeaders req
}
-- | Make a manager suitable for use with a Great Black Swamp server.
newGBSManager ::
MonadIO m =>
[Char] ->
String ->
m Manager
newGBSManager tubid swissnum =
newTlsManagerWith $
managerSettingsForService
(T.pack . init $ tubid)
(T.pack swissnum)
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
{- | An unrecoverable problem arose while attempting to download and/or read
some application data.
-}
data DownloadError
= -- | The configuration included no candidate servers from which to download.
NoConfiguredServers
| -- | Across all of the configured servers, none were actually connectable.
NoReachableServers [DiscoverError]
| -- | Across all of the configured servers, fewer than the required
-- number of shares were found. XXX Could split this into the different
-- cases - did not locate enough shares, did not download enough shares,
-- did not verify enough shares
NotEnoughShares
{ notEnoughSharesNeeded :: Int
, notEnoughSharesFound :: Int
}
| -- | Across all of the shares that we could download, fewer than the
-- required number could actually be decoded.
NotEnoughDecodedShares
{ notEnoughDecodedSharesNeeded :: Int
, notEnoughDecodedSharesFound :: Int
}
| -- | Enough syntactically valid shares were recovered but they could not
-- be interpreted.
ShareDecodingFailed
| -- | An attempt was made to download a share but no servers were given for
-- the download.
NoServers
| -- | An error occurred during share download.
ShareDownloadError String
deriving (Eq, Ord, Show)
{- | A problem arose while attempting to discover the shares held on a
particular server.
-}
data DiscoverError
= -- | An announcement did not include a location for a connection attempt.
StorageServerLocationUnknown
| -- | An announcement included a location we could not interpret.
StorageServerLocationUnsupported
| StorageServerUnreachable LookupError
| StorageServerCommunicationError String
deriving (Eq, Ord, Show)
{- | The type of a function that can produce a concrete StorageServer from
that server's announcement.
-}
type LookupServer m = StorageServerAnnouncement -> m (Either LookupError StorageServer)
-- | There was a problem while trying to look up a server from its announcement.
data LookupError
= -- | The server's announced URI was unparseable.
URIParseError StorageServerAnnouncement
| -- | The port integer in the server's URI was unparseable.
PortParseError String
| -- | The structure of the server's URI was unparseable.
AnnouncementStructureUnmatched
deriving (Eq, Ord, Show)
{- | A problem was encountered attempting to deserialize bytes to a structured
representation of some value.
-}
data DeserializeError = UnknownDeserializeError -- add more later?
type GetShareNumbers = String -> ClientM (CBORSet ShareNumber)
type ReadShare = String -> ShareNumber -> Maybe [ByteRange] -> ClientM B.ByteString
{- | Create a StorageServer that will speak Great Black Swamp using the given
manager to the server at the given host/port.
-}
mkWrapper :: GetShareNumbers -> ReadShare -> NURL -> StorageServer
mkWrapper getShareNumbers readShare nurl =
StorageServer{..}
where
toBase32 = T.unpack . T.toLower . encodeBase32Unpadded
storageServerID = undefined
storageServerWrite = undefined
storageServerRead storageIndex shareNum = do
let clientm = readShare (toBase32 storageIndex) (ShareNumber $ fromIntegral shareNum) Nothing
res <- runGBS nurl clientm
case res of
Left err -> do
throwIO err
Right bs -> pure bs
storageServerGetBuckets storageIndex = do
let clientm = getShareNumbers (toBase32 storageIndex)
r <- try $ runGBS nurl clientm
case r of
Left (_ :: SomeException) -> do
pure mempty
Right res -> do
case res of
Left err -> do
throwIO err
Right (CBORSet s) -> pure $ Set.map (\(ShareNumber i) -> fromIntegral i) s -- XXX fromIntegral aaaaaaaa!!
{- | If possible, populate a StorageServer with functions for operating on data
on the server at the given URI.
-}
makeServer :: MonadIO m => GetShareNumbers -> ReadShare -> URI -> m (Either LookupError StorageServer)
makeServer getShareNumbers readShare uri =
pure $ case parseNURL (T.pack $ uriToString id uri "") of
Nothing -> Left AnnouncementStructureUnmatched
Just nurl -> Right $ mkWrapper getShareNumbers readShare nurl
announcementToStorageServer :: MonadIO m => GetShareNumbers -> ReadShare -> StorageServerAnnouncement -> m (Either LookupError StorageServer)
announcementToStorageServer getShareNumbers readShare ann =
case greatBlackSwampURIs ann of
Nothing -> pure . Left . URIParseError $ ann
Just uri -> makeServer getShareNumbers readShare uri