Safe Haskell | None |
---|
- s3Factory :: (MonadS3 m, MonadUnsafeIO m, MonadThrow m) => Maybe Text -> Text -> Text -> FilePath -> BackendCallbacks -> RepositoryFactory (ReaderT LgRepo (NoLoggingT m)) m LgRepo
- odbS3Backend :: (MonadS3 m, MonadUnsafeIO m, MonadThrow m) => S3Configuration NormalQuery -> Configuration -> Manager -> Text -> Text -> FilePath -> BackendCallbacks -> m (Ptr C'git_odb_backend)
- addS3Backend :: (MonadS3 m, MonadUnsafeIO m, MonadThrow m) => LgRepo -> Text -> Text -> Text -> Text -> Maybe Manager -> Maybe Text -> LogLevel -> FilePath -> BackendCallbacks -> m LgRepo
- data ObjectStatus
- data BackendCallbacks = BackendCallbacks {
- checkQuota :: ObjectLength -> IO (Maybe QuotaStatus)
- registerObject :: SHA -> Maybe (ObjectLength, ObjectType) -> IO ()
- registerPackFile :: Text -> [SHA] -> IO ()
- lookupObject :: SHA -> IO (Maybe ObjectStatus)
- getBucket :: MonadS3 m => Text -> Text -> ResourceT m (Maybe [Text])
- headObject :: MonadS3 m => Text -> Text -> ResourceT m (Maybe Bool)
- getObject :: MonadS3 m => Text -> Text -> Maybe (Int64, Int64) -> ResourceT m (Maybe (Either Text ByteString))
- putObject :: MonadS3 m => Text -> Text -> ObjectLength -> ByteString -> ResourceT m (Maybe (Either Text ()))
- updateRef :: RefName -> Text -> IO ()
- resolveRef :: RefName -> IO (Maybe Text)
- acquireLock :: Text -> IO Text
- releaseLock :: Text -> IO ()
- shuttingDown :: IO ()
- setException :: GitException -> IO ()
- newtype ObjectType = ObjectType {
- getObjectType :: Int
- newtype ObjectLength = ObjectLength {}
- data QuotaStatus
- data S3MockService
- s3MockService :: IO S3MockService
- mockGetBucket :: MonadS3 m => S3MockService -> Text -> Text -> m (Maybe [Text])
- mockHeadObject :: MonadS3 m => S3MockService -> Text -> Text -> m (Maybe Bool)
- mockGetObject :: MonadS3 m => S3MockService -> Text -> Text -> Maybe (Int64, Int64) -> m (Maybe (Either Text ByteString))
- mockPutObject :: MonadS3 m => S3MockService -> Text -> Text -> Int -> ByteString -> m (Maybe (Either Text ()))
Documentation
s3Factory :: (MonadS3 m, MonadUnsafeIO m, MonadThrow m) => Maybe Text -> Text -> Text -> FilePath -> BackendCallbacks -> RepositoryFactory (ReaderT LgRepo (NoLoggingT m)) m LgRepoSource
odbS3Backend :: (MonadS3 m, MonadUnsafeIO m, MonadThrow m) => S3Configuration NormalQuery -> Configuration -> Manager -> Text -> Text -> FilePath -> BackendCallbacks -> m (Ptr C'git_odb_backend)Source
:: (MonadS3 m, MonadUnsafeIO m, MonadThrow m) | |
=> LgRepo | |
-> Text | bucket |
-> Text | prefix |
-> Text | access key |
-> Text | secret key |
-> Maybe Manager | |
-> Maybe Text | mock address |
-> LogLevel | |
-> FilePath | |
-> BackendCallbacks | callbacks |
-> m LgRepo |
Given a repository object obtained from Libgit2, add an S3 backend to it, making it the primary store for objects associated with that repository.
data ObjectStatus Source
data BackendCallbacks Source
BackendCallbacks | |
|
newtype ObjectType Source
newtype ObjectLength Source
data S3MockService Source
mockGetBucket :: MonadS3 m => S3MockService -> Text -> Text -> m (Maybe [Text])Source
mockHeadObject :: MonadS3 m => S3MockService -> Text -> Text -> m (Maybe Bool)Source
mockGetObject :: MonadS3 m => S3MockService -> Text -> Text -> Maybe (Int64, Int64) -> m (Maybe (Either Text ByteString))Source
mockPutObject :: MonadS3 m => S3MockService -> Text -> Text -> Int -> ByteString -> m (Maybe (Either Text ()))Source