Skip to content

Commit

Permalink
Add status-reading endpoints
Browse files Browse the repository at this point in the history
  • Loading branch information
jamesdabbs committed Feb 26, 2017
1 parent c137bce commit 73d1548
Show file tree
Hide file tree
Showing 2 changed files with 55 additions and 6 deletions.
33 changes: 31 additions & 2 deletions src/GitHub/Data/Statuses.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,11 +5,16 @@
module GitHub.Data.Statuses where

import GitHub.Data.Definitions
import GitHub.Data.Name (Name)
import GitHub.Data.Id (Id)
import GitHub.Data.URL (URL)
import GitHub.Internal.Prelude
import Prelude ()

import GitHub.Data.GitData (Commit)
import GitHub.Data.Repos (RepoRef)


data StatusState
= StatusPending
| StatusSuccess
Expand All @@ -33,6 +38,7 @@ instance ToJSON StatusState where
toJSON StatusError = String "error"
toJSON StatusFailure = String "failure"


data Status = Status
{ statusCreatedAt :: !UTCTime
, statusUpdatedAt :: !UTCTime
Expand All @@ -42,7 +48,7 @@ data Status = Status
, statusId :: !(Id Status)
, statusUrl :: !URL
, statusContext :: !(Maybe Text)
, statusCreator :: !SimpleUser
, statusCreator :: !(Maybe SimpleUser)
}
deriving (Show, Data, Typeable, Eq, Ord, Generic)

Expand All @@ -56,7 +62,8 @@ instance FromJSON Status where
<*> o .: "id"
<*> o .: "url"
<*> o .:? "context"
<*> o .: "creator"
<*> o .:? "creator"


data NewStatus = NewStatus
{ newStatusState :: !StatusState
Expand All @@ -79,3 +86,25 @@ instance ToJSON NewStatus where
where
notNull (_, Null) = False
notNull (_, _) = True


data CombinedStatus = CombinedStatus
{ combinedStatusState :: !StatusState
, combinedStatusSha :: !(Name Commit)
, combinedStatusTotalCount :: !Int
, combinedStatusStatuses :: !(Vector Status)
, combinedStatusRepository :: !RepoRef
, combinedStatusCommitUrl :: !URL
, combinedStatusUrl :: !URL
}
deriving (Show, Data, Typeable, Eq, Ord, Generic)

instance FromJSON CombinedStatus where
parseJSON = withObject "CombinedStatus" $ \o -> CombinedStatus
<$> o .: "state"
<*> o .: "sha"
<*> o .: "total_count"
<*> o .: "statuses"
<*> o .: "repository"
<*> o .: "commit_url"
<*> o .: "url"
28 changes: 24 additions & 4 deletions src/GitHub/Endpoints/Repos/Statuses.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,10 @@
module GitHub.Endpoints.Repos.Statuses (
createStatus,
createStatusR,
statusesFor,
statusesForR,
statusFor,
statusForR,
module GitHub.Data
) where

Expand All @@ -14,10 +18,26 @@ import Prelude ()

createStatus :: Auth -> Name Owner -> Name Repo -> Name Commit -> NewStatus -> IO (Either Error Status)
createStatus auth owner repo sha ns =
executeRequest auth $ createStatusR owner repo sha ns
executeRequest auth $ createStatusR owner repo sha ns

createStatusR :: Name Owner -> Name Repo -> Name Commit -> NewStatus -> Request 'RW Status
createStatusR owner repo sha =
command Post parts . encode
where
parts = ["repos", toPathPart owner, toPathPart repo, "statuses", toPathPart sha]
command Post parts . encode
where
parts = ["repos", toPathPart owner, toPathPart repo, "statuses", toPathPart sha]

statusesFor :: Auth -> Name Owner -> Name Repo -> Name Commit -> IO (Either Error (Vector Status))
statusesFor auth user repo sha =
executeRequest auth $ statusesForR user repo sha FetchAll

statusesForR :: Name Owner -> Name Repo -> Name Commit -> FetchCount -> Request 'RW (Vector Status)
statusesForR user repo sha =
pagedQuery ["repos", toPathPart user, toPathPart repo, "commits", toPathPart sha, "statuses"] []

statusFor :: Auth -> Name Owner -> Name Repo -> Name Commit -> IO (Either Error CombinedStatus)
statusFor auth user repo sha =
executeRequest auth $ statusForR user repo sha

statusForR :: Name Owner -> Name Repo -> Name Commit -> Request 'RW CombinedStatus
statusForR user repo sha =
query ["repos", toPathPart user, toPathPart repo, "commits", toPathPart sha, "status"] []

0 comments on commit 73d1548

Please sign in to comment.