| Safe Haskell | Safe-Infered |
|---|
Dropbox
Contents
- mkConfig :: Locale -> String -> String -> AccessType -> IO Config
- data Config = Config {}
- data CertVerifier = CertVerifier {}
- certVerifierInsecure :: CertVerifier
- certVerifierFromPemFile :: FilePath -> IO (Either String CertVerifier)
- certVerifierFromRootCerts :: [X509] -> ByteString -> [X509] -> IO TLSCertificateUsage
- data AppId = AppId String String
- data Hosts = Hosts {}
- hostsDefault :: Hosts
- data Locale
- localeEn :: Locale
- localeEs :: Locale
- localeFr :: Locale
- localeDe :: Locale
- localeJp :: Locale
- data AccessType
- type Manager = Manager
- withManager :: (MonadBaseControl IO m, MonadThrow m, MonadUnsafeIO m, MonadIO m) => (Manager -> ResourceT m a) -> m a
- data RequestToken = RequestToken String String
- authStart :: Manager -> Config -> Maybe URL -> IO (Either ErrorMessage (RequestToken, URL))
- data AccessToken = AccessToken String String
- authFinish :: Manager -> Config -> RequestToken -> IO (Either ErrorMessage (AccessToken, String))
- data Session = Session {}
- getAccountInfo :: Manager -> Session -> IO (Either ErrorMessage AccountInfo)
- data AccountInfo = AccountInfo {}
- getMetadata :: (MonadBaseControl IO m, MonadThrow m, MonadUnsafeIO m, MonadIO m) => Manager -> Session -> Path -> m (Either ErrorMessage Meta)
- getMetadataWithChildren :: (MonadBaseControl IO m, MonadThrow m, MonadUnsafeIO m, MonadIO m) => Manager -> Session -> Path -> Maybe Integer -> m (Either ErrorMessage (Meta, Maybe FolderContents))
- getMetadataWithChildrenIfChanged :: (MonadBaseControl IO m, MonadThrow m, MonadUnsafeIO m, MonadIO m) => Manager -> Session -> Path -> Maybe Integer -> FolderHash -> m (Either ErrorMessage (Maybe (Meta, Maybe FolderContents)))
- data Meta = Meta MetaBase MetaExtra
- data MetaBase = MetaBase {
- metaRoot :: AccessType
- metaPath :: String
- metaIsDeleted :: Bool
- metaThumbnail :: Bool
- metaIcon :: String
- data MetaExtra
- data FolderContents = FolderContents {
- folderHash :: FolderHash
- folderChildren :: [Meta]
- data FileExtra = FileExtra {}
- newtype FolderHash = FolderHash String
- newtype FileRevision = FileRevision String
- getFile :: (MonadBaseControl IO m, MonadThrow m, MonadUnsafeIO m, MonadIO m) => Manager -> Session -> Path -> Maybe FileRevision -> (Meta -> Sink ByteString (ResourceT m) r) -> m (Either ErrorMessage (Meta, r))
- getFileBs :: (MonadBaseControl IO m, MonadThrow m, MonadUnsafeIO m, MonadIO m) => Manager -> Session -> Path -> Maybe FileRevision -> m (Either ErrorMessage (Meta, ByteString))
- putFile :: (MonadBaseControl IO m, MonadThrow m, MonadUnsafeIO m, MonadIO m) => Manager -> Session -> Path -> WriteMode -> RequestBody m -> m (Either ErrorMessage Meta)
- data WriteMode
- fileRevisionToString :: FileRevision -> String
- folderHashToString :: FolderHash -> String
- type ErrorMessage = String
- type URL = String
- type Path = String
- data RequestBody m = RequestBody Int64 (Source (ResourceT m) ByteString)
- bsRequestBody :: MonadIO m => ByteString -> RequestBody m
- bsSink :: Monad m => Sink ByteString m ByteString
Configuration
The configuration used to make API calls. You typically create
one of these via the config helper function.
Constructors
| Config | |
Fields
| |
data CertVerifier Source
How the server's SSL certificate will be verified.
Constructors
| CertVerifier | |
Fields
| |
Instances
certVerifierInsecure :: CertVerifierSource
A dummy implementation that doesn't perform any verification.
certVerifierFromPemFile :: FilePath -> IO (Either String CertVerifier)Source
Reads certificates in PEM format from the given file and uses those as the roots when
verifying certificates. This function basically just loads the certificates and delegates
to certVerifierFromRootCerts for the actual checking.
certVerifierFromRootCertsSource
Arguments
| :: [X509] | The set of trusted root certificates. |
| -> ByteString | The remote server's domain name. |
| -> [X509] | The certificate chain provided by the remote server. |
| -> IO TLSCertificateUsage |
A certificate validation routine. It's in IO to match what Enumerator
expects, but we don't actually do any I/O.
Your application's Dropbox "app key" and "app secret".
The set of hosts that serve the Dropbox API. Just use hostsDefault.
Constructors
| Hosts | |
The standard set of hosts that serve the Dropbox API. Used to create a Config.
Specifies a locale (the string is a two-letter locale code)
data AccessType Source
The type of folder access your Dropbox application uses (https://www.dropbox.com/developers/start/core).
Constructors
| AccessTypeDropbox | Full access to the user's entire Dropbox |
| AccessTypeAppFolder | Access to an application-specific "app folder" within the user's Dropbox |
Instances
HTTP connection manager
The HTTP connection manager. Using the same Manager instance across
multiple API calls
withManager :: (MonadBaseControl IO m, MonadThrow m, MonadUnsafeIO m, MonadIO m) => (Manager -> ResourceT m a) -> m aSource
A bracket around an HTTP connection manager.
Uses default ManagerSettings as computed by managerSettings.
OAuth
data RequestToken Source
An OAuth request token (returned by authStart)
Constructors
| RequestToken String String |
Instances
Arguments
| :: Manager | The HTTP connection manager to use. |
| -> Config | |
| -> Maybe URL | The callback URL (optional) |
| -> IO (Either ErrorMessage (RequestToken, URL)) |
OAuth step 1. If successful, returns a RequestToken (to be used with
authFinish eventually) and an authorization URL that you should redirect the user
to next. If you provide a callback URL (optional), then the authorization URL you
send the user to will redirect to your callback URL after the user authorizes your
application.
data AccessToken Source
An OAuth request token (returned by authFinish, used to construct a Session)
Constructors
| AccessToken String String |
Instances
Arguments
| :: Manager | The HTTP connection manager to use. |
| -> Config | |
| -> RequestToken | The |
| -> IO (Either ErrorMessage (AccessToken, String)) | The |
OAuth step 3. Once you've directed the user to the authorization URL from authStart
and the user has authorized your app, call this function to get a RequestToken, which
is used to make Dropbox API calls.
Contains a Config and an AccessToken. Every API call (after OAuth is complete)
requires this as an argument.
Constructors
| Session | |
Fields
| |
Get user account info
Arguments
| :: Manager | The HTTP connection manager to use. |
| -> Session | |
| -> IO (Either ErrorMessage AccountInfo) |
Retrieve information about the user account your AccessToken is connected to.
data AccountInfo Source
Information about a user account.
Constructors
| AccountInfo | |
Fields
| |
Instances
Get file/folder metadata
Arguments
| :: (MonadBaseControl IO m, MonadThrow m, MonadUnsafeIO m, MonadIO m) | |
| => Manager | The HTTP connection manager to use. |
| -> Session | |
| -> Path | The full path (relative to your |
| -> m (Either ErrorMessage Meta) |
Get the metadata for the file or folder at the given path.
Arguments
| :: (MonadBaseControl IO m, MonadThrow m, MonadUnsafeIO m, MonadIO m) | |
| => Manager | The HTTP connection manager to use. |
| -> Session | |
| -> Path | The full path (relative to your |
| -> Maybe Integer | A limit on folder contents (max: 10,000). If the path refers to a folder and this folder
has more than the specified number of immediate children, the entire
|
| -> m (Either ErrorMessage (Meta, Maybe FolderContents)) |
Get the metadata for the file or folder at the given path. If it's a folder, return the metadata for the folder's immediate children as well.
getMetadataWithChildrenIfChangedSource
Arguments
| :: (MonadBaseControl IO m, MonadThrow m, MonadUnsafeIO m, MonadIO m) | |
| => Manager | The HTTP connection manager to use. |
| -> Session | |
| -> Path | |
| -> Maybe Integer | |
| -> FolderHash | For folders, the returned child metadata will include a |
| -> m (Either ErrorMessage (Maybe (Meta, Maybe FolderContents))) |
Same as getMetadataWithChildren except it'll return Nothing if the FolderHash
of the folder on Dropbox is the same as the FolderHash passed in.
Metadata common to both files and folders.
Constructors
| MetaBase | |
Fields
| |
Extra metadata (in addition to the stuff that's common to files and folders).
data FolderContents Source
The metadata for the immediate children of a folder.
Constructors
| FolderContents | |
Fields
| |
Instances
Extra metadata specific to files (and not folders)
Constructors
| FileExtra | |
Fields
| |
newtype FolderHash Source
Represents an identifier for a folder's metadata and children's metadata. Can be used with
getMetadataWithChildrenIfChanged to avoid downloading a folder's metadata and children's metadata
if it hasn't changed.
Constructors
| FolderHash String |
Instances
newtype FileRevision Source
Represents a file's revision (fileRevision).
Constructors
| FileRevision String |
Instances
Upload/download files
Arguments
| :: (MonadBaseControl IO m, MonadThrow m, MonadUnsafeIO m, MonadIO m) | |
| => Manager | The HTTP connection manager to use. |
| -> Session | |
| -> Path | The full path (relative to your |
| -> Maybe FileRevision | The revision of the file to retrieve. |
| -> (Meta -> Sink ByteString (ResourceT m) r) | Given the file metadata, yield a |
| -> m (Either ErrorMessage (Meta, r)) | This function returns whatever your |
Gets a file's contents and metadata. If you just want the entire contents of
a file as a single ByteString, use getFileBs.
Arguments
| :: (MonadBaseControl IO m, MonadThrow m, MonadUnsafeIO m, MonadIO m) | |
| => Manager | The HTTP connection manager to use. |
| -> Session | |
| -> Path | The full path (relative to your |
| -> Maybe FileRevision | The revision of the file to retrieve. |
| -> m (Either ErrorMessage (Meta, ByteString)) |
A variant of getFile that just returns a strict ByteString (instead of having
you pass in a Sink to process the body.
Arguments
| :: (MonadBaseControl IO m, MonadThrow m, MonadUnsafeIO m, MonadIO m) | |
| => Manager | The HTTP connection manager to use. |
| -> Session | |
| -> Path | The full path (relative to your |
| -> WriteMode | |
| -> RequestBody m | The file contents. |
| -> m (Either ErrorMessage Meta) |
Constructors
| WriteModeAdd | If there is already a file at the specified path, rename the new file. |
| WriteModeUpdate FileRevision | Check that there is a file there with the given revision. If so, overwrite it. If not, rename the new file. |
| WriteModeForce | If there is already a file at the specified path, overwrite it. |
Common data types
type ErrorMessage = StringSource
data RequestBody m Source
Constructors
| RequestBody Int64 (Source (ResourceT m) ByteString) |
bsRequestBody :: MonadIO m => ByteString -> RequestBody mSource
Create a RequestBody from a single ByteString
bsSink :: Monad m => Sink ByteString m ByteStringSource
A Sink that reads in ByteString chunks and constructs one concatenated ByteString