4 Commits

Author SHA1 Message Date
f55a982f57 wip 2018-08-28 22:41:59 +03:00
3f1b2d3588 wip 2018-08-28 22:38:57 +03:00
83e39cbe6c Start implementing channel listing (#2) 2018-08-28 22:38:07 +03:00
e50e234747 Start working opds (#2)
- Relates to #2
2018-08-28 22:37:57 +03:00
6 changed files with 19 additions and 43 deletions

View File

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

View File

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

View File

@ -17,16 +17,14 @@
module API.Catalogue (VersionedAPI, handler) where
import Types
import Servant hiding (contentType)
import Servant
import ClassyPrelude
import GHC.TypeLits
import Server.Auth
import Servant.Auth as SA
import Servant.XML
import qualified Database.Channel as Channel
import Database.Book (Book(..))
import Database
import qualified API.Books
-- 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
@ -104,25 +102,19 @@ instance VersionedCatalog AppM 1 where
getChannels = getChannelsV1
getBooks = getBooksV1
relUrl :: Link -> Rel
relUrl x = Rel ("/api/current/" <> (pack . uriPath . linkURI $ x))
relUrl :: Text -> Rel
relUrl x = Rel ("/api/current/" <> x)
getBooksV1 :: Channel.ChannelID -> SafeUser -> AppM (Catalog 1)
getBooksV1 channelID SafeUser{username} = do
getBooksV1 identifier SafeUser{} = do
updated <- liftIO getCurrentTime
let self = relUrl selfUrl
start = relUrl startUrl
selfUrl = safeLink (Proxy @(BaseAPI 1)) (Proxy @(ChannelCatalog 1)) channelID
startUrl = safeLink (Proxy @(BaseAPI 1)) (Proxy @(RootCatalog 1))
selfUrl = pack . uriPath . linkURI $ safeLink (Proxy @(BaseAPI 1)) (Proxy @(ChannelCatalog 1)) identifier
startUrl = pack . uriPath . linkURI $ safeLink (Proxy @(BaseAPI 1)) (Proxy @(RootCatalog 1))
entries = mempty
pagination = Pagination Nothing Nothing
entries <- map (toEntry updated) <$> runDB (Channel.channelBooks username channelID)
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{username} = do
@ -131,7 +123,7 @@ getChannelsV1 SafeUser{username} = do
-- I'm not sure if this safe link approach is really useable with this
-- api hierarchy since I can't access the topmost api from here. Also
-- authentication would bring a little bit of extra effort as well
selfUrl = safeLink (Proxy @(BaseAPI 1)) (Proxy @(RootCatalog 1))
selfUrl = pack . uriPath . linkURI $ safeLink (Proxy @(BaseAPI 1)) (Proxy @(RootCatalog 1))
start = self
pagination = Pagination Nothing Nothing
entries <- map (fromChannel updated) <$> runDB (Channel.userChannels username)
@ -139,7 +131,7 @@ getChannelsV1 SafeUser{username} = do
where
fromChannel :: UTCTime -> Channel.Channel -> Entry 1
fromChannel updated Channel.Channel{..} =
let url = safeLink (Proxy @(BaseAPI 1)) (Proxy @(ChannelCatalog 1)) identifier
let url = pack . uriPath . linkURI $ safeLink (Proxy @(BaseAPI 1)) (Proxy @(ChannelCatalog 1)) identifier
self = relUrl url
in EntryV1 channel channel updated channel (Left $ SubSection self)

View File

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

View File

@ -11,9 +11,8 @@ module Database.Channel
, Visibility(..)
, clearChannels
, booksChannels
, channelBooks
, Channel(..)
, ChannelID(..) )
, ChannelID )
where
import ClassyPrelude
@ -81,19 +80,6 @@ insertChannel username channel visibility = runMaybeT $ do
restrict (user .== literal username)
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 bookId = fromRels <$> query q
where

View File

@ -42,7 +42,7 @@ instance SqlType Username where
newtype UserID = UserID {unUserID :: Int} deriving (Show)
newtype BookID = BookID {unBookID :: Int} deriving (Show, ToJSON, FromJSON, FromHttpApiData, Eq, Ord, ToHttpApiData)
newtype BookID = BookID {unBookID :: Int} deriving (Show, ToJSON, FromJSON, FromHttpApiData, Eq, Ord)
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
, contentHash :: Maybe HashDigest
, contentType :: Text
, title :: Text
, title :: Maybe Text
, description :: Maybe Text
, owner :: UserID }
deriving (Show, Generic)