5 Commits

Author SHA1 Message Date
d792cb2a81 Merge branch 'sandbox/MasseR/2-opds' of MasseR/ebook-manager into master
Closes #2
2018-08-28 23:28:24 +03:00
cd086165db Initial OPDS support
Channel listing (#2)

List books (#2)

Closes (#2)
2018-08-28 23:26:49 +03:00
0037d4691e #20 Update privacy settings on channels (#22)
- Closes #20
2018-08-15 23:25:06 +03:00
e61fb66c06 #13 Add visibility information to channels (#21)
- closes #13
2018-08-15 22:38:36 +03:00
8b04f3760e Complete functions (#15) 2018-08-15 22:11:30 +03:00
11 changed files with 219 additions and 74 deletions

View File

@ -1,6 +1,3 @@
-- Initial ebook-manager.cabal generated by cabal init. For further
-- documentation, see http://haskell.org/cabal/users-guide/
name: ebook-manager name: ebook-manager
version: 0.1.0.0 version: 0.1.0.0
-- synopsis: -- synopsis:

View File

@ -0,0 +1 @@
alter table channels add column visibility text NOT NULL default 'Private';

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
@ -97,9 +99,9 @@ postBookMetaHandler auth PostBook{..} = flip requireLoggedIn auth $ \SafeUser{us
putBookMetaHandler :: AuthResult SafeUser -> BookID -> JsonBook -> AppM JsonBook putBookMetaHandler :: AuthResult SafeUser -> BookID -> JsonBook -> AppM JsonBook
putBookMetaHandler auth bookId b@JsonBook{..} putBookMetaHandler auth bookId JsonBook{..}
| bookId == identifier = requireBookOwner auth bookId $ \SafeUser{username=owner} -> | bookId == identifier = requireBookOwner auth bookId $ \SafeUser{username=owner} ->
maybe (throwM err403) (const (return b)) =<< runDB (updateBook UpdateBook{..}) maybe (throwM err403) (return . view (super @JsonBook)) =<< runDB (updateBook UpdateBook{..})
| otherwise = throwM err403 | otherwise = throwM err403
listBooksHandler :: AuthResult SafeUser -> AppM [JsonBook] listBooksHandler :: AuthResult SafeUser -> AppM [JsonBook]

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
@ -96,15 +98,40 @@ instance ToNode (Catalog 1) where
class Monad m => VersionedCatalog m (v :: Nat) where class Monad m => VersionedCatalog m (v :: Nat) where
getChannels :: SafeUser -> m (Catalog v) getChannels :: SafeUser -> m (Catalog v)
getBooks :: Channel.ChannelID -> SafeUser -> m (Catalog v)
instance VersionedCatalog AppM 1 where instance VersionedCatalog AppM 1 where
getChannels SafeUser{username} = do getChannels = getChannelsV1
getBooks = getBooksV1
relUrl :: Link -> Rel
relUrl x = Rel ("/api/current/" <> (pack . uriPath . linkURI $ x))
getBooksV1 :: Channel.ChannelID -> SafeUser -> AppM (Catalog 1)
getBooksV1 channelID SafeUser{username} = do
updated <- liftIO getCurrentTime updated <- liftIO getCurrentTime
let self = Rel ("/api/current/" <> selfUrl) let self = relUrl selfUrl
start = relUrl startUrl
selfUrl = safeLink (Proxy @(BaseAPI 1)) (Proxy @(ChannelCatalog 1)) channelID
startUrl = safeLink (Proxy @(BaseAPI 1)) (Proxy @(RootCatalog 1))
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
updated <- liftIO getCurrentTime
let self = relUrl selfUrl
-- I'm not sure if this safe link approach is really useable with this -- 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 -- api hierarchy since I can't access the topmost api from here. Also
-- authentication would bring a little bit of extra effort as well -- authentication would bring a little bit of extra effort as well
selfUrl = pack . uriPath . linkURI $ safeLink (Proxy @(BaseAPI 1)) (Proxy @(RootCatalog 1)) selfUrl = safeLink (Proxy @(BaseAPI 1)) (Proxy @(RootCatalog 1))
start = self start = self
pagination = Pagination Nothing Nothing pagination = Pagination Nothing Nothing
entries <- map (fromChannel updated) <$> runDB (Channel.userChannels username) entries <- map (fromChannel updated) <$> runDB (Channel.userChannels username)
@ -112,14 +139,16 @@ instance VersionedCatalog AppM 1 where
where where
fromChannel :: UTCTime -> Channel.Channel -> Entry 1 fromChannel :: UTCTime -> Channel.Channel -> Entry 1
fromChannel updated Channel.Channel{..} = fromChannel updated Channel.Channel{..} =
let url = pack . uriPath . linkURI $ safeLink (Proxy @(BaseAPI 1)) (Proxy @(ChannelCatalog 1)) identifier let url = safeLink (Proxy @(BaseAPI 1)) (Proxy @(ChannelCatalog 1)) identifier
self = Rel ("/api/current/" <> url) self = relUrl url
in EntryV1 channel channel updated channel (Left $ SubSection self) in EntryV1 channel channel updated channel (Left $ SubSection self)
type VersionedAPI (v :: Nat) = Auth '[SA.BasicAuth, SA.JWT] SafeUser :> BaseAPI v type VersionedAPI (v :: Nat) = Auth '[SA.BasicAuth, SA.JWT] SafeUser :> BaseAPI v
type RootCatalog (v :: Nat) = "catalog" :> Get '[XML] (Catalog v) type CatalogContent = '[XML, OPDS]
type ChannelCatalog (v :: Nat) = "catalog" :> "channel" :> Capture "channel_id" Channel.ChannelID :> Get '[XML] (Catalog v)
type RootCatalog (v :: Nat) = "catalog" :> Get CatalogContent (Catalog v)
type ChannelCatalog (v :: Nat) = "catalog" :> "channel" :> Capture "channel_id" Channel.ChannelID :> Get CatalogContent (Catalog v)
type BaseAPI (v :: Nat) = RootCatalog v type BaseAPI (v :: Nat) = RootCatalog v
:<|> ChannelCatalog v :<|> ChannelCatalog v
@ -127,6 +156,8 @@ handler :: forall v. VersionedCatalog AppM v => ServerT (VersionedAPI v) AppM
handler auth = catalogRoot :<|> catalogChannels handler auth = catalogRoot :<|> catalogChannels
where where
catalogChannels :: Channel.ChannelID -> AppM (Catalog v) catalogChannels :: Channel.ChannelID -> AppM (Catalog v)
catalogChannels _ = throwM err403{errBody="Not implemented"} -- Channel specific catalog returns tags inside the catalog
catalogChannels identifier = flip requireLoggedIn auth (getBooks identifier)
catalogRoot :: AppM (Catalog v) catalogRoot :: AppM (Catalog v)
-- catalog root returns channels
catalogRoot = flip requireLoggedIn auth getChannels catalogRoot = flip requireLoggedIn auth getChannels

View File

@ -11,6 +11,8 @@
{-# Language FlexibleInstances #-} {-# Language FlexibleInstances #-}
{-# Language TypeApplications #-} {-# Language TypeApplications #-}
{-# Language DataKinds #-} {-# Language DataKinds #-}
{-# Language DuplicateRecordFields #-}
{-# Language NamedFieldPuns #-}
module API.Channels (API, handler, JsonChannel(..)) where module API.Channels (API, handler, JsonChannel(..)) where
import Servant import Servant
@ -25,18 +27,37 @@ import Data.Aeson
import Control.Lens import Control.Lens
import Data.Generics.Product import Data.Generics.Product
data JsonChannel = JsonChannel { channel :: Text } deriving (Show, Generic) data JsonChannel = JsonChannel { channel :: Text
, visibility :: Visibility }
deriving (Show, Generic)
data UpdateChannel = UpdateChannel { identifier :: ChannelID
, channel :: Text
, visibility :: Visibility }
deriving (Show, Generic)
instance ToJSON JsonChannel instance ToJSON JsonChannel
instance FromJSON JsonChannel instance FromJSON JsonChannel
instance ToJSON UpdateChannel
instance FromJSON UpdateChannel
type API = Auth '[SA.BasicAuth, SA.Cookie, SA.JWT] SafeUser :> BaseAPI type API = Auth '[SA.BasicAuth, SA.Cookie, SA.JWT] SafeUser :> BaseAPI
type BaseAPI = "channels" :> ReqBody '[JSON] JsonChannel :> Put '[JSON] JsonChannel type BaseAPI = "channels" :> ReqBody '[JSON] JsonChannel :> Post '[JSON] UpdateChannel
:<|> "channels" :> Capture "channel_id" ChannelID :> ReqBody '[JSON] UpdateChannel :> Put '[JSON] UpdateChannel
:<|> "channels" :> Get '[JSON] [JsonChannel] :<|> "channels" :> Get '[JSON] [JsonChannel]
handler :: ServerT API AppM handler :: ServerT API AppM
handler user = newChannelHandler user :<|> listChannelsHandler user handler user = newChannelHandler user :<|> updateChannelHandler user :<|> listChannelsHandler user
requireChannelOwner :: AuthResult SafeUser -> ChannelID -> (SafeUser -> AppM a) -> AppM a
requireChannelOwner auth channelId f = flip requireLoggedIn auth $ \u@SafeUser{username} -> do
unlessM (runDB . channelExists $ channelId) $ throwM err404
runDB (isChannelOwner channelId username) >>= \o -> if o then f u else throwM err403
updateChannelHandler :: AuthResult SafeUser -> ChannelID -> UpdateChannel -> AppM UpdateChannel
updateChannelHandler auth channelId UpdateChannel{visibility} = requireChannelOwner auth channelId $ \_ -> do
mChannel <- fmap toChannel <$> runDB (updateChannelPrivacy channelId visibility)
maybe (throwM err403) return mChannel
listChannelsHandler :: AuthResult SafeUser -> AppM [JsonChannel] listChannelsHandler :: AuthResult SafeUser -> AppM [JsonChannel]
listChannelsHandler = requireLoggedIn $ \user -> listChannelsHandler = requireLoggedIn $ \user ->
@ -44,8 +65,11 @@ listChannelsHandler = requireLoggedIn $ \user ->
-- use the 'channel' accessor somehow or export it -- use the 'channel' accessor somehow or export it
fmap (\Channel{..} -> JsonChannel{..}) <$> runDB (userChannels (view (field @"username") user)) fmap (\Channel{..} -> JsonChannel{..}) <$> runDB (userChannels (view (field @"username") user))
newChannelHandler :: AuthResult SafeUser -> JsonChannel -> AppM JsonChannel newChannelHandler :: AuthResult SafeUser -> JsonChannel -> AppM UpdateChannel
newChannelHandler auth ch@JsonChannel{..} = flip requireLoggedIn auth $ \user -> do newChannelHandler auth JsonChannel{..} = flip requireLoggedIn auth $ \user -> do
$logInfo $ "Creating channel for user " <> pack (show user) $logInfo $ "Creating channel for user " <> pack (show user)
runDB (insertChannel (view (field @"username") user) channel) mChannel <- fmap toChannel <$> runDB (insertChannel (view (field @"username") user) channel visibility)
return ch maybe (throwM err403{errBody="Could not create the channel"}) return mChannel
toChannel :: Channel -> UpdateChannel
toChannel Channel{..} = UpdateChannel{..}

View File

@ -23,8 +23,11 @@ import Database
import Database.Selda import Database.Selda
import Database.Selda.Generic import Database.Selda.Generic
import Database.Tag (attachTag, clearTags) import Control.Lens (view)
import Database.Channel (attachChannel, clearChannels) import Data.Generics.Product
import Database.Tag (booksTags, attachTag, clearTags)
import Database.Channel (booksChannels, attachChannel, clearChannels)
usersBooks :: (MonadSelda m, MonadMask m, MonadIO m) => Username -> m [Book] usersBooks :: (MonadSelda m, MonadMask m, MonadIO m) => Username -> m [Book]
usersBooks username = fromRels <$> query q usersBooks username = fromRels <$> query q
@ -48,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 }
@ -65,11 +68,12 @@ 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]
, channels :: [Text] } , channels :: [Text] }
deriving (Show, Generic)
bookExists :: (MonadSelda m, MonadMask m, MonadIO m) => BookID -> m Bool bookExists :: (MonadSelda m, MonadMask m, MonadIO m) => BookID -> m Bool
bookExists identifier = not . null <$> query q bookExists identifier = not . null <$> query q
@ -92,23 +96,32 @@ bookOwner' identifier username = do
return (userId :*: bookId) return (userId :*: bookId)
updateBook :: (MonadSelda m, MonadMask m, MonadIO m) => UpdateBook -> m (Maybe UpdateBook) updateBook :: (MonadSelda m, MonadMask m, MonadIO m) => UpdateBook -> m (Maybe UpdateBook)
updateBook book@UpdateBook{..} = do updateBook UpdateBook{..} = do
clearTags identifier >> connectTags clearTags identifier >> connectTags
clearChannels identifier >> connectChannels clearChannels identifier >> connectChannels
updateBook' updateBook'
getUpdateBook identifier owner
where where
connectTags = mapM_ (attachTag owner identifier) tags connectTags = mapM_ (attachTag owner identifier) tags
connectChannels = mapM_ (attachChannel owner identifier) channels connectChannels = mapM_ (attachChannel owner identifier) channels
updateBook' = do updateBook' = do
mUserId <- query (bookOwner' identifier owner) mUserId <- query (bookOwner' identifier owner)
forM (listToMaybe mUserId) $ \_userId -> do forM_ (listToMaybe mUserId) $ \_userId -> do
update_ (gen books) predicate (\b -> b `with` [ pContentType := literal contentType update_ (gen books) predicate (\b -> b `with` [ pContentType := literal contentType
, pTitle := literal title , pTitle := literal title
, pDescription := literal description ]) , pDescription := literal description ])
return book
_ :*: _ :*: pContentType :*: pTitle :*: pDescription :*: _ = selectors (gen books) _ :*: _ :*: pContentType :*: pTitle :*: pDescription :*: _ = selectors (gen books)
predicate (bookId :*: _) = bookId .== literal identifier predicate (bookId :*: _) = bookId .== literal identifier
getUpdateBook :: (MonadMask m, MonadIO m, MonadSelda m) => BookID -> Username -> m (Maybe UpdateBook)
getUpdateBook bookId username = do
mBook <- getBook bookId username
forM mBook $ \Book{..} -> do
channels <- map (view (field @"channel")) <$> booksChannels bookId
tags <- map (view (field @"tag")) <$> booksTags bookId
return UpdateBook{owner=username,..}
setContent :: (MonadSelda m, MonadMask m, MonadIO m) => BookID -> Username -> HashDigest -> m () setContent :: (MonadSelda m, MonadMask m, MonadIO m) => BookID -> Username -> HashDigest -> m ()
setContent identifier owner digest = do setContent identifier owner digest = do
mOwner <- query (bookOwner' identifier owner) mOwner <- query (bookOwner' identifier owner)

View File

@ -4,11 +4,16 @@
module Database.Channel module Database.Channel
( userChannels ( userChannels
, insertChannel , insertChannel
, channelExists
, isChannelOwner
, updateChannelPrivacy
, attachChannel , attachChannel
, Visibility(..)
, clearChannels , clearChannels
, booksChannels , booksChannels
, channelBooks
, Channel(..) , Channel(..)
, ChannelID ) , ChannelID(..) )
where where
import ClassyPrelude import ClassyPrelude
@ -17,29 +22,79 @@ import Database
import Database.Selda import Database.Selda
import Database.Selda.Generic import Database.Selda.Generic
import Control.Monad.Trans.Maybe
getChannel :: (MonadSelda m, MonadMask m, MonadIO m) => ChannelID -> m (Maybe Channel)
getChannel identifier = listToMaybe . fromRels <$> query q
where
q = do
ch@(channelId :*: _) <- select (gen channels)
restrict (channelId .== literal identifier)
return ch
channelExists :: (MonadSelda m, MonadMask m, MonadIO m) => ChannelID -> m Bool
channelExists identifier = not . null <$> getChannel identifier
isChannelOwner :: (MonadSelda m, MonadIO m, MonadMask m) => ChannelID -> Username -> m Bool
isChannelOwner identifier username = not . null <$> query q
where
q = do
userId :*: _ :*: username' :*: _ <- select (gen users)
channelId :*: _ :*: channelOwner :*: _ <- select (gen channels)
restrict (userId .== channelOwner)
restrict (username' .== literal username)
restrict (channelId .== literal identifier)
return channelId
userChannels :: (MonadMask m, MonadIO m) => Username -> SeldaT m [Channel] userChannels :: (MonadMask m, MonadIO m) => Username -> SeldaT m [Channel]
userChannels username = fromRels <$> query q userChannels username = fromRels <$> query q
where where
q = do q = do
userId :*: _ :*: username' :*: _ <- select (gen users) userId :*: _ :*: username' :*: _ <- select (gen users)
channel@(_ :*: _ :*: owner) <- select (gen channels) channel@(_ :*: _ :*: owner :*: _) <- select (gen channels)
restrict (owner .== userId) restrict (owner .== userId)
restrict (username' .== literal username) restrict (username' .== literal username)
return channel return channel
insertChannel :: (MonadMask m, MonadIO m) => Username -> Text -> SeldaT m () updateChannelPrivacy :: (MonadMask m, MonadIO m, MonadSelda m) => ChannelID -> Visibility -> m (Maybe Channel)
insertChannel username channel = do updateChannelPrivacy channelId visibility = do
mUserId <- listToMaybe <$> getUser void $ update (gen channels) predicate (\channel -> channel `with` [pVis := literal visibility])
void $ forM mUserId $ \userId -> getChannel channelId
insertUnless (gen channels) (doesNotExist userId) [ def :*: channel :*: userId ]
where where
doesNotExist userId (_ :*: channel' :*: userId') = channel' .== literal channel .&& userId' .== literal userId predicate (channelId' :*: _) = channelId' .== literal channelId
_ :*: _ :*: _ :*: pVis = selectors (gen channels)
insertChannel :: (MonadMask m, MonadIO m, MonadSelda m) => Username -> Text -> Visibility -> m (Maybe Channel)
insertChannel username channel visibility = runMaybeT $ do
userId <- MaybeT (listToMaybe <$> getUser)
channelId <- toChannelId <$> MaybeT (insertUnless (gen channels) (doesNotExist userId) [ def :*: channel :*: userId :*: visibility ])
MaybeT (listToMaybe . fromRels <$> query (q channelId))
where
q channelId = do
ch@(channelId' :*: _) <- select (gen channels)
restrict (channelId' .== literal channelId)
return ch
toChannelId = ChannelID . fromRowId
doesNotExist userId (_ :*: channel' :*: userId' :*: _) = channel' .== literal channel .&& userId' .== literal userId
getUser = query $ do getUser = query $ do
userId :*: _ :*: user :*: _ <- select (gen users) userId :*: _ :*: user :*: _ <- select (gen users)
restrict (user .== literal username) restrict (user .== literal username)
return userId return userId
booksChannels :: (MonadMask m, MonadIO m) => BookID -> SeldaT m [Channel] 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 booksChannels bookId = fromRels <$> query q
where where
q = do q = do
@ -51,8 +106,8 @@ booksChannels bookId = fromRels <$> query q
attachChannel :: (MonadMask m, MonadIO m, MonadSelda m) => Username -> BookID -> Text -> m () attachChannel :: (MonadMask m, MonadIO m, MonadSelda m) => Username -> BookID -> Text -> m ()
attachChannel username bookId channel = do attachChannel username bookId channel = do
-- XXX: test what happens if channel doesn't exist mCh <- fromRels <$> query channelQ
[Channel{identifier}] <- fromRels <$> query channelQ forM_ mCh $ \Channel{identifier} ->
whenM (null <$> query (attachQ identifier)) $ whenM (null <$> query (attachQ identifier)) $
void $ insertGen bookChannels [BookChannel identifier bookId] void $ insertGen bookChannels [BookChannel identifier bookId]
where where
@ -62,7 +117,7 @@ attachChannel username bookId channel = do
return channelId' return channelId'
channelQ = do channelQ = do
userId :*: _ :*: username' :*: _ <- select (gen users) userId :*: _ :*: username' :*: _ <- select (gen users)
ch@(_ :*: channel' :*: owner) <- select (gen channels) ch@(_ :*: channel' :*: owner :*: _) <- select (gen channels)
restrict (username' .== literal username) restrict (username' .== literal username)
restrict (owner .== userId) restrict (owner .== userId)
restrict (channel' .== literal channel) restrict (channel' .== literal channel)

View File

@ -42,9 +42,9 @@ 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) newtype ChannelID = ChannelID {unChannelID :: Int} deriving (Show, ToHttpApiData, FromHttpApiData, ToJSON, FromJSON)
newtype TagID = TagID {unTagID :: Int} deriving (Show) newtype TagID = TagID {unTagID :: Int} deriving (Show)
@ -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)
@ -124,9 +124,22 @@ data Tag = Tag { identifier :: TagID
, owner :: UserID } , owner :: UserID }
deriving (Show, Generic) deriving (Show, Generic)
data Visibility = Public | Private | Followers
deriving (Show, Read, Generic)
instance ToJSON Visibility
instance FromJSON Visibility
instance SqlType Visibility where
mkLit = LCustom . LText . pack . show
fromSql (SqlString x) = fromMaybe (error "fromSql: Not a valid visibility token") . readMay . unpack $ x
fromSql _ = error "fromSql: Not a valid visibility token"
defaultValue = mkLit Private
data Channel = Channel { identifier :: ChannelID data Channel = Channel { identifier :: ChannelID
, channel :: Text , channel :: Text
, owner :: UserID } , owner :: UserID
, visibility :: Visibility }
deriving (Show, Generic) deriving (Show, Generic)
tags :: GenTable Tag tags :: GenTable Tag

View File

@ -16,15 +16,13 @@ import Database.Schema
import Database import Database
import Database.Selda import Database.Selda
import Database.Selda.Generic import Database.Selda.Generic
import Control.Monad.Trans.Maybe
upsertTag :: (MonadMask m, MonadIO m, MonadSelda m) => Username -> Text -> m Tag upsertTag :: (MonadMask m, MonadIO m, MonadSelda m) => Username -> Text -> m (Maybe Tag)
upsertTag username tag = do upsertTag username tag = runMaybeT $ do
-- I want this to error out if some data is invariant is wrong and roll back userId <- MaybeT (listToMaybe <$> query userQ)
-- the transaction. Also as a side note, run this in a transaction plz void $ lift $ upsert (gen tags) (predicate userId) id [toRel (Tag def tag userId)]
[userId] <- query userQ MaybeT (listToMaybe . fromRels <$> query (tagQ userId))
void $ upsert (gen tags) (predicate userId) id [toRel (Tag def tag userId)]
[t] <- fromRels <$> query (tagQ userId)
return t
where where
predicate userId (_ :*: tag' :*: owner) = tag' .== literal tag .&& owner .== literal userId predicate userId (_ :*: tag' :*: owner) = tag' .== literal tag .&& owner .== literal userId
tagQ userId = do tagQ userId = do
@ -48,7 +46,8 @@ booksTags bookId = fromRels <$> query q
attachTag :: (MonadMask m, MonadIO m, MonadSelda m) => Username -> BookID -> Text -> m () attachTag :: (MonadMask m, MonadIO m, MonadSelda m) => Username -> BookID -> Text -> m ()
attachTag username bookId tag = do attachTag username bookId tag = do
Tag{identifier} <- upsertTag username tag maybeT <- upsertTag username tag
forM_ maybeT $ \Tag{identifier} -> do
whenM (null <$> query (tagQ identifier)) $ whenM (null <$> query (tagQ identifier)) $
void $ insertGen bookTags [BookTag identifier bookId] void $ insertGen bookTags [BookTag identifier bookId]
where where

View File

@ -1,9 +1,11 @@
{-# Language OverloadedStrings #-} {-# Language OverloadedStrings #-}
{-# Language FlexibleInstances #-} {-# Language FlexibleInstances #-}
{-# Language MultiParamTypeClasses #-} {-# Language MultiParamTypeClasses #-}
{-# Language TypeApplications #-}
module Servant.XML module Servant.XML
( ToNode(..) ( ToNode(..)
, XML , XML
, OPDS
, Text.Hamlet.XML.xml , Text.Hamlet.XML.xml
, iso8601 ) , iso8601 )
where where
@ -16,14 +18,22 @@ import Network.HTTP.Media.MediaType
data XML data XML
data OPDS
instance (ToNode a) => MimeRender XML a where instance (ToNode a) => MimeRender XML a where
mimeRender _ a = mimeRender _ a =
let [NodeElement root] = toNode a let [NodeElement root] = toNode a
in renderLBS def (Document (Prologue [] Nothing []) root []) in renderLBS def (Document (Prologue [] Nothing []) root [])
instance (ToNode a) => MimeRender OPDS a where
mimeRender _ a = mimeRender (Proxy @XML) a
instance Accept XML where instance Accept XML where
contentType _ = "application" // "xml" /: ("charset", "utf-8") contentType _ = "application" // "xml" /: ("charset", "utf-8")
instance Accept OPDS where
contentType _ = "application" // "atom+xml" /: ("charset", "utf-8") /: ("profile", "opds-catalog")
iso8601 :: UTCTime -> Text iso8601 :: UTCTime -> Text
iso8601 = pack . formatTime defaultTimeLocale "%Y-%m-%dT%H:%M:%SZ" iso8601 = pack . formatTime defaultTimeLocale "%Y-%m-%dT%H:%M:%SZ"