File: ArtifactsSpec.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 (66 lines) | stat: -rw-r--r-- 2,358 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
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell   #-}
module GitHub.Actions.ArtifactsSpec where

import qualified GitHub as GH

import Prelude ()
import Prelude.Compat

import           Data.Aeson         (eitherDecodeStrict)
import           Data.ByteString    (ByteString)
import           Data.Either.Compat (isRight)
import           Data.FileEmbed     (embedFile)
import           Data.Foldable      (for_)
import           Data.String        (fromString)
import qualified Data.Vector        as V
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 :: (GH.Auth -> IO ()) -> IO ()
withAuth action = do
    mtoken <- lookupEnv "GITHUB_TOKEN"
    case mtoken of
        Nothing    -> pendingWith "no GITHUB_TOKEN"
        Just token -> action (GH.OAuth $ fromString token)

spec :: Spec
spec = do
    describe "artifactsForR" $ do
        it "works" $ withAuth $ \auth -> for_ repos $ \(owner, repo) -> do
            cs <- GH.executeRequest auth $
                GH.artifactsForR owner repo mempty GH.FetchAll
            cs `shouldSatisfy` isRight

    describe "decoding artifacts payloads" $ do
        it "decodes artifacts list payload" $ do
            GH.withTotalCountTotalCount artifactList `shouldBe` 23809
            V.length (GH.withTotalCountItems artifactList) `shouldBe` 2
        it "decodes signle artifact payload" $ do
            GH.artifactName artifact `shouldBe` "dist-without-markdown"
            GH.artifactWorkflowRunHeadSha (GH.artifactWorkflowRun artifact) `shouldBe` "601593ecb1d8a57a04700fdb445a28d4186b8954"

  where
    repos =
      [ ("thoughtbot", "paperclip")
      , ("phadej", "github")
      ]

    artifactList :: GH.WithTotalCount GH.Artifact
    artifactList =
        fromRightS (eitherDecodeStrict artifactsListPayload)

    artifact :: GH.Artifact
    artifact =
        fromRightS (eitherDecodeStrict artifactPayload)

    artifactsListPayload :: ByteString
    artifactsListPayload = $(embedFile "fixtures/actions/artifacts-list.json")

    artifactPayload :: ByteString
    artifactPayload = $(embedFile "fixtures/actions/artifact.json")