File: ReposSpec.hs

package info (click to toggle)
haskell-github 0.29-1
  • links: PTS, VCS
  • area: main
  • in suites: sid
  • size: 944 kB
  • sloc: haskell: 7,744; makefile: 3
file content (52 lines) | stat: -rw-r--r-- 1,744 bytes parent folder | download | duplicates (2)
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
{-# LANGUAGE OverloadedStrings #-}
module GitHub.ReposSpec where

import GitHub
       (Auth (..), FetchCount (..), Repo (..), RepoPublicity (..), github,
       repositoryR)
import GitHub.Endpoints.Repos (currentUserReposR, languagesForR, userReposR)

import Data.Either.Compat (isRight)
import Data.String        (fromString)
import System.Environment (lookupEnv)
import Test.Hspec
       (Spec, describe, it, pendingWith, shouldBe, shouldSatisfy)

import qualified Data.HashMap.Strict as HM

fromRightS :: Show a => Either a b -> b
fromRightS (Right b) = b
fromRightS (Left a) = error $ "Expected a Right and got a Left" ++ show a

withAuth :: (Auth -> IO ()) -> IO ()
withAuth action = do
  mtoken <- lookupEnv "GITHUB_TOKEN"
  case mtoken of
    Nothing    -> pendingWith "no GITHUB_TOKEN"
    Just token -> action (OAuth $ fromString token)

spec :: Spec
spec = do
  describe "repositoryR" $ do
    it "works" $ withAuth $ \auth -> do
      er <- github auth repositoryR "haskell-github" "github"
      er `shouldSatisfy` isRight
      let Right r = er
      -- https://github.com/haskell-github/github/pull/219
      repoDefaultBranch r `shouldBe` Just "master"

  describe "currentUserRepos" $ do
    it "works" $ withAuth $ \auth -> do
      cs <- github auth currentUserReposR RepoPublicityAll FetchAll
      cs `shouldSatisfy` isRight

  describe "userRepos" $ do
    it "works" $ withAuth $ \auth -> do
      cs <- github auth userReposR "phadej" RepoPublicityAll FetchAll
      cs `shouldSatisfy` isRight

  describe "languagesFor'" $ do
    it "works" $ withAuth $ \auth -> do
      ls <- github auth languagesForR "haskell-github" "github"
      ls `shouldSatisfy` isRight
      fromRightS ls `shouldSatisfy` HM.member "Haskell"