Compare commits

...

2 Commits

Author SHA1 Message Date
a7f75ee20e List books (#2) 2018-08-28 23:25:48 +03:00
efa7ed7f92 WIP 2018-08-28 23:14:11 +03:00
6 changed files with 37 additions and 13 deletions

View File

@ -27,8 +27,8 @@ data Index = Index
type API = Get '[HTML] (AppView Index) type API = Get '[HTML] (AppView Index)
:<|> Users.API :<|> Users.API
:<|> "api" :> Channels.API :<|> "api" :> "current" :> Channels.API
:<|> "api" :> Books.API :<|> "api" :> "current" :> Books.API
:<|> "api" :> "1" :> Catalogue.VersionedAPI 1 :<|> "api" :> "1" :> Catalogue.VersionedAPI 1
:<|> "api" :> "current" :> Catalogue.VersionedAPI 1 :<|> "api" :> "current" :> Catalogue.VersionedAPI 1

View File

@ -36,14 +36,14 @@ import Crypto.Hash (digestFromByteString)
data JsonBook = JsonBook { identifier :: BookID data JsonBook = JsonBook { identifier :: BookID
, contentType :: Text , contentType :: Text
, title :: Maybe Text , title :: Text
, description :: Maybe Text , description :: Maybe Text
, channels :: [Text] , channels :: [Text]
, tags :: [Text] } , tags :: [Text] }
deriving (Generic, Show) deriving (Generic, Show)
data PostBook = PostBook { contentType :: Text data PostBook = PostBook { contentType :: Text
, title :: Maybe Text , title :: Text
, description :: Maybe Text , description :: Maybe Text
, channels :: [Text] , channels :: [Text]
, tags :: [Text] } , tags :: [Text] }
@ -61,7 +61,9 @@ type BaseAPI = "books" :> Get '[JSON] [JsonBook]
:<|> "books" :> ReqBody '[JSON] PostBook :> Post '[JSON] JsonBook :<|> "books" :> ReqBody '[JSON] PostBook :> Post '[JSON] JsonBook
:<|> "books" :> Capture "book_id" BookID :> "meta" :> ReqBody '[JSON] JsonBook :> Put '[JSON] JsonBook :<|> "books" :> Capture "book_id" BookID :> "meta" :> ReqBody '[JSON] JsonBook :> Put '[JSON] JsonBook
:<|> "books" :> Capture "book_id" BookID :> ReqBody '[OctetStream] ByteString :> Put '[JSON] NoContent :<|> "books" :> Capture "book_id" BookID :> ReqBody '[OctetStream] ByteString :> Put '[JSON] NoContent
:<|> "books" :> Capture "book_id" BookID :> Get '[OctetStream] ByteString :<|> GetBook
type GetBook = "books" :> Capture "book_id" BookID :> Get '[OctetStream] ByteString
handler :: ServerT API AppM handler :: ServerT API AppM
handler user = listBooksHandler user handler user = listBooksHandler user

View File

@ -17,14 +17,16 @@
module API.Catalogue (VersionedAPI, handler) where module API.Catalogue (VersionedAPI, handler) where
import Types import Types
import Servant import Servant hiding (contentType)
import ClassyPrelude import ClassyPrelude
import GHC.TypeLits import GHC.TypeLits
import Server.Auth import Server.Auth
import Servant.Auth as SA import Servant.Auth as SA
import Servant.XML import Servant.XML
import qualified Database.Channel as Channel import qualified Database.Channel as Channel
import Database.Book (Book(..))
import Database import Database
import qualified API.Books
-- This is my first try on going to versioned apis, things might change -- This is my first try on going to versioned apis, things might change
-- I think my rule of thumb is that you can add new things as you want, but -- I think my rule of thumb is that you can add new things as you want, but
@ -106,15 +108,21 @@ relUrl :: Link -> Rel
relUrl x = Rel ("/api/current/" <> (pack . uriPath . linkURI $ x)) relUrl x = Rel ("/api/current/" <> (pack . uriPath . linkURI $ x))
getBooksV1 :: Channel.ChannelID -> SafeUser -> AppM (Catalog 1) getBooksV1 :: Channel.ChannelID -> SafeUser -> AppM (Catalog 1)
getBooksV1 identifier SafeUser{} = do getBooksV1 channelID SafeUser{username} = do
updated <- liftIO getCurrentTime updated <- liftIO getCurrentTime
let self = relUrl selfUrl let self = relUrl selfUrl
start = relUrl startUrl start = relUrl startUrl
selfUrl = safeLink (Proxy @(BaseAPI 1)) (Proxy @(ChannelCatalog 1)) identifier selfUrl = safeLink (Proxy @(BaseAPI 1)) (Proxy @(ChannelCatalog 1)) channelID
startUrl = safeLink (Proxy @(BaseAPI 1)) (Proxy @(RootCatalog 1)) startUrl = safeLink (Proxy @(BaseAPI 1)) (Proxy @(RootCatalog 1))
entries = mempty
pagination = Pagination Nothing Nothing pagination = Pagination Nothing Nothing
entries <- map (toEntry updated) <$> runDB (Channel.channelBooks username channelID)
pure CatalogV1{..} pure CatalogV1{..}
where
toEntry updated Book{description,title,identifier=bookId} =
let content = fromMaybe "no content" description
identifier = pack . show $ bookId
link = Right (Acquisition (relUrl (safeLink (Proxy @API.Books.BaseAPI) (Proxy @API.Books.GetBook) bookId)))
in EntryV1{..}
getChannelsV1 :: SafeUser -> AppM (Catalog 1) getChannelsV1 :: SafeUser -> AppM (Catalog 1)
getChannelsV1 SafeUser{username} = do getChannelsV1 SafeUser{username} = do

View File

@ -51,7 +51,7 @@ getBook identifier owner = listToMaybe . fromRels <$> query q
return book return book
data InsertBook = InsertBook { contentType :: Text data InsertBook = InsertBook { contentType :: Text
, title :: Maybe Text , title :: Text
, description :: Maybe Text , description :: Maybe Text
, owner :: Username } , owner :: Username }
@ -68,7 +68,7 @@ insertBook InsertBook{..} = do
data UpdateBook = UpdateBook { identifier :: BookID data UpdateBook = UpdateBook { identifier :: BookID
, contentType :: Text , contentType :: Text
, title :: Maybe Text , title :: Text
, description :: Maybe Text , description :: Maybe Text
, owner :: Username , owner :: Username
, tags :: [Text] , tags :: [Text]

View File

@ -11,6 +11,7 @@ module Database.Channel
, Visibility(..) , Visibility(..)
, clearChannels , clearChannels
, booksChannels , booksChannels
, channelBooks
, Channel(..) , Channel(..)
, ChannelID(..) ) , ChannelID(..) )
where where
@ -80,6 +81,19 @@ insertChannel username channel visibility = runMaybeT $ do
restrict (user .== literal username) restrict (user .== literal username)
return userId return userId
channelBooks :: (MonadSelda m, MonadMask m, MonadIO m) => Username -> ChannelID -> m [Book]
channelBooks username identifier = fromRels <$> query q
where
q = do
channelId :*: bookId' <- select (gen bookChannels)
channelId' :*: _ :*: owner :*: _ <- select (gen channels)
userId :*: _ :*: username' :*: _ <- select (gen users)
book@(bookId :*: _) <- select (gen books)
restrict (username' .== literal username .&& owner .== userId)
restrict (channelId .== literal identifier .&& channelId .== channelId')
restrict (bookId .== bookId')
return book
booksChannels :: (MonadSelda m, MonadMask m, MonadIO m) => BookID -> m [Channel] booksChannels :: (MonadSelda m, MonadMask m, MonadIO m) => BookID -> m [Channel]
booksChannels bookId = fromRels <$> query q booksChannels bookId = fromRels <$> query q
where where

View File

@ -42,7 +42,7 @@ instance SqlType Username where
newtype UserID = UserID {unUserID :: Int} deriving (Show) newtype UserID = UserID {unUserID :: Int} deriving (Show)
newtype BookID = BookID {unBookID :: Int} deriving (Show, ToJSON, FromJSON, FromHttpApiData, Eq, Ord) newtype BookID = BookID {unBookID :: Int} deriving (Show, ToJSON, FromJSON, FromHttpApiData, Eq, Ord, ToHttpApiData)
newtype ChannelID = ChannelID {unChannelID :: Int} deriving (Show, ToHttpApiData, FromHttpApiData, ToJSON, FromJSON) newtype ChannelID = ChannelID {unChannelID :: Int} deriving (Show, ToHttpApiData, FromHttpApiData, ToJSON, FromJSON)
@ -101,7 +101,7 @@ newtype HashDigest = HashDigest { unHex :: ByteString } deriving Show
data Book = Book { identifier :: BookID data Book = Book { identifier :: BookID
, contentHash :: Maybe HashDigest , contentHash :: Maybe HashDigest
, contentType :: Text , contentType :: Text
, title :: Maybe Text , title :: Text
, description :: Maybe Text , description :: Maybe Text
, owner :: UserID } , owner :: UserID }
deriving (Show, Generic) deriving (Show, Generic)