Safe Haskell | None |
---|---|
Language | Haskell2010 |
A high-level interface to downloading share data as bytes from storage servers.
Synopsis
- type LookupServer m = StorageServerAnnouncement -> m (Either LookupError StorageServer)
- data DownloadError
- data DirectoryDownloadError
- data LookupError
- data DiscoverError
- discoverShares :: LookupServer IO -> StorageIndex -> (StorageServerID, StorageServerAnnouncement) -> IO (Either DiscoverError (StorageServer, Set ShareNum))
- download :: (MonadIO m, Readable readCap, Verifiable v, Verifier readCap ~ v) => Map StorageServerID StorageServerAnnouncement -> readCap -> LookupServer IO -> m (Either DownloadError ByteString)
- downloadDirectory :: (MonadIO m, Readable readCap, Verifiable v, Verifier readCap ~ v) => Map StorageServerID StorageServerAnnouncement -> DirectoryCapability readCap -> LookupServer IO -> m (Either DirectoryDownloadError Directory)
- announcementToImmutableStorageServer :: MonadIO m => StorageServerAnnouncement -> m (Either LookupError StorageServer)
- announcementToMutableStorageServer :: MonadIO m => StorageServerAnnouncement -> m (Either LookupError StorageServer)
- getShareNumbers :: (Verifiable v, MonadIO m) => v -> StorageServer -> m (Set ShareNum)
Documentation
type LookupServer m = StorageServerAnnouncement -> m (Either LookupError StorageServer) Source #
The type of a function that can produce a concrete StorageServer from that server's announcement.
data DownloadError Source #
An unrecoverable problem arose while attempting to download and/or read some application data.
NoConfiguredServers | The configuration included no candidate servers from which to download. |
NoReachableServers [DiscoverError] | Across all of the configured servers, none were actually connectable. |
NotEnoughShares | 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 |
NotEnoughDecodedShares | Across all of the shares that we could download, fewer than the required number could actually be decoded. |
ShareDecodingFailed | Enough syntactically valid shares were recovered but they could not be interpreted. |
NoServers | An attempt was made to download a share but no servers were given for the download. |
ShareDownloadError String | An error occurred during share download. |
Instances
Eq DownloadError Source # | |
Defined in Tahoe.Download.Internal.Client (==) :: DownloadError -> DownloadError -> Bool # (/=) :: DownloadError -> DownloadError -> Bool # | |
Ord DownloadError Source # | |
Defined in Tahoe.Download.Internal.Client compare :: DownloadError -> DownloadError -> Ordering # (<) :: DownloadError -> DownloadError -> Bool # (<=) :: DownloadError -> DownloadError -> Bool # (>) :: DownloadError -> DownloadError -> Bool # (>=) :: DownloadError -> DownloadError -> Bool # max :: DownloadError -> DownloadError -> DownloadError # min :: DownloadError -> DownloadError -> DownloadError # | |
Show DownloadError Source # | |
Defined in Tahoe.Download.Internal.Client showsPrec :: Int -> DownloadError -> ShowS # show :: DownloadError -> String # showList :: [DownloadError] -> ShowS # |
data DirectoryDownloadError Source #
Instances
Eq DirectoryDownloadError Source # | |
Defined in Tahoe.Download | |
Ord DirectoryDownloadError Source # | |
Defined in Tahoe.Download compare :: DirectoryDownloadError -> DirectoryDownloadError -> Ordering # (<) :: DirectoryDownloadError -> DirectoryDownloadError -> Bool # (<=) :: DirectoryDownloadError -> DirectoryDownloadError -> Bool # (>) :: DirectoryDownloadError -> DirectoryDownloadError -> Bool # (>=) :: DirectoryDownloadError -> DirectoryDownloadError -> Bool # max :: DirectoryDownloadError -> DirectoryDownloadError -> DirectoryDownloadError # min :: DirectoryDownloadError -> DirectoryDownloadError -> DirectoryDownloadError # | |
Show DirectoryDownloadError Source # | |
Defined in Tahoe.Download showsPrec :: Int -> DirectoryDownloadError -> ShowS # show :: DirectoryDownloadError -> String # showList :: [DirectoryDownloadError] -> ShowS # |
data LookupError Source #
There was a problem while trying to look up a server from its announcement.
URIParseError StorageServerAnnouncement | The server's announced URI was unparseable. |
PortParseError String | The port integer in the server's URI was unparseable. |
AnnouncementStructureUnmatched | The structure of the server's URI was unparseable. |
Instances
Eq LookupError Source # | |
Defined in Tahoe.Download.Internal.Client (==) :: LookupError -> LookupError -> Bool # (/=) :: LookupError -> LookupError -> Bool # | |
Ord LookupError Source # | |
Defined in Tahoe.Download.Internal.Client compare :: LookupError -> LookupError -> Ordering # (<) :: LookupError -> LookupError -> Bool # (<=) :: LookupError -> LookupError -> Bool # (>) :: LookupError -> LookupError -> Bool # (>=) :: LookupError -> LookupError -> Bool # max :: LookupError -> LookupError -> LookupError # min :: LookupError -> LookupError -> LookupError # | |
Show LookupError Source # | |
Defined in Tahoe.Download.Internal.Client showsPrec :: Int -> LookupError -> ShowS # show :: LookupError -> String # showList :: [LookupError] -> ShowS # |
data DiscoverError Source #
A problem arose while attempting to discover the shares held on a particular server.
StorageServerLocationUnknown | An announcement did not include a location for a connection attempt. |
StorageServerLocationUnsupported | An announcement included a location we could not interpret. |
StorageServerUnreachable LookupError | |
StorageServerCommunicationError String |
Instances
Eq DiscoverError Source # | |
Defined in Tahoe.Download.Internal.Client (==) :: DiscoverError -> DiscoverError -> Bool # (/=) :: DiscoverError -> DiscoverError -> Bool # | |
Ord DiscoverError Source # | |
Defined in Tahoe.Download.Internal.Client compare :: DiscoverError -> DiscoverError -> Ordering # (<) :: DiscoverError -> DiscoverError -> Bool # (<=) :: DiscoverError -> DiscoverError -> Bool # (>) :: DiscoverError -> DiscoverError -> Bool # (>=) :: DiscoverError -> DiscoverError -> Bool # max :: DiscoverError -> DiscoverError -> DiscoverError # min :: DiscoverError -> DiscoverError -> DiscoverError # | |
Show DiscoverError Source # | |
Defined in Tahoe.Download.Internal.Client showsPrec :: Int -> DiscoverError -> ShowS # show :: DiscoverError -> String # showList :: [DiscoverError] -> ShowS # |
discoverShares :: LookupServer IO -> StorageIndex -> (StorageServerID, StorageServerAnnouncement) -> IO (Either DiscoverError (StorageServer, Set ShareNum)) Source #
Ask one server which shares it has related to the storage index in question.
:: (MonadIO m, Readable readCap, Verifiable v, Verifier readCap ~ v) | |
=> Map StorageServerID StorageServerAnnouncement | Information about the servers from which to consider downloading shares representing the application data. |
-> readCap | The read capability for the application data. |
-> LookupServer IO | Get functions for interacting with a server given its URL. |
-> m (Either DownloadError ByteString) | Either a description of how the recovery failed or the recovered application data. |
Recover the application data associated with a given capability from the given servers, if possible.
:: (MonadIO m, Readable readCap, Verifiable v, Verifier readCap ~ v) | |
=> Map StorageServerID StorageServerAnnouncement | Information about the servers from which to consider downloading shares representing the application data. |
-> DirectoryCapability readCap | The read capability for the application data. |
-> LookupServer IO | Get functions for interacting with a server given its URL. |
-> m (Either DirectoryDownloadError Directory) | Either a description of how the recovery failed or the recovered application data. |
Download the data associated with a directory capability and interpret it as a collection of entries.
announcementToImmutableStorageServer :: MonadIO m => StorageServerAnnouncement -> m (Either LookupError StorageServer) Source #
Interpret the location in an announcement as a Tahoe-LAFS fURL pointed at a Great Black Swamp server and construct a StorageServer for interacting with immutable shares stored on it.
announcementToMutableStorageServer :: MonadIO m => StorageServerAnnouncement -> m (Either LookupError StorageServer) Source #
Interpret the location in an announcement as a Tahoe-LAFS fURL pointed at a Great Black Swamp server and construct a StorageServer for interacting with mutable shares stored on it.
getShareNumbers :: (Verifiable v, MonadIO m) => v -> StorageServer -> m (Set ShareNum) Source #
Ask a storage server which share numbers related to this capability it is holding. This is an unverified result and the storage server could present incorrect information. Even if it correctly reports that it holds a share, it could decline to give it out when asked.