generated from tpl/purs
Compare commits
18 Commits
listForOrg
...
main
Author | SHA1 | Date | |
---|---|---|---|
10e3a78523 | |||
8a806e9064 | |||
2a4ee6482d | |||
df273eb635 | |||
5699ad5c54 | |||
2d932a22a0 | |||
487c4e9953 | |||
31171561b2 | |||
e13d2f3b8e | |||
d52674fad9 | |||
fc37992181 | |||
8e0009350d | |||
032ff8fa63 | |||
0bab60e1fb | |||
4dbc94624a | |||
bd2d3ff486 | |||
3fe42d78ff | |||
123b90c92f |
@ -1,6 +1,7 @@
|
||||
package:
|
||||
dependencies:
|
||||
- aff
|
||||
- arrays
|
||||
- effect
|
||||
- either
|
||||
- exceptions
|
||||
@ -9,8 +10,10 @@ package:
|
||||
- mmorph
|
||||
- newtype
|
||||
- node-buffer
|
||||
- parallel
|
||||
- prelude
|
||||
- simple-json
|
||||
- tailrec
|
||||
- transformers
|
||||
- tuples
|
||||
- typelevel-prelude
|
||||
@ -20,7 +23,7 @@ workspace:
|
||||
extra_packages:
|
||||
fetch:
|
||||
git: 'https://git.orionkindel.com/thunderstrike/purescript-fetch.git'
|
||||
ref: '01f505d'
|
||||
ref: 'd74d343'
|
||||
dependencies:
|
||||
- aff
|
||||
- aff-promise
|
||||
|
@ -1,6 +1,9 @@
|
||||
module Gitea.Config where
|
||||
|
||||
import Prelude
|
||||
|
||||
import Data.URL (URL)
|
||||
import Effect (Effect)
|
||||
import Gitea.Auth (Authenticated)
|
||||
|
||||
type Config = { baseURI :: URL, auth :: Authenticated }
|
||||
type Config = { logTrace :: String -> Effect Unit, log :: String -> Effect Unit, baseURI :: URL, auth :: Authenticated }
|
||||
|
@ -3,6 +3,9 @@ module Gitea.Error where
|
||||
import Prelude
|
||||
|
||||
import Control.Monad.Error.Class (class MonadThrow, throwError)
|
||||
import Data.Eq.Generic (genericEq)
|
||||
import Data.Generic.Rep (class Generic)
|
||||
import Data.Show.Generic (genericShow)
|
||||
import Effect.Aff.Class (class MonadAff)
|
||||
import HTTP.Response as HTTP
|
||||
import HTTP.Response as HTTP.Rep
|
||||
@ -13,6 +16,13 @@ data Error
|
||||
| ENotFound
|
||||
| EValidation { message :: String, url :: String }
|
||||
|
||||
derive instance Generic Error _
|
||||
instance Eq Error where
|
||||
eq = genericEq
|
||||
|
||||
instance Show Error where
|
||||
show = genericShow
|
||||
|
||||
guardStatusOk :: forall m. MonadThrow Error m => MonadAff m => HTTP.Response -> m Unit
|
||||
guardStatusOk rep = do
|
||||
status <- HTTP.Rep.status rep
|
||||
|
45
src/Gitea.HTTP.purs
Normal file
45
src/Gitea.HTTP.purs
Normal file
@ -0,0 +1,45 @@
|
||||
module Gitea.HTTP where
|
||||
|
||||
import Prelude
|
||||
|
||||
import Control.Monad.Error.Class (catchError)
|
||||
import Control.Monad.Reader (ask)
|
||||
import Data.ArrayBuffer.ArrayBuffer as ArrayBuffer
|
||||
import Data.Foldable (intercalate)
|
||||
import Data.Maybe (maybe)
|
||||
import Data.Tuple.Nested ((/\))
|
||||
import Data.URL as URL
|
||||
import Effect.Aff.Class (class MonadAff)
|
||||
import Effect.Class (liftEffect)
|
||||
import Gitea.Auth as Auth
|
||||
import Gitea.Trans (GiteaT(..))
|
||||
import HTTP (class Request)
|
||||
import HTTP as HTTP
|
||||
import HTTP.Header (Headers(..))
|
||||
import HTTP.Request (bodyToRaw, rawRequestBodySize, requestBody, requestHeaders, requestMethod, requestUrl)
|
||||
import HTTP.Response (Response)
|
||||
import HTTP.Response as Rep
|
||||
|
||||
fetch :: forall m a. MonadAff m => Request a => a -> GiteaT m Response
|
||||
fetch req = do
|
||||
{ logTrace, auth } <- ask
|
||||
method <- requestMethod req
|
||||
url <- requestUrl req
|
||||
reqHeaders <- requestHeaders req
|
||||
authHeaders <- liftEffect $ Auth.headers auth
|
||||
let headers = reqHeaders <> authHeaders
|
||||
|
||||
body <- requestBody req
|
||||
rawBody <- bodyToRaw body
|
||||
bodySize <- liftEffect $ maybe (pure 0) rawRequestBodySize rawBody
|
||||
|
||||
liftEffect $ logTrace $ intercalate " " $ [ show method, show bodySize <> "b", URL.toString url ]
|
||||
|
||||
rep <- HTTP.fetch $ method /\ url /\ body /\ headers
|
||||
|
||||
status <- Rep.status rep
|
||||
statusText <- Rep.statusText rep
|
||||
repBodyDebug <- catchError (Rep.text =<< Rep.clone rep) (const $ map ((_ <> "b") <<< show <<< ArrayBuffer.byteLength) $ flip bind Rep.arrayBuffer $ Rep.clone rep)
|
||||
liftEffect $ logTrace $ intercalate " " $ [ show status, statusText, repBodyDebug ]
|
||||
|
||||
pure rep
|
@ -8,24 +8,30 @@ import Data.URL (URL, (/))
|
||||
import Effect.Aff.Class (class MonadAff)
|
||||
import Gitea.Auth as Auth
|
||||
import Gitea.Error as Error
|
||||
import Gitea.HTTP (fetch) as HTTP
|
||||
import Gitea.Trans (GiteaT)
|
||||
import Gitea.Types (BranchProtection, BranchProtectionName(..), BranchProtectionUpdate, RepoName(..), Username(..))
|
||||
import HTTP (Method(..), fetch) as HTTP
|
||||
import Gitea.Types (BranchProtection, BranchProtectionName(..), BranchProtectionUpdate, RepoName(..), Username(..), BranchProtectionCreate)
|
||||
import HTTP (Method(..)) as HTTP
|
||||
import HTTP.Request (json) as HTTP
|
||||
import Simple.JSON (class WriteForeign)
|
||||
import Type.Row.Subset (class Subset)
|
||||
|
||||
branchProtectionURL :: forall m. Monad m => Username -> RepoName -> GiteaT m URL
|
||||
branchProtectionURL (Username owner) (RepoName repo) = (\{ baseURI } -> baseURI / "repos" / owner / repo) <$> ask
|
||||
branchProtectionURL (Username owner) (RepoName repo) = (\{ baseURI } -> baseURI / "repos" / owner / repo / "branch_protections") <$> ask
|
||||
|
||||
branchProtectionOneURL :: forall m. Monad m => Username -> RepoName -> BranchProtectionName -> GiteaT m URL
|
||||
branchProtectionOneURL (Username owner) (RepoName repo) (BranchProtectionName rule) = (\{ baseURI } -> baseURI / "repos" / owner / repo / "branch_protections" / rule) <$> ask
|
||||
branchProtectionOneURL o r (BranchProtectionName rule) = (\base -> base / rule) <$> branchProtectionURL o r
|
||||
|
||||
get :: forall m. MonadAff m => Username -> RepoName -> BranchProtectionName -> GiteaT m (Record BranchProtection)
|
||||
get u r b = do
|
||||
{ auth } <- ask
|
||||
url <- branchProtectionOneURL u r b
|
||||
rep <- HTTP.fetch $ HTTP.GET /\ url /\ Auth.headers auth
|
||||
rep <- HTTP.fetch $ HTTP.GET /\ url
|
||||
Error.tryGetRepJSON rep
|
||||
|
||||
list :: forall m. MonadAff m => Username -> RepoName -> GiteaT m (Array (Record BranchProtection))
|
||||
list u r = do
|
||||
url <- branchProtectionURL u r
|
||||
rep <- HTTP.fetch $ HTTP.GET /\ url
|
||||
Error.tryGetRepJSON rep
|
||||
|
||||
update
|
||||
@ -39,14 +45,18 @@ update
|
||||
-> Record patch
|
||||
-> GiteaT m (Record BranchProtection)
|
||||
update u r b patch = do
|
||||
{ auth } <- ask
|
||||
url <- branchProtectionOneURL u r b
|
||||
rep <- HTTP.fetch $ HTTP.PATCH /\ url /\ HTTP.json patch /\ Auth.headers auth
|
||||
rep <- HTTP.fetch $ HTTP.PATCH /\ url /\ HTTP.json patch
|
||||
Error.tryGetRepJSON rep
|
||||
|
||||
delete :: forall m. MonadAff m => Username -> RepoName -> BranchProtectionName -> GiteaT m Unit
|
||||
delete u r b = do
|
||||
{ auth } <- ask
|
||||
url <- branchProtectionOneURL u r b
|
||||
rep <- HTTP.fetch $ HTTP.DELETE /\ url /\ Auth.headers auth
|
||||
rep <- HTTP.fetch $ HTTP.DELETE /\ url
|
||||
Error.guardStatusOk rep
|
||||
|
||||
create :: forall m. MonadAff m => Username -> RepoName -> Record BranchProtectionCreate -> GiteaT m (Record BranchProtection)
|
||||
create u r new = do
|
||||
url <- branchProtectionURL u r
|
||||
rep <- HTTP.fetch $ HTTP.POST /\ url /\ HTTP.json new
|
||||
Error.tryGetRepJSON rep
|
||||
|
@ -10,7 +10,8 @@ import Gitea.Auth as Auth
|
||||
import Gitea.Error as Error
|
||||
import Gitea.Trans (GiteaT)
|
||||
import Gitea.Types (RepoName(..), SecretName(..), Username(..))
|
||||
import HTTP (Method(..), fetch) as HTTP
|
||||
import Gitea.HTTP (fetch) as HTTP
|
||||
import HTTP (Method(..)) as HTTP
|
||||
import HTTP.Request (json) as HTTP
|
||||
|
||||
secretsURL :: forall m. Monad m => Username -> RepoName -> SecretName -> GiteaT m URL
|
||||
@ -18,14 +19,12 @@ secretsURL (Username owner) (RepoName repo) (SecretName secret) = (\{ baseURI }
|
||||
|
||||
set :: forall m. MonadAff m => Username -> RepoName -> SecretName -> String -> GiteaT m Unit
|
||||
set u r s sv = do
|
||||
{ auth } <- ask
|
||||
url <- secretsURL u r s
|
||||
rep <- HTTP.fetch $ HTTP.PUT /\ url /\ HTTP.json { "data": sv } /\ Auth.headers auth
|
||||
rep <- HTTP.fetch $ HTTP.PUT /\ url /\ HTTP.json { "data": sv }
|
||||
Error.guardStatusOk rep
|
||||
|
||||
remove :: forall m. MonadAff m => Username -> RepoName -> SecretName -> GiteaT m Unit
|
||||
remove u r s = do
|
||||
{ auth } <- ask
|
||||
url <- secretsURL u r s
|
||||
rep <- HTTP.fetch $ HTTP.DELETE /\ url /\ Auth.headers auth
|
||||
rep <- HTTP.fetch $ HTTP.DELETE /\ url
|
||||
Error.guardStatusOk rep
|
||||
|
@ -1,22 +1,21 @@
|
||||
-- GET /orgs/{org}/repos
|
||||
-- GET /repos/{owner}/{repo}/topics
|
||||
-- PUT /repos/{owner}/{repo}/topics/{topic}
|
||||
-- DELETE /repos/{owner}/{repo}/topics/{topic}
|
||||
|
||||
module Gitea.Repo where
|
||||
|
||||
import Prelude hiding ((/))
|
||||
|
||||
import Control.Monad.Reader (ask)
|
||||
import Control.Monad.Rec.Class (class MonadRec, Step(..), tailRecM)
|
||||
import Data.Array as Array
|
||||
import Data.Tuple.Nested ((/\))
|
||||
import Data.URL (URL, (/))
|
||||
import Data.URL (URL, (/), (?), (&))
|
||||
import Data.URL as URL
|
||||
import Effect.Aff.Class (class MonadAff)
|
||||
import Effect.Class (liftEffect)
|
||||
import Gitea.Auth as Auth
|
||||
import Gitea.Error as Error
|
||||
import Gitea.Trans (GiteaT)
|
||||
import Gitea.Types (Repo, RepoName(..), Username(..), RepoUpdate)
|
||||
import HTTP (Method(..), fetch) as HTTP
|
||||
import Gitea.Types (OrgName(..), Repo, RepoName(..), RepoUpdate, TopicName(..), Username(..))
|
||||
import Gitea.HTTP (fetch) as HTTP
|
||||
import HTTP (Method(..)) as HTTP
|
||||
import HTTP.Request (json) as HTTP
|
||||
import Node.Buffer (Buffer)
|
||||
import Node.Buffer as Buffer
|
||||
@ -25,15 +24,47 @@ import Simple.JSON (class WriteForeign)
|
||||
import Type.Row.Subset (class Subset)
|
||||
|
||||
reposURL :: forall m. Monad m => Username -> RepoName -> GiteaT m URL
|
||||
reposURL (Username owner) (RepoName repo) = (\{ baseURI } -> baseURI / "repos" / owner / repo) <$> ask
|
||||
reposURL (Username owner) (RepoName repo) =
|
||||
let
|
||||
build { baseURI } = baseURI / "repos" / owner / repo
|
||||
in
|
||||
build <$> ask
|
||||
|
||||
repoTopicsPageURL :: forall m. Monad m => Username -> RepoName -> { page :: Int, limit :: Int } -> GiteaT m URL
|
||||
repoTopicsPageURL o repo { page, limit } = (\repos -> repos / "topics" ? "limit" /\ show limit & "page" /\ show page) <$> reposURL o repo
|
||||
|
||||
repoTopicsURL :: forall m. Monad m => Username -> RepoName -> GiteaT m URL
|
||||
repoTopicsURL o repo = (\repos -> repos / "topics") <$> reposURL o repo
|
||||
|
||||
repoTopicsOneURL :: forall m. Monad m => Username -> RepoName -> TopicName -> GiteaT m URL
|
||||
repoTopicsOneURL o repo (TopicName topic) = (\repos -> repos / "topics" / topic) <$> reposURL o repo
|
||||
|
||||
orgReposURL :: forall m. Monad m => OrgName -> { page :: Int, limit :: Int } -> GiteaT m URL
|
||||
orgReposURL (OrgName org) { page, limit } = (\{ baseURI } -> baseURI / "orgs" / org / "repos" ? "limit" /\ show limit & "page" /\ show page) <$> ask
|
||||
|
||||
get :: forall m. MonadAff m => Username -> RepoName -> GiteaT m (Record Repo)
|
||||
get u r = do
|
||||
{ auth } <- ask
|
||||
url <- reposURL u r
|
||||
rep <- HTTP.fetch $ HTTP.GET /\ url /\ Auth.headers auth
|
||||
get owner repo = do
|
||||
url <- reposURL owner repo
|
||||
rep <- HTTP.fetch $ HTTP.GET /\ url
|
||||
Error.tryGetRepJSON rep
|
||||
|
||||
listForOrg :: forall m. MonadAff m => MonadRec m => OrgName -> GiteaT m (Array (Record Repo))
|
||||
listForOrg o =
|
||||
let
|
||||
limit = 10
|
||||
|
||||
maybeFetchMore repos n newRepos
|
||||
| Array.length newRepos < limit = Done $ repos <> newRepos
|
||||
| otherwise = Loop $ (repos <> newRepos) /\ (n + 1)
|
||||
paginate (repos /\ n) = maybeFetchMore repos n <$> getPage n
|
||||
|
||||
getPage n = do
|
||||
url <- orgReposURL o { limit, page: n }
|
||||
rep <- HTTP.fetch $ HTTP.GET /\ url
|
||||
Error.tryGetRepJSON rep
|
||||
in
|
||||
tailRecM paginate ([] /\ 1)
|
||||
|
||||
update
|
||||
:: forall m patch
|
||||
. MonadAff m
|
||||
@ -43,30 +74,63 @@ update
|
||||
-> RepoName
|
||||
-> Record patch
|
||||
-> GiteaT m (Record Repo)
|
||||
update u r patch = do
|
||||
{ auth } <- ask
|
||||
url <- reposURL u r
|
||||
rep <- HTTP.fetch $ HTTP.PATCH /\ url /\ HTTP.json patch /\ Auth.headers auth
|
||||
update owner repo patch = do
|
||||
url <- reposURL owner repo
|
||||
rep <- HTTP.fetch $ HTTP.PATCH /\ url /\ HTTP.json patch
|
||||
Error.tryGetRepJSON rep
|
||||
|
||||
delete :: forall m. MonadAff m => Username -> RepoName -> GiteaT m Unit
|
||||
delete u r = do
|
||||
{ auth } <- ask
|
||||
url <- reposURL u r
|
||||
rep <- HTTP.fetch $ HTTP.DELETE /\ url /\ Auth.headers auth
|
||||
delete owner repo = do
|
||||
url <- reposURL owner repo
|
||||
rep <- HTTP.fetch $ HTTP.DELETE /\ url
|
||||
Error.guardStatusOk rep
|
||||
|
||||
updateAvatar :: forall m. MonadAff m => Username -> RepoName -> Buffer -> GiteaT m Unit
|
||||
updateAvatar u r av = do
|
||||
{ auth } <- ask
|
||||
url <- map (_ / "avatar") $ reposURL u r
|
||||
b64 <- liftEffect $ Buffer.toString Base64 av
|
||||
rep <- HTTP.fetch $ HTTP.POST /\ url /\ HTTP.json { image: b64 } /\ Auth.headers auth
|
||||
updateAvatar owner repo avatar = do
|
||||
url <- map (_ / "avatar") $ reposURL owner repo
|
||||
b64 <- liftEffect $ Buffer.toString Base64 avatar
|
||||
rep <- HTTP.fetch $ HTTP.POST /\ url /\ HTTP.json { image: b64 }
|
||||
Error.guardStatusOk rep
|
||||
|
||||
removeAvatar :: forall m. MonadAff m => Username -> RepoName -> GiteaT m Unit
|
||||
removeAvatar u r = do
|
||||
{ auth } <- ask
|
||||
url <- map (_ / "avatar") $ reposURL u r
|
||||
rep <- HTTP.fetch $ HTTP.DELETE /\ url /\ Auth.headers auth
|
||||
removeAvatar owner repo = do
|
||||
url <- map (_ / "avatar") $ reposURL owner repo
|
||||
rep <- HTTP.fetch $ HTTP.DELETE /\ url
|
||||
Error.guardStatusOk rep
|
||||
|
||||
addTopic :: forall m. MonadAff m => Username -> RepoName -> TopicName -> GiteaT m Unit
|
||||
addTopic owner repo topic = do
|
||||
url <- repoTopicsOneURL owner repo topic
|
||||
rep <- HTTP.fetch $ HTTP.PUT /\ url
|
||||
Error.guardStatusOk rep
|
||||
|
||||
getTopics :: forall m. MonadAff m => MonadRec m => Username -> RepoName -> GiteaT m (Array TopicName)
|
||||
getTopics owner repo =
|
||||
let
|
||||
limit = 10
|
||||
|
||||
maybeFetchMore topics n newTopics
|
||||
| Array.length newTopics < limit = Done $ topics <> newTopics
|
||||
| otherwise = Loop $ (topics <> newTopics) /\ (n + 1)
|
||||
|
||||
paginate (topics /\ n) = maybeFetchMore topics n <$> getPage n
|
||||
|
||||
getPage n = do
|
||||
url <- repoTopicsPageURL owner repo { limit, page: n }
|
||||
rep <- HTTP.fetch $ HTTP.GET /\ url
|
||||
{ topics } <- Error.tryGetRepJSON @{ topics :: Array TopicName } rep
|
||||
pure topics
|
||||
in
|
||||
tailRecM paginate ([] /\ 1)
|
||||
|
||||
removeTopic :: forall m. MonadAff m => Username -> RepoName -> TopicName -> GiteaT m Unit
|
||||
removeTopic owner repo topic = do
|
||||
url <- repoTopicsOneURL owner repo topic
|
||||
rep <- HTTP.fetch $ HTTP.DELETE /\ url
|
||||
Error.guardStatusOk rep
|
||||
|
||||
setTopics :: forall m. MonadAff m => Username -> RepoName -> Array TopicName -> GiteaT m Unit
|
||||
setTopics owner repo topics = do
|
||||
url <- repoTopicsURL owner repo
|
||||
rep <- HTTP.fetch $ HTTP.PUT /\ url /\ HTTP.json { topics }
|
||||
Error.guardStatusOk rep
|
||||
|
@ -2,12 +2,16 @@ module Gitea.Trans where
|
||||
|
||||
import Prelude
|
||||
|
||||
import Control.Monad.Error.Class (class MonadError, class MonadThrow, throwError)
|
||||
import Control.Monad.Error.Class (class MonadError, class MonadThrow, liftEither, throwError)
|
||||
import Control.Monad.Except (ExceptT, runExceptT)
|
||||
import Control.Monad.Morph (class MFunctor, class MMonad, embed, hoist)
|
||||
import Control.Monad.Reader (class MonadAsk, class MonadReader, ReaderT(..), ask, runReaderT)
|
||||
import Control.Monad.Rec.Class (class MonadRec)
|
||||
import Control.Monad.Trans.Class (class MonadTrans, lift)
|
||||
import Control.Parallel (class Parallel, parallel, sequential)
|
||||
import Data.Bifunctor (lmap)
|
||||
import Data.Either (Either)
|
||||
import Data.Functor.Compose (Compose(..))
|
||||
import Data.Newtype (class Newtype, unwrap, wrap)
|
||||
import Effect.Aff.Class (class MonadAff)
|
||||
import Effect.Class (class MonadEffect)
|
||||
@ -15,6 +19,14 @@ import Effect.Exception as Effect.Exception
|
||||
import Gitea.Config (Config)
|
||||
import Gitea.Error as Gitea.Error
|
||||
|
||||
newtype GiteaParT :: (Type -> Type) -> Type -> Type
|
||||
newtype GiteaParT m a = GiteaParT (ReaderT Config (Compose m (Either Gitea.Error.Error)) a)
|
||||
|
||||
derive instance Newtype (GiteaParT m a) _
|
||||
derive newtype instance Functor m => Functor (GiteaParT m)
|
||||
derive newtype instance Apply m => Apply (GiteaParT m)
|
||||
derive newtype instance Applicative m => Applicative (GiteaParT m)
|
||||
|
||||
newtype GiteaT :: (Type -> Type) -> Type -> Type
|
||||
newtype GiteaT m a = GiteaT (ReaderT Config (ExceptT Gitea.Error.Error m) a)
|
||||
|
||||
@ -39,6 +51,10 @@ derive newtype instance MonadEffect m => MonadEffect (GiteaT m)
|
||||
derive newtype instance MonadAff m => MonadAff (GiteaT m)
|
||||
derive newtype instance Monad m => MonadError Gitea.Error.Error (GiteaT m)
|
||||
derive newtype instance Monad m => MonadThrow Gitea.Error.Error (GiteaT m)
|
||||
derive newtype instance MonadRec m => MonadRec (GiteaT m)
|
||||
instance (Parallel f m, Monad m) => Parallel (GiteaParT f) (GiteaT m) where
|
||||
parallel m = wrap $ parallel $ unwrap m
|
||||
sequential f = wrap $ sequential $ unwrap f
|
||||
|
||||
derive newtype instance Monad m => Functor (GiteaT m)
|
||||
derive newtype instance Monad m => Apply (GiteaT m)
|
||||
@ -47,3 +63,8 @@ derive newtype instance Monad m => Bind (GiteaT m)
|
||||
|
||||
runGitea :: forall m a. Config -> GiteaT m a -> m (Either Gitea.Error.Error a)
|
||||
runGitea config m = runExceptT $ runReaderT (unwrap m) config
|
||||
|
||||
runGiteaE :: forall m a. MonadThrow Effect.Exception.Error m => Config -> GiteaT m a -> m a
|
||||
runGiteaE config m = do
|
||||
e <- runGitea config m
|
||||
liftEither $ lmap (Effect.Exception.error <<< show) e
|
@ -2,6 +2,7 @@ module Gitea.Types where
|
||||
|
||||
import Prelude
|
||||
|
||||
import Data.Maybe (Maybe)
|
||||
import Data.Newtype (class Newtype)
|
||||
import Foreign.Object (Object)
|
||||
import Simple.JSON (class ReadForeign, class WriteForeign)
|
||||
@ -13,14 +14,34 @@ newtype RepoName = RepoName String
|
||||
|
||||
derive instance Newtype RepoName _
|
||||
derive newtype instance Eq RepoName
|
||||
derive newtype instance Ord RepoName
|
||||
derive newtype instance Show RepoName
|
||||
derive newtype instance WriteForeign RepoName
|
||||
derive newtype instance ReadForeign RepoName
|
||||
|
||||
newtype TopicName = TopicName String
|
||||
|
||||
derive instance Newtype TopicName _
|
||||
derive newtype instance Eq TopicName
|
||||
derive newtype instance Ord TopicName
|
||||
derive newtype instance Show TopicName
|
||||
derive newtype instance WriteForeign TopicName
|
||||
derive newtype instance ReadForeign TopicName
|
||||
|
||||
newtype OrgName = OrgName String
|
||||
|
||||
derive instance Newtype OrgName _
|
||||
derive newtype instance Eq OrgName
|
||||
derive newtype instance Ord OrgName
|
||||
derive newtype instance Show OrgName
|
||||
derive newtype instance WriteForeign OrgName
|
||||
derive newtype instance ReadForeign OrgName
|
||||
|
||||
newtype TagName = TagName String
|
||||
|
||||
derive instance Newtype TagName _
|
||||
derive newtype instance Eq TagName
|
||||
derive newtype instance Ord TagName
|
||||
derive newtype instance Show TagName
|
||||
derive newtype instance WriteForeign TagName
|
||||
derive newtype instance ReadForeign TagName
|
||||
@ -29,6 +50,7 @@ newtype CommitId = CommitId String
|
||||
|
||||
derive instance Newtype CommitId _
|
||||
derive newtype instance Eq CommitId
|
||||
derive newtype instance Ord CommitId
|
||||
derive newtype instance Show CommitId
|
||||
derive newtype instance WriteForeign CommitId
|
||||
derive newtype instance ReadForeign CommitId
|
||||
@ -37,6 +59,7 @@ newtype BranchName = BranchName String
|
||||
|
||||
derive instance Newtype BranchName _
|
||||
derive newtype instance Eq BranchName
|
||||
derive newtype instance Ord BranchName
|
||||
derive newtype instance Show BranchName
|
||||
derive newtype instance WriteForeign BranchName
|
||||
derive newtype instance ReadForeign BranchName
|
||||
@ -45,6 +68,7 @@ newtype BranchProtectionName = BranchProtectionName String
|
||||
|
||||
derive instance Newtype BranchProtectionName _
|
||||
derive newtype instance Eq BranchProtectionName
|
||||
derive newtype instance Ord BranchProtectionName
|
||||
derive newtype instance Show BranchProtectionName
|
||||
derive newtype instance WriteForeign BranchProtectionName
|
||||
derive newtype instance ReadForeign BranchProtectionName
|
||||
@ -53,6 +77,7 @@ newtype TeamName = TeamName String
|
||||
|
||||
derive instance Newtype TeamName _
|
||||
derive newtype instance Eq TeamName
|
||||
derive newtype instance Ord TeamName
|
||||
derive newtype instance Show TeamName
|
||||
derive newtype instance WriteForeign TeamName
|
||||
derive newtype instance ReadForeign TeamName
|
||||
@ -61,6 +86,7 @@ newtype SecretName = SecretName String
|
||||
|
||||
derive instance Newtype SecretName _
|
||||
derive newtype instance Eq SecretName
|
||||
derive newtype instance Ord SecretName
|
||||
derive newtype instance Show SecretName
|
||||
derive newtype instance WriteForeign SecretName
|
||||
derive newtype instance ReadForeign SecretName
|
||||
@ -69,6 +95,7 @@ newtype RepoId = RepoId Int
|
||||
|
||||
derive instance Newtype RepoId _
|
||||
derive newtype instance Eq RepoId
|
||||
derive newtype instance Ord RepoId
|
||||
derive newtype instance Show RepoId
|
||||
derive newtype instance WriteForeign RepoId
|
||||
derive newtype instance ReadForeign RepoId
|
||||
@ -77,6 +104,7 @@ newtype Username = Username String
|
||||
|
||||
derive instance Newtype Username _
|
||||
derive newtype instance Eq Username
|
||||
derive newtype instance Ord Username
|
||||
derive newtype instance Show Username
|
||||
derive newtype instance WriteForeign Username
|
||||
derive newtype instance ReadForeign Username
|
||||
@ -85,6 +113,7 @@ newtype UserId = UserId Int
|
||||
|
||||
derive instance Newtype UserId _
|
||||
derive newtype instance Eq UserId
|
||||
derive newtype instance Ord UserId
|
||||
derive newtype instance Show UserId
|
||||
derive newtype instance WriteForeign UserId
|
||||
derive newtype instance ReadForeign UserId
|
||||
@ -93,6 +122,7 @@ newtype OrgId = OrgId Int
|
||||
|
||||
derive instance Newtype OrgId _
|
||||
derive newtype instance Eq OrgId
|
||||
derive newtype instance Ord OrgId
|
||||
derive newtype instance Show OrgId
|
||||
derive newtype instance WriteForeign OrgId
|
||||
derive newtype instance ReadForeign OrgId
|
||||
@ -101,6 +131,7 @@ newtype TeamId = TeamId Int
|
||||
|
||||
derive instance Newtype TeamId _
|
||||
derive newtype instance Eq TeamId
|
||||
derive newtype instance Ord TeamId
|
||||
derive newtype instance Show TeamId
|
||||
derive newtype instance WriteForeign TeamId
|
||||
derive newtype instance ReadForeign TeamId
|
||||
@ -219,22 +250,15 @@ type RepoSectionVisibilityImmutable r =
|
||||
type RepoSectionProfileMutable r =
|
||||
( "avatar_url" :: String
|
||||
, "description" :: String
|
||||
, "language" :: String
|
||||
, "languages_url" :: String
|
||||
, "link" :: String
|
||||
, "original_url" :: String
|
||||
, "website" :: String
|
||||
| r
|
||||
)
|
||||
|
||||
type RepoSectionProfileImmutable r =
|
||||
( "avatar_url" :: String
|
||||
, "description" :: String
|
||||
, "language" :: String
|
||||
( "language" :: String
|
||||
, "languages_url" :: String
|
||||
, "link" :: String
|
||||
, "original_url" :: String
|
||||
, "website" :: String
|
||||
| r
|
||||
)
|
||||
|
||||
@ -251,7 +275,7 @@ type RepoGiteaSettingsMutable r =
|
||||
|
||||
type RepoSectionGiteaStatsMutable r =
|
||||
( "template" :: Boolean
|
||||
, "external_wiki" :: RepoExternalWiki
|
||||
, "external_wiki" :: Maybe RepoExternalWiki
|
||||
| r
|
||||
)
|
||||
|
||||
@ -264,13 +288,13 @@ type RepoSectionGiteaStatsImmutable r =
|
||||
, "watchers_count" :: Int
|
||||
, "fork" :: Boolean
|
||||
, "forks_count" :: Int
|
||||
, "repo_transfer" :: RepoTransfer
|
||||
, "repo_transfer" :: Maybe RepoTransfer
|
||||
| r
|
||||
)
|
||||
|
||||
type RepoMeta =
|
||||
{ "id" :: RepoId
|
||||
, "owner" :: String
|
||||
, "owner" :: Username
|
||||
, "name" :: RepoName
|
||||
, "full_name" :: String
|
||||
}
|
||||
@ -295,8 +319,8 @@ type RepoSectionStatsImmutable r =
|
||||
)
|
||||
|
||||
type RepoSectionTrackerMutable r =
|
||||
( "external_tracker" :: RepoExternalTracker
|
||||
, "internal_tracker" :: RepoInternalTracker
|
||||
( "external_tracker" :: Maybe RepoExternalTracker
|
||||
, "internal_tracker" :: Maybe RepoInternalTracker
|
||||
| r
|
||||
)
|
||||
|
||||
@ -315,6 +339,8 @@ type Repo =
|
||||
+ RepoGiteaSettingsMutable
|
||||
+ RepoPermsMutable
|
||||
+ RepoPermsImmutable
|
||||
+ RepoSectionProfileMutable
|
||||
+ RepoSectionProfileImmutable
|
||||
+ RepoSectionVisibilityMutable
|
||||
+ RepoSectionVisibilityImmutable
|
||||
+ RepoSectionMergeSettingsMutable ()
|
||||
@ -326,6 +352,7 @@ type RepoUpdate =
|
||||
+ RepoSectionGiteaStatsMutable
|
||||
+ RepoGiteaSettingsMutable
|
||||
+ RepoPermsMutable
|
||||
+ RepoSectionProfileMutable
|
||||
+ RepoSectionVisibilityMutable
|
||||
+ RepoSectionMergeSettingsMutable ()
|
||||
)
|
||||
@ -364,7 +391,7 @@ type Branch =
|
||||
, "name" :: String
|
||||
, "protected" :: Boolean
|
||||
, "required_approvals" :: Int
|
||||
, "status_check_contexts" :: Array String
|
||||
, "status_check_contexts" :: Maybe (Array String)
|
||||
, "user_can_merge" :: Boolean
|
||||
, "user_can_push" :: Boolean
|
||||
}
|
||||
@ -375,22 +402,22 @@ type BranchProtectionMutable r =
|
||||
, "block_on_official_review_requests" :: Boolean
|
||||
, "block_on_outdated_branch" :: Boolean
|
||||
, "block_on_rejected_reviews" :: Boolean
|
||||
, "branch_name" :: String
|
||||
, "branch_name" :: BranchName
|
||||
, "dismiss_stale_approvals" :: Boolean
|
||||
, "enable_approvals_whitelist" :: Boolean
|
||||
, "enable_merge_whitelist" :: Boolean
|
||||
, "enable_push" :: Boolean
|
||||
, "enable_push_whitelist" :: Boolean
|
||||
, "enable_status_check" :: Boolean
|
||||
, "merge_whitelist_teams" :: Array String
|
||||
, "merge_whitelist_teams" :: Array TeamName
|
||||
, "merge_whitelist_usernames" :: Array String
|
||||
, "protected_file_patterns" :: String
|
||||
, "push_whitelist_deploy_keys" :: Boolean
|
||||
, "push_whitelist_teams" :: Array String
|
||||
, "push_whitelist_teams" :: Array TeamName
|
||||
, "push_whitelist_usernames" :: Array String
|
||||
, "require_signed_commits" :: Boolean
|
||||
, "required_approvals" :: Int
|
||||
, "status_check_contexts" :: Array String
|
||||
, "status_check_contexts" :: Maybe (Array String)
|
||||
, "unprotected_file_patterns" :: String
|
||||
| r
|
||||
)
|
||||
@ -406,5 +433,6 @@ type BranchProtectionImmutable r =
|
||||
| r
|
||||
)
|
||||
|
||||
type BranchProtectionCreate = (BranchProtectionMutable + BranchProtectionMutableOnCreate ())
|
||||
type BranchProtectionUpdate = BranchProtectionMutable ()
|
||||
type BranchProtection = (BranchProtectionMutable + BranchProtectionImmutable + BranchProtectionMutableOnCreate ())
|
Loading…
Reference in New Issue
Block a user