File: Repos.hs

package info (click to toggle)
haskell-github 0.8-1
  • links: PTS, VCS
  • area: main
  • in suites: jessie, jessie-kfreebsd
  • size: 444 kB
  • sloc: haskell: 2,572; makefile: 2
file content (285 lines) | stat: -rw-r--r-- 10,141 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE CPP #-}
-- | The Github Repos API, as documented at
-- <http://developer.github.com/v3/repos/>
module Github.Repos (

-- * Querying repositories
 userRepos
,userRepos'
,userRepo
,userRepo'
,organizationRepos
,organizationRepos'
,organizationRepo
,organizationRepo'
,contributors
,contributorsWithAnonymous
,languagesFor
,tagsFor
,branchesFor
,module Github.Data
,RepoPublicity(..)

-- * Modifying repositories
-- |
-- Only authenticated users may modify repositories.
,GithubAuth(..)

-- ** Create
,createRepo
,createOrganizationRepo
,newRepo
,NewRepo(..)

-- ** Edit
,editRepo
,def
,Edit(..)

-- ** Delete
,deleteRepo
) where

import Data.Default
import Data.Aeson.Types
import Github.Data
import Github.Private
import Network.HTTP.Conduit
import Control.Applicative
import qualified Control.Exception as E
import Network.HTTP.Types

-- | Filter the list of the user's repos using any of these constructors.
data RepoPublicity =
    All     -- ^ All repos accessible to the user.
  | Owner   -- ^ Only repos owned by the user.
  | Public  -- ^ Only public repos.
  | Private -- ^ Only private repos.
  | Member  -- ^ Only repos to which the user is a member but not an owner.
 deriving (Show, Eq)

-- | The repos for a user, by their login. Can be restricted to just repos they
-- own, are a member of, or publicize. Private repos are currently not
-- supported.
--
-- > userRepos "mike-burns" All
userRepos :: String -> RepoPublicity -> IO (Either Error [Repo])
userRepos = userRepos' Nothing

-- | The repos for a user, by their login.
-- | With authentication, but note that private repos are currently not supported.
--
-- > userRepos' (Just (GithubUser (user, password))) "mike-burns" All
userRepos' :: Maybe GithubAuth -> String -> RepoPublicity -> IO (Either Error [Repo])
userRepos' auth userName All =
  githubGetWithQueryString' auth ["users", userName, "repos"] "type=all"
userRepos' auth userName Owner =
  githubGetWithQueryString' auth ["users", userName, "repos"] "type=owner"
userRepos' auth userName Member =
  githubGetWithQueryString' auth ["users", userName, "repos"] "type=member"
userRepos' auth userName Public =
  githubGetWithQueryString' auth ["users", userName, "repos"] "type=public"
userRepos' _auth _userName Private =
  return $ Left $ UserError "Cannot access private repos using userRepos"

-- | The repos for an organization, by the organization name.
--
-- > organizationRepos "thoughtbot"
organizationRepos :: String -> IO (Either Error [Repo])
organizationRepos = organizationRepos' Nothing

-- | The repos for an organization, by the organization name.
-- | With authentication
--
-- > organizationRepos (Just (GithubUser (user, password))) "thoughtbot"
organizationRepos' :: Maybe GithubAuth -> String -> IO (Either Error [Repo])
organizationRepos' auth orgName = githubGet' auth ["orgs", orgName, "repos"]

-- | A specific organization repo, by the organization name.
--
-- > organizationRepo "thoughtbot" "github"
organizationRepo :: String -> String -> IO (Either Error Repo)
organizationRepo = organizationRepo' Nothing

-- | A specific organization repo, by the organization name.
-- | With authentication
--
-- > organizationRepo (Just (GithubUser (user, password))) "thoughtbot" "github"
organizationRepo' :: Maybe GithubAuth -> String -> String -> IO (Either Error Repo)
organizationRepo' auth orgName reqRepoName = githubGet' auth ["orgs", orgName, reqRepoName]

-- | Details on a specific repo, given the owner and repo name.
--
-- > userRepo "mike-burns" "github"
userRepo :: String -> String -> IO (Either Error Repo)
userRepo = userRepo' Nothing

-- | Details on a specific repo, given the owner and repo name.
-- | With authentication
--
-- > userRepo' (Just (GithubUser (user, password))) "mike-burns" "github"
userRepo' :: Maybe GithubAuth -> String -> String -> IO (Either Error Repo)
userRepo' auth userName reqRepoName = githubGet' auth ["repos", userName, reqRepoName]

-- | The contributors to a repo, given the owner and repo name.
--
-- > contributors "thoughtbot" "paperclip"
contributors :: String -> String -> IO (Either Error [Contributor])
contributors userName reqRepoName =
  githubGet ["repos", userName, reqRepoName, "contributors"]

-- | The contributors to a repo, including anonymous contributors (such as
-- deleted users or git commits with unknown email addresses), given the owner
-- and repo name.
--
-- > contributorsWithAnonymous "thoughtbot" "paperclip"
contributorsWithAnonymous :: String -> String -> IO (Either Error [Contributor])
contributorsWithAnonymous userName reqRepoName =
  githubGetWithQueryString
    ["repos", userName, reqRepoName, "contributors"]
    "anon=true"

