git-lfs-1.1.0: git-lfs protocol

Safe HaskellNone
LanguageHaskell98

Network.GitLFS

Contents

Description

This implementation of the git-lfs API uses http Request and Response, but leaves actually connecting up the http client to the user.

You'll want to use a Manager that supports https, since the protocol uses http basic auth.

Some LFS servers, notably Github's, may require a User-Agent header in some of the requests, in order to allow eg, uploads. No such header is added by default, so be sure to add your own.

Synopsis

Transfer requests

data TransferRequest Source #

Instances
Show TransferRequest Source # 
Instance details

Defined in Network.GitLFS

Generic TransferRequest Source # 
Instance details

Defined in Network.GitLFS

Associated Types

type Rep TransferRequest :: Type -> Type #

ToJSON TransferRequest Source # 
Instance details

Defined in Network.GitLFS

FromJSON TransferRequest Source # 
Instance details

Defined in Network.GitLFS

type Rep TransferRequest Source # 
Instance details

Defined in Network.GitLFS

data TransferRequestObject Source #

startTransferRequest :: Endpoint -> TransferRequest -> Request Source #

Makes a Request that will start the process of making a transfer to or from the LFS endpoint.

Responses to transfer requests

data TransferResponse op Source #

Instances
Show op => Show (TransferResponse op) Source # 
Instance details

Defined in Network.GitLFS

Generic (TransferResponse op) Source # 
Instance details

Defined in Network.GitLFS

Associated Types

type Rep (TransferResponse op) :: Type -> Type #

IsTransferResponseOperation op => ToJSON (TransferResponse op) Source # 
Instance details

Defined in Network.GitLFS

IsTransferResponseOperation op => FromJSON (TransferResponse op) Source # 
Instance details

Defined in Network.GitLFS

type Rep (TransferResponse op) Source # 
Instance details

Defined in Network.GitLFS

