Newer
Older
Jean-Paul Calderone
committed
{-# LANGUAGE ViewPatterns #-}
{- | A high-level interface to downloading share data as bytes from storage
servers.
-}
module Tahoe.Download (LookupServer, DownloadError (..), discoverShares, download) where
Jean-Paul Calderone
committed
k with)
module Tahoe.Download (
LookupServer,
DownloadError (..),
discoverOnce,
download,
gbsURLToStorageServer,
) where
Jean-Paul Calderone
committed
import Control.Exception (throwIO)
import Control.Monad.Catch (MonadCatch, catch)
import Control.Monad.IO.Class (MonadIO (liftIO))
import Data.Binary (decodeOrFail)
import qualified Data.ByteString.Lazy as LB
import Data.Either (isRight, rights)
import Data.List (foldl')
Jean-Paul Calderone
committed
import Data.List.NonEmpty (NonEmpty ((:|)))
import qualified Data.Map.Strict as Map
import qualified Data.Set as Set
Jean-Paul Calderone
committed
import qualified Data.Text as T
import Data.Text.Encoding (decodeUtf8)
import Network.HTTP.Client (ManagerSettings, defaultManagerSettings, newManager)
import Servant.Client (Scheme (Https), mkClientEnv, runClientM)
import Servant.Client.Core (BaseUrl (BaseUrl, baseUrlHost, baseUrlPath, baseUrlPort, baseUrlScheme))
import qualified Tahoe.CHK
import Tahoe.CHK.Capability (Reader (..), Verifier (..))
import qualified Tahoe.CHK.Encrypt
import Tahoe.CHK.Server (StorageServer (..), StorageServerAnnouncement (..), StorageServerID, URL)
import Tahoe.CHK.Types (ShareNum, StorageIndex)
Jean-Paul Calderone
committed
import TahoeLAFS.Storage.API (ShareNumber (ShareNumber))
import TahoeLAFS.Storage.Client (readImmutableShares)
import Text.URI (Authority (Authority, authHost, authPort, authUserInfo), ParseException (ParseException), RText, URI (..), UserInfo (UserInfo, uiPassword, uiUsername), mkURI, unRText)
-- | A view pattern for matching on the text of an RTest value.
restrictedText :: RText l -> String
restrictedText (T.unpack . unRText -> t) = t
{- | 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
| -- | 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,
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
deriving (Eq, Ord, Show)
{- | An 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
Jean-Paul Calderone
committed
| -- | An announcement included a location we could not interpret.
StorageServerLocationUnsupported
| StorageServerUnreachable
-- TODO The result might need to be in IO in case the URL indicates a
-- Tor-based route to the server. In this case we might need to launch a Tor
-- daemon or connect to a running Tor daemon or at least set up a new Tor
-- circuit. All of which require I/O. But we can always refactor later!
type LookupServer = URL -> Maybe StorageServer
{- | Recover the application data associated with a given capability from the
given servers, if possible.
-}
-- | Information about the servers from which to consider downloading shares
-- representing the application data.
Map.Map StorageServerID StorageServerAnnouncement ->
-- | The read capability for the application data.
-- | Get functions for interacting with a server given its URL.
-- | Either a description of how the recovery failed or the recovered
-- application data.
IO (Either DownloadError LB.ByteString)
download servers cap@Reader{readKey, verifier = Verifier{..}} lookupServer =
case Map.toList servers of
[] -> pure . Left $ NoConfiguredServers
serverList -> do
-- Ask each server for all shares it has.
discovered <- rights <$> mapM (discoverShares lookupServer storageIndex) serverList :: IO [(StorageServer, Set.Set ShareNum)]
if null discovered
then pure $ Left NoReachableServers
else
if (fromIntegral required >) . countDistinctShares $ discovered
then pure $ Left NotEnoughShares{notEnoughSharesNeeded = fromIntegral required, notEnoughSharesFound = countDistinctShares discovered}
else do
-- XXX up to here is probably "locateShares". now we move in to "fetchShares".
let sharemap = makeShareMap discovered
-- XXX note shares can contain failures
shares <- mapM (uncurry $ downloadShare storageIndex) (Map.toList sharemap)
-- XXX That was brief. Probably missing some complexity. now we move on to "decodeShares".
-- Filter down to shares we actually got.
let someShares = filter (isRight . snd) shares
fewerShares = filter (isRight . snd) $ (\(sharenum, Right bs) -> (sharenum, decodeOrFail bs)) <$> someShares
onlyDecoded = (\(sharenum, Right (_, _, share)) -> (fromIntegral sharenum, share)) <$> fewerShares
if length onlyDecoded < fromIntegral required
then pure $ Left NotEnoughDecodedShares{notEnoughDecodedSharesNeeded = fromIntegral required, notEnoughDecodedSharesFound = length onlyDecoded}
else do
ciphertext <- Tahoe.CHK.decode cap onlyDecoded
case ciphertext of
Nothing -> pure $ Left ShareDecodingFailed
Just ct ->
pure . Right $ Tahoe.CHK.Encrypt.decrypt readKey ct
{- | Figure the total number of distinct shares reported by all of the servers
we asked.
-}
countDistinctShares :: Ord b => [(a, Set.Set b)] -> Int
countDistinctShares = Set.size . foldl' Set.union mempty . map snd
{- | Ask one server which shares it has related to the storage index in
question.
-}
discoverShares :: LookupServer -> StorageIndex -> (StorageServerID, StorageServerAnnouncement) -> IO (Either DiscoverError (StorageServer, Set.Set ShareNum))
discoverShares lookupServer storageIndex (_sid, sann) = do
case storageServerAnnouncementFURL sann of
Nothing -> pure $ Left StorageServerLocationUnknown
Just url -> do
let server = lookupServer url
case server of
Nothing -> pure $ Left StorageServerUnreachable
Just ss@StorageServer{storageServerGetBuckets} ->
Right . (ss,) <$> storageServerGetBuckets storageIndex
{- | Invert the mapping implied by the list of two tuples so that the servers
that claim to have a certain share can easily be retrieved.
-}
makeShareMap :: Ord k => [(v, Set.Set k)] -> Map.Map k [v]
makeShareMap locations =
foldl' (Map.unionWith (<>)) mempty ((\(k, v) -> Map.fromSet (const [k]) v) <$> locations)
-- | Download the bytes of a share from one (or more!) of the given servers.
downloadShare ::
-- | The storage index of the share to download.
StorageIndex ->
-- | The number of the share to download.
ShareNum ->
-- | The servers which we have a reasonable belief could hold a copy of the
-- share. It is common for there to be only one server holding each share
-- but nothing *prevents* multiple servers from having one. In this case we
-- could download the share from both of them, perhaps.
[StorageServer] ->
-- | The bytes of the share or some error that was encountered during
-- download.
IO (ShareNum, Either DownloadError LB.ByteString)
downloadShare _ shareNum [] = pure (shareNum, Left NoServers)
downloadShare storageIndex shareNum (s : _) = do
-- TODO: There might be more servers. We could try them if this fails.
-- On the other hand, we might get bytes but we don't verify them here so
-- we might also need retry logic up a level or two from here.
shareBytes <- storageServerRead s storageIndex shareNum
pure (shareNum, Right $ LB.fromStrict shareBytes)
Jean-Paul Calderone
committed
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
gbsURLToStorageServer :: (MonadIO m, MonadCatch m) => T.Text -> m (Maybe StorageServer)
gbsURLToStorageServer url =
catch (mkURI url >>= makeServer) (\ParseException{} -> pure Nothing)
makeServer :: MonadIO m => URI -> m (Maybe StorageServer)
makeServer
URI
{ uriScheme = Just (restrictedText -> "pb")
, uriAuthority =
Right
( Authority
{ authUserInfo =
Just
( UserInfo
{ uiUsername = tubid
, uiPassword = Nothing
}
)
, authHost = host
, authPort = Just port
}
)
, uriPath = Just (False, swissnum :| [])
, uriQuery = []
, uriFragment = Just (restrictedText -> "v=1")
} =
do
manager <- liftIO $ newManager (managerSettingsForService (unRText tubid) (unRText swissnum))
let baseUrl = https (T.unpack $ unRText host) (fromIntegral port)
env = mkClientEnv manager baseUrl
storageServerID = undefined
storageServerWrite = undefined
storageServerRead storageIndex shareNum = do
let clientm = readImmutableShares (T.unpack $ decodeUtf8 storageIndex) (ShareNumber $ fromIntegral shareNum) Nothing
res <- runClientM clientm env
case res of
Left err -> throwIO err
Right bs -> pure bs
storageServerGetBuckets = undefined
pure $ Just StorageServer{..}
makeServer _ = pure Nothing
https :: String -> Int -> BaseUrl
https host port =
BaseUrl
{ baseUrlScheme = Https
, baseUrlHost = host
, baseUrlPort = port
, baseUrlPath = "/"
}
managerSettingsForService :: T.Text -> T.Text -> ManagerSettings
managerSettingsForService _ _ = defaultManagerSettings