Initialize the database on startup

Tests updated to use a test database.
This commit is contained in:
Correl Roush 2022-03-28 00:47:57 -04:00
parent 384affe29e
commit 492b4fa71b
4 changed files with 174 additions and 16 deletions

2
.gitignore vendored
View file

@ -11,3 +11,5 @@ htmlcov
.stack-work/
tutor.cabal
test.db
tutor.db

View file

@ -1,11 +1,14 @@
module Tutor ( startApp )
where
module Tutor (startApp) where
import Network.Wai.Handler.Warp
import Network.Wai.Logger
import Servant (serve)
import Tutor.Api (app)
import Tutor.Database (initDb)
startApp :: FilePath -> IO ()
startApp dbFile = withStdoutLogger $ \logger ->
runSettings (setPort 8080 $ setLogger logger $ defaultSettings) (app dbFile)
startApp dbFile = do
initDb dbFile
withStdoutLogger $
\logger ->
runSettings (setPort 8080 $ setLogger logger $ defaultSettings) (app dbFile)

View file

@ -1,7 +1,7 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
module Tutor.Database (searchCards) where
module Tutor.Database (initDb, searchCards) where
import qualified Data.List as List
import Data.Maybe
@ -17,12 +17,154 @@ import Tutor.Card
import Tutor.Search
import Tutor.SearchParser
import Tutor.Select
( Select (..),
join,
limit,
orderBy,
parameter,
selectSimple,
sqlJoin,
toQuery,
whereNamedParam,
where_,
)
schema :: [Query]
schema =
[ [sql|
CREATE TABLE IF NOT EXISTS `sets` (
`set_code` TEXT PRIMARY KEY,
`name` TEXT NOT NULL
);
|],
[sql|
CREATE TABLE IF NOT EXISTS `rarities` (
`rarity` TEXT PRIMARY KEY,
`rarity_ord` INTEGER NOT NULL
);
|],
[sql|
DELETE FROM `rarities`;
|],
[sql|
INSERT INTO `rarities` (`rarity`, `rarity_ord`) VALUES
('n/a', 0),
('common', 1),
('uncommon', 2),
('rare', 3),
('special', 4),
('mythic', 5),
('bonus', 6);
|],
[sql|
CREATE TABLE IF NOT EXISTS `cards` (
`scryfall_id` TEXT PRIMARY KEY,
`oracle_id` TEXT,
`name` TEXT NOT NULL,
`set_code` TEXT,
`collector_number` TEXT,
`release_date` TEXT,
`rarity` TEXT NOT NULL,
`color_identity` TEXT NOT NULL,
`cmc` TEXT NOT NULL, -- Decimal value
`type_line` TEXT NOT NULL,
`foil` INTEGER NOT NULL DEFAULT 0,
`nonfoil` INTEGER NOT NULL DEFAULT 1,
`variation` INTEGER NOT NULL DEFAULT 0,
`edhrec_rank` INTEGER,
`oracle_text` TEXT,
FOREIGN KEY (`set_code`) REFERENCES `sets` (`set_code`),
FOREIGN KEY (`rarity`) REFERENCES `rarities` (`rarity`)
);
|],
[sql|
CREATE INDEX IF NOT EXISTS `cards_name` ON `cards`(`name` COLLATE nocase);
|],
[sql|
CREATE INDEX IF NOT EXISTS `cards_rarity` ON `cards`(`rarity`);
|],
[sql|
CREATE INDEX IF NOT EXISTS `cards_color_identity` ON `cards`(`color_identity`);
|],
[sql|
CREATE INDEX IF NOT EXISTS `cards_oracle_id` ON `cards` (`oracle_id`);
|],
[sql|
CREATE INDEX IF NOT EXISTS `cards_name` ON `cards` (`name`);
|],
[sql|
CREATE TABLE IF NOT EXISTS `copies` (
`id` INTEGER PRIMARY KEY AUTOINCREMENT,
`collection` TEXT NOT NULL DEFAULT 'Default',
`scryfall_id` TEXT,
`isFoil` INTEGER NOT NULL DEFAULT 0,
`language` TEXT,
`condition` TEXT,
FOREIGN KEY (`scryfall_id`) REFERENCES `cards`(`scryfall_id`)
);
|],
[sql|
CREATE TABLE IF NOT EXISTS `card_prices` (
`scryfall_id` TEXT,
`date` TEXT,
`usd` TEXT, -- Decimal value
`usd_foil` TEXT, -- Decimal value
`eur` TEXT, -- Decimal value
`eur_foil` TEXT, -- Decimal value
`tix` TEXT, -- Decimal value
PRIMARY KEY (`scryfall_id`, `date`),
FOREIGN KEY (`scryfall_id`) REFERENCES `cards`(`scryfall_id`)
);
|],
[sql|
CREATE TABLE IF NOT EXISTS `legalities` (
`scryfall_id` TEXT NOT NULL,
`format` TEXT NOT NULL,
`legality` TEXT NOT NULL,
PRIMARY KEY (`scryfall_id`, `format`),
FOREIGN KEY (`scryfall_id`) REFERENCES `cards`(`scryfall_id`)
);
|],
[sql|
CREATE TABLE IF NOT EXISTS `games` (
`scryfall_id` TEXT NOT NULL,
`game` TEXT NOT NULL, -- 'paper', 'arena', or 'mtgo'
PRIMARY KEY (`scryfall_id`, `game`),
FOREIGN KEY (`scryfall_id`) REFERENCES `cards`(`scryfall_id`)
);
|],
[sql|
CREATE TABLE IF NOT EXISTS `decks` (
`deck_id` INTEGER PRIMARY KEY AUTOINCREMENT,
`name` TEXT NOT NULL
);
|],
[sql|
CREATE TABLE IF NOT EXISTS `deck_cards` (
`deck_id` INTEGER NOT NULL,
`oracle_id` TEXT NOT NULL,
`quantity` INTEGER NOT NULL DEFAULT 1,
PRIMARY KEY (`deck_id`, `oracle_id`),
FOREIGN KEY (`deck_id`) REFERENCES `decks`(`deck_id`)
);
|],
[sql|
CREATE TABLE IF NOT EXISTS `vars` (
`key` TEXT PRIMARY KEY,
`value` TEXT
);
|]
]
initDb :: FilePath -> IO ()
initDb dbFile =
withConnection dbFile $ \conn ->
mapM_ (execute_ conn) schema
instance FromField UUID.UUID where
fromField (Field (SQLText txt) _) = Ok $ fromMaybe UUID.nil $ UUID.fromText txt
fromField f = returnError ConversionFailed f "need a text"
instance FromRow Card where
fromRow = do
scryfall_id <- field

View file

@ -1,18 +1,29 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
module AppSpec (spec) where
import Tutor (app)
import Database.SQLite.Simple (execute_, withConnection)
import Test.Hspec
import Test.Hspec.Wai
import Test.Hspec.Wai.JSON
main :: IO ()
main = hspec spec
import Tutor.Api (app)
import Tutor.Database (initDb)
spec :: Spec
spec = with (return $ app "tutor.db") $ do
describe "GET /search" $ do
it "responds with 200" $ do
get "/search" `shouldRespondWith` 200
spec = do
with startApp $ do
describe "GET /search" $ do
it "responds with 200" $ do
get "/search" `shouldRespondWith` 200
where
dbFile = "test.db"
startApp = do
initDb dbFile
resetDb
return $ app dbFile
resetDb = do
withConnection dbFile $ \conn ->
mapM_
(execute_ conn)
[ "DELETE FROM copies",
"DELETE FROM cards"
]