module GitHub.Endpoints.Repos.Contents (
contentsForR,
readmeForR,
archiveForR,
createFileR,
updateFileR,
deleteFileR,
module GitHub.Data
) where
import GitHub.Data
import GitHub.Internal.Prelude
import Prelude ()
import Data.Maybe (maybeToList)
import qualified Data.Text.Encoding as TE
import Network.URI (URI)
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
readmeForR :: Name Owner -> Name Repo -> Request k Content
readmeForR user repo =
query ["repos", toPathPart user, toPathPart repo, "readme"] []
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
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)
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)
deleteFileR
:: Name Owner
-> Name Repo
-> DeleteFile
-> GenRequest 'MtUnit 'RW ()
deleteFileR user repo body =
Command Delete ["repos", toPathPart user, toPathPart repo, "contents", deleteFilePath body] (encode body)