File: OrganizationsSpec.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 (54 lines) | stat: -rw-r--r-- 2,072 bytes parent folder | download | duplicates (3)
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
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell   #-}
module GitHub.OrganizationsSpec where

import GitHub                                 (FetchCount (..), github)
import GitHub.Auth                            (Auth (..))
import GitHub.Data
       (SimpleOrganization (..), SimpleOwner (..), SimpleTeam (..))
import GitHub.Endpoints.Organizations         (publicOrganizationsForR)
import GitHub.Endpoints.Organizations.Members (membersOfR)

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

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 "publicOrganizationsFor'" $ do
    it "decodes simple organization json" $ do
      let orgs = eitherDecodeStrict $(embedFile "fixtures/user-organizations.json")
      simpleOrganizationLogin (head $ fromRightS orgs) `shouldBe` "github"

    it "returns information about the user's organizations" $ withAuth $ \auth -> do
      orgs <- github auth publicOrganizationsForR "mike-burns" FetchAll
      orgs  `shouldSatisfy` isRight

  describe "teamsOf" $ do
    it "parse" $ do
      let ts = eitherDecodeStrict $(embedFile "fixtures/list-teams.json")
      simpleTeamName (head $ fromRightS ts) `shouldBe` "Justice League"

  describe "membersOf" $ do
    it "parse" $ do
      let ms = eitherDecodeStrict $(embedFile "fixtures/members-list.json")
      simpleOwnerLogin (head $ fromRightS ms) `shouldBe` "octocat"

    it "works" $ withAuth $ \auth -> do
      ms <- github auth membersOfR "haskell" FetchAll
      ms `shouldSatisfy` isRight