type Rep (TransferResponse op) = D1 (MetaData "TransferResponse" "Network.GitLFS" "git-lfs-1.1.0-Ch1MpAt56bPGJKID18by7f" False) (C1 (MetaCons "TransferResponse" PrefixI True) (S1 (MetaSel (Just "transfer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe TransferAdapter)) :*: S1 (MetaSel (Just "objects") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TransferResponseOperation op])))

data TransferResponseOperation op Source #

Instances
Show op => Show (TransferResponseOperation op) Source # 
Instance details

Defined in Network.GitLFS

Generic (TransferResponseOperation op) Source # 
Instance details

Defined in Network.GitLFS

Associated Types

type Rep (TransferResponseOperation op) :: Type -> Type #

ToJSON op => ToJSON (TransferResponseOperation op) Source # 
Instance details

Defined in Network.GitLFS

FromJSON op => FromJSON (TransferResponseOperation op) Source # 
Instance details

Defined in Network.GitLFS

type Rep (TransferResponseOperation op) Source # 
Instance details

Defined in Network.GitLFS

class (FromJSON op, ToJSON op) => IsTransferResponseOperation op Source #

Class of types that can be responses to a transfer request, that contain an operation to use to make the transfer.

data UploadOperation Source #

data OperationParams Source #

Instances
Show OperationParams Source # 
Instance details

Defined in Network.GitLFS

Generic OperationParams Source # 
Instance details

Defined in Network.GitLFS

Associated Types

type Rep OperationParams :: Type -> Type #

ToJSON OperationParams Source # 
Instance details

Defined in Network.GitLFS

FromJSON OperationParams Source # 
Instance details

Defined in Network.GitLFS

type Rep OperationParams Source # 
Instance details

Defined in Network.GitLFS

parseTransferResponse :: IsTransferResponseOperation op => ByteString -> ParsedTransferResponse op Source #

Parse the body of a response to a transfer request.

Making transfers

downloadOperationRequest :: DownloadOperation -> Maybe Request Source #

Builds a http request to perform a download.

uploadOperationRequests :: UploadOperation -> RequestBody -> SHA256 -> Integer -> Maybe [Request] Source #

Builds http request to perform an upload. The content to upload is provided in the RequestBody, along with its SHA256 and size.

When the LFS server requested verification, there will be a second Request that does that; it should be run only after the upload has succeeded.

When the LFS server already contains the object, an empty list may be returned.

Endpoint discovery

data Endpoint Source #

The endpoint of a git-lfs server.

Instances
Show Endpoint Source # 
Instance details

Defined in Network.GitLFS

modifyEndpointRequest :: Endpoint -> (Request -> Request) -> Endpoint Source #

When an Endpoint is used to generate a Request, this allows adjusting that Request.

This can be used to add http basic authentication to an Endpoint:

modifyEndpointRequest (guessEndpoint u) (applyBasicAuth "user" "pass")

sshDiscoverEndpointCommand :: FilePath -> TransferRequestOperation -> [String] Source #

Command to run via ssh with to discover an endpoint. The FilePath is the location of the git repository on the ssh server.

Note that, when sshing to the server, you should take care that the hostname you pass to ssh is really a hostname and not something that ssh will parse an an option, such as -oProxyCommand=".

parseSshDiscoverEndpointResponse :: ByteString -> Maybe Endpoint Source #

Parse the json output when doing ssh endpoint discovery.

Errors

data TransferResponseError Source #

This is an error with a TransferRequest as a whole. It's also possible for a TransferRequest to overall succeed, but fail for some objects; such failures use TransferResponseObjectError.

Instances
Show TransferResponseError Source # 
Instance details

Defined in Network.GitLFS

Generic TransferResponseError Source # 
Instance details

Defined in Network.GitLFS

Associated Types

type Rep TransferResponseError :: Type -> Type #

ToJSON TransferResponseError Source # 
Instance details

Defined in Network.GitLFS

FromJSON TransferResponseError Source # 
Instance details

Defined in Network.GitLFS

type Rep TransferResponseError Source # 
Instance details

Defined in Network.GitLFS

type Rep TransferResponseError = D1 (MetaData "TransferResponseError" "Network.GitLFS" "git-lfs-1.1.0-Ch1MpAt56bPGJKID18by7f" False) (C1 (MetaCons "TransferResponseError" PrefixI True) (S1 (MetaSel (Just "resperr_message") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: (S1 (MetaSel (Just "resperr_request_id") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "resperr_documentation_url") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Url)))))

data TransferResponseObjectError Source #

An error with a single object within a TransferRequest.

Instances
Show TransferResponseObjectError Source # 
Instance details

Defined in Network.GitLFS

Generic TransferResponseObjectError Source # 
Instance details

Defined in Network.GitLFS

Associated Types

type Rep TransferResponseObjectError :: Type -> Type #

ToJSON TransferResponseObjectError Source # 
Instance details

Defined in Network.GitLFS

FromJSON TransferResponseObjectError Source # 
Instance details

Defined in Network.GitLFS

type Rep TransferResponseObjectError Source # 
Instance details

Defined in Network.GitLFS

type Rep TransferResponseObjectError = D1 (MetaData "TransferResponseObjectError" "Network.GitLFS" "git-lfs-1.1.0-Ch1MpAt56bPGJKID18by7f" False) (C1 (MetaCons "TransferResponseObjectError" PrefixI True) (S1 (MetaSel (Just "respobjerr_code") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "respobjerr_message") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

Additional data types

type Url = Text Source #

data GitRef Source #

Constructors

GitRef 

Fields

Instances
Show GitRef Source # 
Instance details

Defined in Network.GitLFS

Generic GitRef Source # 
Instance details

Defined in Network.GitLFS

Associated Types

type Rep GitRef :: Type -> Type #

Methods

from :: GitRef -> Rep GitRef x #

to :: Rep GitRef x -> GitRef #

ToJSON GitRef Source # 
Instance details

Defined in Network.GitLFS

FromJSON GitRef Source # 
Instance details

Defined in Network.GitLFS

type Rep GitRef Source # 
Instance details

Defined in Network.GitLFS

type Rep GitRef = D1 (MetaData "GitRef" "Network.GitLFS" "git-lfs-1.1.0-Ch1MpAt56bPGJKID18by7f" False) (C1 (MetaCons "GitRef" PrefixI True) (S1 (MetaSel (Just "name") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))