-- | The programming languages used in a repo along with the number of
-- characters written in that language. Takes the repo owner and name.
--
-- > languagesFor "mike-burns" "ohlaunch"
languagesFor :: String -> String -> IO (Either Error [Language])
languagesFor userName reqRepoName = do
  result <- githubGet ["repos", userName, reqRepoName, "languages"]
  return $ either Left (Right . getLanguages) result

-- | The git tags on a repo, given the repo owner and name.
--
-- > tagsFor "thoughtbot" "paperclip"
tagsFor :: String -> String -> IO (Either Error [Tag])
tagsFor userName reqRepoName =
  githubGet ["repos", userName, reqRepoName, "tags"]

-- | The git branches on a repo, given the repo owner and name.
--
-- > branchesFor "thoughtbot" "paperclip"
branchesFor :: String -> String -> IO (Either Error [Branch])
branchesFor userName reqRepoName =
  githubGet ["repos", userName, reqRepoName, "branches"]


data NewRepo = NewRepo {
  newRepoName         :: String
, newRepoDescription  :: (Maybe String)
, newRepoHomepage     :: (Maybe String)
, newRepoPrivate      :: (Maybe Bool)
, newRepoHasIssues    :: (Maybe Bool)
, newRepoHasWiki      :: (Maybe Bool)
, newRepoAutoInit     :: (Maybe Bool)
} deriving Show

instance ToJSON  NewRepo where
  toJSON (NewRepo { newRepoName         = name
                  , newRepoDescription  = description
                  , newRepoHomepage     = homepage
                  , newRepoPrivate      = private
                  , newRepoHasIssues    = hasIssues
                  , newRepoHasWiki      = hasWiki
                  , newRepoAutoInit     = autoInit
                  }) = object
                  [ "name"                .= name
                  , "description"         .= description
                  , "homepage"            .= homepage
                  , "private"             .= private
                  , "has_issues"          .= hasIssues
                  , "has_wiki"            .= hasWiki
                  , "auto_init"           .= autoInit
                  ]

newRepo :: String -> NewRepo
newRepo name = NewRepo name Nothing Nothing Nothing Nothing Nothing Nothing

-- |
-- Create a new repository.
--
-- > createRepo (GithubUser (user, password)) (newRepo "some_repo") {newRepoHasIssues = Just False}
createRepo :: GithubAuth -> NewRepo -> IO (Either Error Repo)
createRepo auth = githubPost auth ["user", "repos"]

-- |
-- Create a new repository for an organization.
--
-- > createOrganizationRepo (GithubUser (user, password)) "thoughtbot" (newRepo "some_repo") {newRepoHasIssues = Just False}
createOrganizationRepo :: GithubAuth -> String -> NewRepo -> IO (Either Error Repo)
createOrganizationRepo auth org = githubPost auth ["orgs", org, "repos"]

data Edit = Edit {
  editName         :: Maybe String
, editDescription  :: Maybe String
, editHomepage     :: Maybe String
, editPublic       :: Maybe Bool
, editHasIssues    :: Maybe Bool
, editHasWiki      :: Maybe Bool
, editHasDownloads :: Maybe Bool
} deriving Show

instance Default Edit where
  def = Edit def def def def def def def

instance ToJSON  Edit where
  toJSON (Edit { editName         = name
               , editDescription  = description
               , editHomepage     = homepage
               , editPublic       = public
               , editHasIssues    = hasIssues
               , editHasWiki      = hasWiki
               , editHasDownloads = hasDownloads
               }) = object
               [ "name"          .= name
               , "description"   .= description
               , "homepage"      .= homepage
               , "public"        .= public
               , "has_issues"    .= hasIssues
               , "has_wiki"      .= hasWiki
               , "has_downloads" .= hasDownloads
               ]

-- |
-- Edit an existing repository.
--
-- > editRepo (GithubUser (user, password)) "some_user" "some_repo" def {editDescription = Just "some description"}
editRepo :: GithubAuth
     -> String      -- ^ owner
     -> String      -- ^ repository name
     -> Edit
     -> IO (Either Error Repo)
editRepo auth user repo body = githubPatch auth ["repos", user, repo] b
  where
    -- if no name is given, use curent name
    b = body {editName = editName body <|> Just repo}

-- |
-- Delete an existing repository.
--
-- > deleteRepo (GithubUser (user, password)) "thoughtbot" "some_repo"
deleteRepo :: GithubAuth
           -> String      -- ^ owner
           -> String      -- ^ repository name
           -> IO (Either Error ())
deleteRepo auth owner repo = do
  result <- doHttps "DELETE" url (Just auth) Nothing
  case result of
      Left e -> return (Left (HTTPConnectionError e))
      Right resp ->
          let status = responseStatus resp
              headers = responseHeaders resp
          in if status == notFound404
                -- doHttps silently absorbs 404 errors, but for this operation
                -- we want the user to know if they've tried to delete a
                -- non-existent repository
             then return (Left (HTTPConnectionError
                                (E.toException
                                 (StatusCodeException status headers
#if MIN_VERSION_http_conduit(1, 9, 0)
                                 (responseCookieJar resp)
#endif
                                 ))))
             else return (Right ())
  where
    url = "https://api.github.com/repos/" ++ owner ++ "/" ++ repo