Skip to content

Commit

Permalink
Add tests for nevraToGroupId.
Browse files Browse the repository at this point in the history
Also includes a Utils function to help with making ephemeral test
databases.
  • Loading branch information
dashea committed Jul 14, 2017
1 parent 6991420 commit 35680bb
Show file tree
Hide file tree
Showing 3 changed files with 102 additions and 2 deletions.
3 changes: 3 additions & 0 deletions importer/db.cabal
Expand Up @@ -142,7 +142,10 @@ Test-Suite test-db
build-depends: hspec,
base >= 4.8 && < 5.0,
codec-rpm >= 0.1.1 && < 0.2,
monad-logger,
persistent,
persistent-sqlite,
resourcet,
db

default-language: Haskell2010
58 changes: 58 additions & 0 deletions importer/tests/BDCS/GroupsSpec.hs
@@ -0,0 +1,58 @@
-- Copyright (C) 2017 Red Hat, Inc.
--
-- This library is free software; you can redistribute it and/or
-- modify it under the terms of the GNU Lesser General Public
-- License as published by the Free Software Foundation; either
-- version 2.1 of the License, or (at your option) any later version.
--
-- This library is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
-- Lesser General Public License for more details.
--
-- You should have received a copy of the GNU Lesser General Public
-- License along with this library; if not, see <http://www.gnu.org/licenses/>.

{-# LANGUAGE OverloadedStrings #-}

module BDCS.GroupsSpec(spec)
where

import BDCS.Groups(nevraToGroupId)
import BDCS.DB

import Database.Persist.Sql(toSqlKey)
import Test.Hspec

import Utils(withDb)

spec :: Spec
spec = describe "BDCS.Groups Tests" $ do
it "nevraToGroupId, has epoch" $
-- gid <- withDb $ nevraToGroupId ("hasEpoch", Just "7", "1.0", "1.el7", "x86_64")
-- gid `shouldBe` Just (toSqlKey 1)
withDb (nevraToGroupId ("hasEpoch", Just "7", "1.0", "1.el7", "x86_64")) >>= (`shouldBe` Just (toSqlKey 1))

it "nevraToGroupId, no epoch" $
withDb (nevraToGroupId ("noEpoch", Nothing, "1.0", "1.el7", "x86_64")) >>= (`shouldBe` Just (toSqlKey 2))

it "nevraToGroupId, has epoch, not specified" $
withDb (nevraToGroupId ("hasEpoch", Nothing, "1.0", "1.el7", "x86_64")) >>= (`shouldBe` Nothing)

it "nevraToGroupId, no epoch, is specified" $
withDb (nevraToGroupId ("noEpoch", Just "7", "1.0", "1.el7", "x86_64")) >>= (`shouldBe` Nothing)

it "nevraToGroupId, has wrong epoch" $
withDb (nevraToGroupId ("hasEpoch", Just "8", "1.0", "1.el7", "x86_64")) >>= (`shouldBe` Nothing)

it "nevraToGroupId, wrong name" $
withDb (nevraToGroupId ("missingEpoch", Just "7", "1.0", "1.el7", "x86_64")) >>= (`shouldBe` Nothing)

it "nevraToGroupId, wrong version" $
withDb (nevraToGroupId ("hasEpoch", Just "7", "1.1", "1.el7", "x86_64")) >>= (`shouldBe` Nothing)

it "nevraToGroupId, wrong release" $
withDb (nevraToGroupId ("hasEpoch", Just "7", "1.0", "2.el7", "x86_64")) >>= (`shouldBe` Nothing)

it "nevraToGroupId, wrong arch" $
withDb (nevraToGroupId ("hasEpoch", Just "7", "1.0", "1.el7", "i686")) >>= (`shouldBe` Nothing)
43 changes: 41 additions & 2 deletions importer/tests/Utils.hs
Expand Up @@ -14,11 +14,50 @@
-- License along with this library; if not, see <http://www.gnu.org/licenses/>.
--
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}

module Utils(fakeKey)
module Utils(fakeKey,
withDb)
where

import Database.Persist.Sql(Key, SqlBackend, ToBackendKey, toSqlKey)
import Control.Monad(void)
import Control.Monad.IO.Class(MonadIO)
import Control.Monad.Trans.Resource(MonadBaseControl, MonadResource, ResourceT)
import Control.Monad.Logger(NoLoggingT)
import Database.Persist.Sql(Key, SqlBackend, SqlPersistT, ToBackendKey, insertKey, runMigrationSilent, toSqlKey)
import Database.Persist.Sqlite(runSqlite)

import BDCS.DB
import BDCS.GroupKeyValue
import BDCS.KeyType

{-# ANN module ("HLint: ignore Reduce duplication" :: String) #-}

fakeKey :: ToBackendKey SqlBackend a => Key a
fakeKey = toSqlKey 0

-- Run a database action within an in-memory test database
withDb :: (MonadBaseControl IO m, MonadIO m) => SqlPersistT (NoLoggingT (ResourceT m)) a -> m a
withDb action = runSqlite ":memory:" (initDb >> action)
where
initDb :: (MonadBaseControl IO m, MonadIO m) => SqlPersistT m ()
initDb = do
void $ runMigrationSilent migrateAll

-- For nevraToGroupId:
-- hasEpoch-7:1.0-1.el7.x86_64
let gid_1 = toSqlKey 1
insertKey gid_1 $ Groups "hasEpoch" "rpm"
void $ insertGroupKeyValue (TextKey "name") "hasEpoch" Nothing gid_1
void $ insertGroupKeyValue (TextKey "epoch") "7" Nothing gid_1
void $ insertGroupKeyValue (TextKey "version") "1.0" Nothing gid_1
void $ insertGroupKeyValue (TextKey "release") "1.el7" Nothing gid_1
void $ insertGroupKeyValue (TextKey "arch") "x86_64" Nothing gid_1

-- noEpoch-1.0-1.el7.x86_64
let gid_2 = toSqlKey 2
insertKey gid_2 $ Groups "noEpoch" "rpm"
void $ insertGroupKeyValue (TextKey "name") "noEpoch" Nothing gid_2
void $ insertGroupKeyValue (TextKey "version") "1.0" Nothing gid_2
void $ insertGroupKeyValue (TextKey "release") "1.el7" Nothing gid_2
void $ insertGroupKeyValue (TextKey "arch") "x86_64" Nothing gid_2

0 comments on commit 35680bb

Please sign in to comment.