module GitHub.Endpoints.Repos.Contents (
contentsFor,
contentsFor',
contentsForR,
readmeFor,
readmeFor',
readmeForR,
archiveFor,
archiveFor',
archiveForR,
createFile,
createFileR,
updateFile,
updateFileR,
deleteFile,
deleteFileR,
module GitHub.Data
) where
import GitHub.Data
import GitHub.Internal.Prelude
import GitHub.Request
import Prelude ()
import Data.Maybe (maybeToList)
import qualified Data.Text.Encoding as TE
import Network.URI (URI)
contentsFor :: Name Owner -> Name Repo -> Text -> Maybe Text -> IO (Either Error Content)
contentsFor = contentsFor' Nothing
contentsFor' :: Maybe Auth -> Name Owner -> Name Repo -> Text -> Maybe Text -> IO (Either Error Content)
contentsFor' auth user repo path ref =
executeRequestMaybe auth $ contentsForR user repo path ref
contentsForR
:: Name Owner
-> Name Repo
-> Text
-> Maybe Text
-> Request k Content
contentsForR user repo path ref =
query ["repos", toPathPart user, toPathPart repo, "contents", path] qs
where
qs = maybe [] (\r -> [("ref", Just . TE.encodeUtf8 $ r)]) ref
readmeFor :: Name Owner -> Name Repo -> IO (Either Error Content)
readmeFor = readmeFor' Nothing
readmeFor' :: Maybe Auth -> Name Owner -> Name Repo -> IO (Either Error Content)
readmeFor' auth user repo =
executeRequestMaybe auth $ readmeForR user repo
readmeForR :: Name Owner -> Name Repo -> Request k Content
readmeForR user repo =
query ["repos", toPathPart user, toPathPart repo, "readme"] []
archiveFor :: Name Owner -> Name Repo -> ArchiveFormat -> Maybe Text -> IO (Either Error URI)
archiveFor = archiveFor' Nothing
archiveFor' :: Maybe Auth -> Name Owner -> Name Repo -> ArchiveFormat -> Maybe Text -> IO (Either Error URI)
archiveFor' auth user repo path ref =
executeRequestMaybe auth $ archiveForR user repo path ref
archiveForR
:: Name Owner
-> Name Repo
-> ArchiveFormat
-> Maybe Text
-> GenRequest 'MtRedirect rw URI
archiveForR user repo format ref = Query path []
where
path = ["repos", toPathPart user, toPathPart repo, toPathPart format] <> maybeToList ref
createFile
:: Auth
-> Name Owner
-> Name Repo
-> CreateFile
-> IO (Either Error ContentResult)
createFile auth user repo body =
executeRequest auth $ createFileR user repo body
createFileR
:: Name Owner
-> Name Repo
-> CreateFile
-> Request 'RW ContentResult
createFileR user repo body =
command Put ["repos", toPathPart user, toPathPart repo, "contents", createFilePath body] (encode body)
updateFile
:: Auth
-> Name Owner
-> Name Repo
-> UpdateFile
-> IO (Either Error ContentResult)
updateFile auth user repo body =
executeRequest auth $ updateFileR user repo body
updateFileR
:: Name Owner
-> Name Repo
-> UpdateFile
-> Request 'RW ContentResult
updateFileR user repo body =
command Put ["repos", toPathPart user, toPathPart repo, "contents", updateFilePath body] (encode body)
deleteFile
:: Auth
-> Name Owner
-> Name Repo
-> DeleteFile
-> IO (Either Error ())
deleteFile auth user repo body =
executeRequest auth $ deleteFileR user repo body
deleteFileR
:: Name Owner
-> Name Repo
-> DeleteFile
-> Request 'RW ()
deleteFileR user repo body =
command Delete ["repos", toPathPart user, toPathPart repo, "contents", deleteFilePath body] (encode body)