Compare commits
1 commit
1ea0aebdb7
...
3eff953def
Author | SHA1 | Date | |
---|---|---|---|
3eff953def |
6 changed files with 73 additions and 13 deletions
|
@ -24,6 +24,7 @@ dependencies:
|
||||||
- containers
|
- containers
|
||||||
- envy
|
- envy
|
||||||
- lens
|
- lens
|
||||||
|
- network-uri
|
||||||
- openapi3
|
- openapi3
|
||||||
- parsec
|
- parsec
|
||||||
- parsec-extra
|
- parsec-extra
|
||||||
|
|
|
@ -1,6 +1,7 @@
|
||||||
{-# LANGUAGE DataKinds #-}
|
{-# LANGUAGE DataKinds #-}
|
||||||
{-# LANGUAGE DeriveDataTypeable #-}
|
{-# LANGUAGE DeriveDataTypeable #-}
|
||||||
{-# LANGUAGE DeriveGeneric #-}
|
{-# LANGUAGE DeriveGeneric #-}
|
||||||
|
{-# LANGUAGE FlexibleContexts #-}
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
{-# LANGUAGE TypeOperators #-}
|
{-# LANGUAGE TypeOperators #-}
|
||||||
|
|
||||||
|
@ -24,12 +25,16 @@ import qualified Data.Text as T
|
||||||
import Data.Typeable (Typeable)
|
import Data.Typeable (Typeable)
|
||||||
import Data.Version (showVersion)
|
import Data.Version (showVersion)
|
||||||
import GHC.Generics (Generic)
|
import GHC.Generics (Generic)
|
||||||
|
import Network.URI
|
||||||
import qualified Paths_tutor as PT
|
import qualified Paths_tutor as PT
|
||||||
import Servant
|
import Servant
|
||||||
import Servant.OpenApi (HasOpenApi (toOpenApi))
|
import Servant.OpenApi (HasOpenApi (toOpenApi))
|
||||||
|
import qualified Tutor.Pagination as Pagination
|
||||||
import Tutor.Card
|
import Tutor.Card
|
||||||
import Tutor.Config
|
import Tutor.Config
|
||||||
import Tutor.Database
|
import Tutor.Database
|
||||||
|
import Data.Maybe (fromMaybe)
|
||||||
|
import qualified Data.Text.Lazy.Lens as T
|
||||||
|
|
||||||
data Status = Status
|
data Status = Status
|
||||||
{ apiVersion :: T.Text,
|
{ apiVersion :: T.Text,
|
||||||
|
@ -68,6 +73,11 @@ type GetStatus =
|
||||||
:> "status"
|
:> "status"
|
||||||
:> Get '[JSON] Status
|
:> Get '[JSON] Status
|
||||||
|
|
||||||
|
type LinkHeaders =
|
||||||
|
'[ Header "Link" T.Text
|
||||||
|
, Header "Link" T.Text
|
||||||
|
, Header "Link" T.Text]
|
||||||
|
|
||||||
type SearchCards =
|
type SearchCards =
|
||||||
Summary "Search for cards in a collection"
|
Summary "Search for cards in a collection"
|
||||||
:> Description
|
:> Description
|
||||||
|
@ -176,7 +186,9 @@ type SearchCards =
|
||||||
:> QueryParam' '[Description "Query string"] "q" T.Text
|
:> QueryParam' '[Description "Query string"] "q" T.Text
|
||||||
:> QueryParam' '[Description "Sorting method"] "sort_by" T.Text
|
:> QueryParam' '[Description "Sorting method"] "sort_by" T.Text
|
||||||
:> QueryParam' '[Description "Search across collection or all cards"] "in_collection" T.Text
|
:> QueryParam' '[Description "Search across collection or all cards"] "in_collection" T.Text
|
||||||
:> Get '[JSON] [Card]
|
:> QueryParam' '[Description "Pagination limit"] "limit" Int
|
||||||
|
:> QueryParam' '[Description "Pagination offset"] "offset" Int
|
||||||
|
:> Get '[JSON] (Headers LinkHeaders [Card])
|
||||||
|
|
||||||
type TutorAPI =
|
type TutorAPI =
|
||||||
GetStatus
|
GetStatus
|
||||||
|
@ -206,9 +218,25 @@ openapi =
|
||||||
tutorServer :: Config -> Server TutorAPI
|
tutorServer :: Config -> Server TutorAPI
|
||||||
tutorServer config = status config :<|> searchCards (tutorDatabase config)
|
tutorServer config = status config :<|> searchCards (tutorDatabase config)
|
||||||
where
|
where
|
||||||
searchCards :: FilePath -> Maybe T.Text -> Maybe T.Text -> Maybe T.Text -> Handler [Card]
|
searchCards :: FilePath -> Maybe T.Text -> Maybe T.Text -> Maybe T.Text -> Maybe Int -> Maybe Int -> Handler (Headers LinkHeaders [Card])
|
||||||
searchCards dbFile q sortBy inCollection =
|
searchCards dbFile q sortBy inCollection limit offset = do
|
||||||
liftIO $ Tutor.Database.searchCards dbFile q sortBy inCollection
|
page <- liftIO $ Tutor.Database.searchCards dbFile q sortBy inCollection pagination
|
||||||
|
return $ headers page (Pagination.items page)
|
||||||
|
where pagination = Pagination.Pagination (fromMaybe 10 limit) (fromMaybe 0 offset)
|
||||||
|
headers page = self . next page . prev page
|
||||||
|
self = addHeader $ link "self" $ uri limit offset
|
||||||
|
next Pagination.Page {Pagination.next = Just p} = addHeader $ link "next" $ uri (Just $ Pagination.limit p) (Just $ Pagination.offset p)
|
||||||
|
next _ = noHeader
|
||||||
|
prev Pagination.Page {Pagination.previous = Just p} = addHeader $ link "prev" $ uri (Just $ Pagination.limit p) (Just $ Pagination.offset p)
|
||||||
|
prev _ = noHeader
|
||||||
|
uri :: Maybe Int -> Maybe Int -> URI
|
||||||
|
uri limit' offset' =
|
||||||
|
-- TODO: Apply the generated relative URI to the requested absolute URI
|
||||||
|
relativeTo
|
||||||
|
(linkURI $ safeLink api (Proxy :: Proxy SearchCards) q sortBy inCollection limit' offset')
|
||||||
|
(configuredBaseURI config)
|
||||||
|
link :: T.Text -> URI -> T.Text
|
||||||
|
link rel uri = T.concat ["<", T.pack $ show uri, ">; rel=\"", rel, "\""]
|
||||||
|
|
||||||
docsServer :: Server DocsAPI
|
docsServer :: Server DocsAPI
|
||||||
docsServer = return openapi
|
docsServer = return openapi
|
||||||
|
|
|
@ -1,14 +1,16 @@
|
||||||
{-# LANGUAGE DeriveGeneric #-}
|
{-# LANGUAGE DeriveGeneric #-}
|
||||||
|
|
||||||
module Tutor.Config (Config (..), defaultConfig) where
|
module Tutor.Config (Config (..), defaultConfig, configuredBaseURI) where
|
||||||
|
|
||||||
import GHC.Generics
|
import GHC.Generics
|
||||||
|
import Network.URI
|
||||||
import System.Envy
|
import System.Envy
|
||||||
|
|
||||||
data Config = Config
|
data Config = Config
|
||||||
{ tutorPort :: Int,
|
{ tutorPort :: Int,
|
||||||
tutorDatabase :: FilePath,
|
tutorDatabase :: FilePath,
|
||||||
tutorStatic :: FilePath
|
tutorStatic :: FilePath,
|
||||||
|
tutorBaseUrl :: Maybe String
|
||||||
}
|
}
|
||||||
deriving (Generic, Show)
|
deriving (Generic, Show)
|
||||||
|
|
||||||
|
@ -16,7 +18,14 @@ defaultConfig =
|
||||||
Config
|
Config
|
||||||
{ tutorPort = 8000,
|
{ tutorPort = 8000,
|
||||||
tutorDatabase = "tutor.db",
|
tutorDatabase = "tutor.db",
|
||||||
tutorStatic = "www/public"
|
tutorStatic = "www/public",
|
||||||
|
tutorBaseUrl = Nothing
|
||||||
}
|
}
|
||||||
|
|
||||||
|
configuredBaseURI :: Config -> URI
|
||||||
|
configuredBaseURI config =
|
||||||
|
case tutorBaseUrl config >>= parseURI of
|
||||||
|
Just uri -> uri
|
||||||
|
Nothing -> URI "http:" (Just $ URIAuth "" "localhost" (":" ++ show (tutorPort config))) "/" "" ""
|
||||||
|
|
||||||
instance FromEnv Config
|
instance FromEnv Config
|
||||||
|
|
|
@ -14,12 +14,13 @@ import Database.SQLite.Simple.Internal
|
||||||
import Database.SQLite.Simple.Ok
|
import Database.SQLite.Simple.Ok
|
||||||
import Database.SQLite.Simple.QQ
|
import Database.SQLite.Simple.QQ
|
||||||
import Tutor.Card
|
import Tutor.Card
|
||||||
|
import qualified Tutor.Pagination as Pagination
|
||||||
import qualified Tutor.Search as Search
|
import qualified Tutor.Search as Search
|
||||||
import Tutor.SearchParser
|
import Tutor.SearchParser
|
||||||
import Tutor.Select
|
import Tutor.Select
|
||||||
( Select (..),
|
( Select (..),
|
||||||
join,
|
join,
|
||||||
limit,
|
limitOffset,
|
||||||
orderBy,
|
orderBy,
|
||||||
parameter,
|
parameter,
|
||||||
selectSimple,
|
selectSimple,
|
||||||
|
@ -198,14 +199,23 @@ instance FromRow Card where
|
||||||
}
|
}
|
||||||
}
|
}
|
||||||
|
|
||||||
searchCards :: FilePath -> Maybe T.Text -> Maybe T.Text -> Maybe T.Text -> IO [Card]
|
searchCards :: FilePath -> Maybe T.Text -> Maybe T.Text -> Maybe T.Text -> Pagination.Pagination -> IO (Pagination.Page Card)
|
||||||
searchCards dbFile q sortBy inCollection =
|
searchCards dbFile q sortBy inCollection pagination =
|
||||||
withConnection dbFile $ \conn ->
|
withConnection dbFile $ \conn ->
|
||||||
queryNamed
|
asPage <$> queryNamed
|
||||||
conn
|
conn
|
||||||
(toQuery query)
|
(toQuery query)
|
||||||
(selectParameters query)
|
(selectParameters query)
|
||||||
where
|
where
|
||||||
|
limit = Pagination.limit pagination
|
||||||
|
offset = Pagination.offset pagination
|
||||||
|
asPage results =
|
||||||
|
if length results > limit then
|
||||||
|
Pagination.Page prev (Just $ Pagination.Pagination limit (offset + limit)) (take limit results)
|
||||||
|
else
|
||||||
|
Pagination.Page prev Nothing results
|
||||||
|
where
|
||||||
|
prev = if offset > 0 then Just $ Pagination.Pagination limit (max 0 (offset - limit)) else Nothing
|
||||||
baseQuery =
|
baseQuery =
|
||||||
selectSimple
|
selectSimple
|
||||||
[ "cards.scryfall_id",
|
[ "cards.scryfall_id",
|
||||||
|
@ -234,7 +244,7 @@ searchCards dbFile q sortBy inCollection =
|
||||||
ELSE cards.color_identity END ASC|]
|
ELSE cards.color_identity END ASC|]
|
||||||
<> orderBy "cards.name ASC"
|
<> orderBy "cards.name ASC"
|
||||||
<> parameter ":last_update_key" ("last_update" :: T.Text)
|
<> parameter ":last_update_key" ("last_update" :: T.Text)
|
||||||
<> limit 10
|
<> limitOffset (1 + Pagination.limit pagination) (Pagination.offset pagination)
|
||||||
query =
|
query =
|
||||||
mconcat $
|
mconcat $
|
||||||
catMaybes
|
catMaybes
|
||||||
|
|
12
src/Tutor/Pagination.hs
Normal file
12
src/Tutor/Pagination.hs
Normal file
|
@ -0,0 +1,12 @@
|
||||||
|
module Tutor.Pagination (Pagination(..), Page(..)) where
|
||||||
|
|
||||||
|
data Pagination = Pagination
|
||||||
|
{ limit :: Int
|
||||||
|
, offset :: Int
|
||||||
|
}
|
||||||
|
|
||||||
|
data Page a = Page
|
||||||
|
{ previous :: Maybe Pagination
|
||||||
|
, next :: Maybe Pagination
|
||||||
|
, items :: [a]
|
||||||
|
}
|
|
@ -96,7 +96,7 @@ toQuery select =
|
||||||
[] -> Nothing
|
[] -> Nothing
|
||||||
xs -> Just $ "ORDER BY " <> sqlJoin ", " xs
|
xs -> Just $ "ORDER BY " <> sqlJoin ", " xs
|
||||||
sqlLimitOffset = case (selectLimit select, selectOffset select) of
|
sqlLimitOffset = case (selectLimit select, selectOffset select) of
|
||||||
(Just l, Just o) -> Just "LIMIT :__limit, :__offset"
|
(Just l, Just o) -> Just "LIMIT :__limit OFFSET :__offset"
|
||||||
(Just l, Nothing) -> Just "LIMIT :__limit"
|
(Just l, Nothing) -> Just "LIMIT :__limit"
|
||||||
_ -> Nothing
|
_ -> Nothing
|
||||||
|
|
||||||
|
|
Loading…
Reference in a new issue