Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
2 changes: 1 addition & 1 deletion Github/Data.hs
Original file line number Diff line number Diff line change
Expand Up @@ -145,7 +145,7 @@ instance FromJSON File where
<*> o .: "additions"
<*> o .: "sha"
<*> o .: "changes"
<*> o .: "patch"
<*> o .:? "patch"
<*> o .: "filename"
<*> o .: "deletions"
parseJSON _ = fail "Could not build a File"
Expand Down
13 changes: 7 additions & 6 deletions Github/Data/GitData.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@
module Github.Data.GitData where

import Github.Data.Definitions
import Github.Data.Name (Name)

import Control.DeepSeq (NFData (..))
import Control.DeepSeq.Generics (genericRnf)
Expand All @@ -13,7 +14,7 @@ import Data.Vector (Vector)
import GHC.Generics (Generic)

data Commit = Commit {
commitSha :: !Text
commitSha :: !(Name Commit)
,commitParents :: !(Vector Tree)
,commitUrl :: !Text
,commitGitCommit :: !GitCommit
Expand All @@ -26,7 +27,7 @@ data Commit = Commit {
instance NFData Commit where rnf = genericRnf

data Tree = Tree {
treeSha :: !Text
treeSha :: !(Name Tree)
,treeUrl :: !Text
,treeGitTrees :: !(Vector GitTree)
} deriving (Show, Data, Typeable, Eq, Ord, Generic)
Expand All @@ -35,7 +36,7 @@ instance NFData Tree where rnf = genericRnf

data GitTree = GitTree {
gitTreeType :: !Text
,gitTreeSha :: !Text
,gitTreeSha :: !(Name GitTree)
-- Can be empty for submodule
,gitTreeUrl :: !(Maybe Text)
,gitTreeSize :: !(Maybe Int)
Expand All @@ -51,7 +52,7 @@ data GitCommit = GitCommit {
,gitCommitCommitter :: !GitUser
,gitCommitAuthor :: !GitUser
,gitCommitTree :: !Tree
,gitCommitSha :: !(Maybe Text)
,gitCommitSha :: !(Maybe (Name GitCommit))
,gitCommitParents :: !(Vector Tree)
} deriving (Show, Data, Typeable, Eq, Ord, Generic)

Expand All @@ -61,7 +62,7 @@ data Blob = Blob {
blobUrl :: !Text
,blobEncoding :: !Text
,blobContent :: !Text
,blobSha :: !Text
,blobSha :: !(Name Blob)
,blobSize :: !Int
} deriving (Show, Data, Typeable, Eq, Ord, Generic)

Expand Down Expand Up @@ -145,7 +146,7 @@ data File = File {
,fileAdditions :: !Int
,fileSha :: !Text
,fileChanges :: !Int
,filePatch :: !Text
,filePatch :: !(Maybe Text)
,fileFilename :: !Text
,fileDeletions :: !Int
} deriving (Show, Data, Typeable, Eq, Ord, Generic)
Expand Down
21 changes: 18 additions & 3 deletions spec/Github/CommitsSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,12 +3,12 @@
module Github.CommitsSpec where

import Github.Auth (GithubAuth (..))
import Github.Repos.Commits (commitsFor', commitsForR)
import Github.Repos.Commits (Commit, mkName, commitSha, commitsFor', commitsForR, diffR)
import Github.Request (executeRequest)

-- import Data.Aeson.Compat (eitherDecodeStrict)
import Control.Monad (forM_)
import Data.Either.Compat (isRight)
-- import Data.FileEmbed (embedFile)
import Data.Proxy (Proxy (..))
import System.Environment (lookupEnv)
import Test.Hspec (Spec, describe, it, pendingWith, shouldSatisfy)

Expand Down Expand Up @@ -38,3 +38,18 @@ spec = do
cs <- executeRequest auth $ commitsForR "phadej" "github" (Just 40)
cs `shouldSatisfy` isRight
V.length (fromRightS cs) `shouldSatisfy` (< 70)

describe "diff" $ do
it "works" $ withAuth $ \auth -> do
cs <- executeRequest auth $ commitsForR "phadej" "github" (Just 30)
cs `shouldSatisfy` isRight
let commits = take 10 . V.toList . fromRightS $ cs
let pairs = zip commits $ drop 1 commits
forM_ pairs $ \(a, b) -> do
d <- executeRequest auth $ diffR "phadej" "github" (commitSha a) (commitSha b)
d `shouldSatisfy` isRight

it "issue #155" $ withAuth $ \auth -> do
let mkCommitName = mkName (Proxy :: Proxy Commit)
d <- executeRequest auth $ diffR "nomeata" "codespeed" (mkCommitName "ghc") (mkCommitName "tobami:master")
d `shouldSatisfy` isRight