Compare commits
2 Commits
e40834bc52
...
5ff629902c
Author | SHA1 | Date | |
---|---|---|---|
5ff629902c | |||
3d7f40eac9 |
@ -28,6 +28,7 @@ executable ebook-manager
|
||||
, Database
|
||||
, Database.Book
|
||||
, Database.Channel
|
||||
, Database.Tag
|
||||
, Database.Schema
|
||||
, Database.User
|
||||
, Datastore
|
||||
|
@ -21,9 +21,9 @@ import ClassyPrelude
|
||||
import Server.Auth
|
||||
import Servant.Auth as SA
|
||||
import Data.Aeson
|
||||
import API.Channels (JsonChannel(..))
|
||||
import Database.Book
|
||||
import Database.Channel
|
||||
import Database.Tag
|
||||
import Database
|
||||
import Control.Lens
|
||||
import Data.Generics.Product
|
||||
@ -38,13 +38,15 @@ data JsonBook = JsonBook { identifier :: BookID
|
||||
, contentType :: Text
|
||||
, title :: Maybe Text
|
||||
, description :: Maybe Text
|
||||
, channels :: [JsonChannel] }
|
||||
, channels :: [Text]
|
||||
, tags :: [Text] }
|
||||
deriving (Generic, Show)
|
||||
|
||||
data PostBook = PostBook { contentType :: Text
|
||||
, title :: Maybe Text
|
||||
, description :: Maybe Text
|
||||
, channels :: [JsonChannel] }
|
||||
, channels :: [Text]
|
||||
, tags :: [Text] }
|
||||
deriving (Generic, Show)
|
||||
|
||||
|
||||
@ -105,5 +107,6 @@ listBooksHandler = requireLoggedIn $ \user -> do
|
||||
runDB (usersBooks (view (field @"username") user) >>= mapM augment)
|
||||
where
|
||||
augment Book{identifier=bookId,contentType,title,description} = do
|
||||
channels <- fmap (\Channel{..} -> JsonChannel{..}) <$> booksChannels bookId
|
||||
channels <- fmap (view (field @"channel")) <$> booksChannels bookId
|
||||
tags <- fmap (view (field @"tag")) <$> booksTags bookId
|
||||
pure JsonBook{identifier=bookId,..}
|
||||
|
@ -11,6 +11,7 @@ module Database
|
||||
, fromRel
|
||||
, fromRels
|
||||
, toRel
|
||||
, transaction
|
||||
, SeldaT )
|
||||
where
|
||||
|
||||
@ -18,7 +19,7 @@ import Data.Generics.Product
|
||||
import Control.Lens (view)
|
||||
import Data.Pool (Pool, withResource)
|
||||
import Database.Selda.Backend (SeldaConnection, runSeldaT, SeldaT)
|
||||
import Database.Selda (query, select)
|
||||
import Database.Selda (query, select, transaction)
|
||||
import Database.Selda.Generic (gen, fromRel, fromRels, toRel)
|
||||
import ClassyPrelude
|
||||
|
||||
|
@ -18,11 +18,14 @@ module Database.Book
|
||||
, BookID) where
|
||||
|
||||
import ClassyPrelude
|
||||
import Database.Schema
|
||||
import Database.Schema (books, users, Username, Book(..), BookID(..), UserID, HashDigest(..))
|
||||
import Database
|
||||
import Database.Selda
|
||||
import Database.Selda.Generic
|
||||
|
||||
import Database.Tag (attachTag, clearTags)
|
||||
import Database.Channel (attachChannel, clearChannels)
|
||||
|
||||
usersBooks :: (MonadSelda m, MonadMask m, MonadIO m) => Username -> m [Book]
|
||||
usersBooks username = fromRels <$> query q
|
||||
where
|
||||
@ -64,7 +67,9 @@ data UpdateBook = UpdateBook { identifier :: BookID
|
||||
, contentType :: Text
|
||||
, title :: Maybe Text
|
||||
, description :: Maybe Text
|
||||
, owner :: Username }
|
||||
, owner :: Username
|
||||
, tags :: [Text]
|
||||
, channels :: [Text] }
|
||||
|
||||
bookExists :: (MonadSelda m, MonadMask m, MonadIO m) => BookID -> m Bool
|
||||
bookExists identifier = not . null <$> query q
|
||||
@ -88,13 +93,19 @@ bookOwner' identifier username = do
|
||||
|
||||
updateBook :: (MonadSelda m, MonadMask m, MonadIO m) => UpdateBook -> m (Maybe UpdateBook)
|
||||
updateBook book@UpdateBook{..} = do
|
||||
mUserId <- query (bookOwner' identifier owner)
|
||||
forM (listToMaybe mUserId) $ \_userId -> do
|
||||
update_ (gen books) predicate (\b -> b `with` [ pContentType := literal contentType
|
||||
, pTitle := literal title
|
||||
, pDescription := literal description ])
|
||||
return book
|
||||
clearTags identifier >> connectTags
|
||||
clearChannels identifier >> connectChannels
|
||||
updateBook'
|
||||
where
|
||||
connectTags = mapM_ (attachTag owner identifier) tags
|
||||
connectChannels = mapM_ (attachChannel owner identifier) channels
|
||||
updateBook' = do
|
||||
mUserId <- query (bookOwner' identifier owner)
|
||||
forM (listToMaybe mUserId) $ \_userId -> do
|
||||
update_ (gen books) predicate (\b -> b `with` [ pContentType := literal contentType
|
||||
, pTitle := literal title
|
||||
, pDescription := literal description ])
|
||||
return book
|
||||
_ :*: _ :*: pContentType :*: pTitle :*: pDescription :*: _ = selectors (gen books)
|
||||
predicate (bookId :*: _) = bookId .== literal identifier
|
||||
|
||||
|
@ -1,8 +1,11 @@
|
||||
{-# Language TypeApplications #-}
|
||||
{-# Language DataKinds #-}
|
||||
{-# Language NamedFieldPuns #-}
|
||||
module Database.Channel
|
||||
( userChannels
|
||||
, insertChannel
|
||||
, attachChannel
|
||||
, clearChannels
|
||||
, booksChannels
|
||||
, Channel(..)
|
||||
, ChannelID )
|
||||
@ -12,6 +15,7 @@ import ClassyPrelude
|
||||
import Database.Schema
|
||||
import Database
|
||||
import Database.Selda
|
||||
import Database.Selda.Generic
|
||||
|
||||
userChannels :: (MonadMask m, MonadIO m) => Username -> SeldaT m [Channel]
|
||||
userChannels username = fromRels <$> query q
|
||||
@ -36,11 +40,33 @@ insertChannel username channel = do
|
||||
return userId
|
||||
|
||||
booksChannels :: (MonadMask m, MonadIO m) => BookID -> SeldaT m [Channel]
|
||||
booksChannels contentHash = fromRels <$> query q
|
||||
booksChannels bookId = fromRels <$> query q
|
||||
where
|
||||
q = do
|
||||
channelId :*: contentHash' <- select (gen bookChannels)
|
||||
channelId :*: bookId' <- select (gen bookChannels)
|
||||
ch@(channelId' :*: _) <- select (gen channels)
|
||||
restrict (channelId .== channelId')
|
||||
restrict (contentHash' .== literal contentHash)
|
||||
restrict (bookId' .== literal bookId)
|
||||
return ch
|
||||
|
||||
attachChannel :: (MonadMask m, MonadIO m, MonadSelda m) => Username -> BookID -> Text -> m ()
|
||||
attachChannel username bookId channel = do
|
||||
-- XXX: test what happens if channel doesn't exist
|
||||
[Channel{identifier}] <- fromRels <$> query channelQ
|
||||
whenM (null <$> query (attachQ identifier)) $
|
||||
void $ insertGen bookChannels [BookChannel identifier bookId]
|
||||
where
|
||||
attachQ channelId = do
|
||||
(channelId' :*: bookId') <- select (gen bookChannels)
|
||||
restrict (channelId' .== literal channelId .&& bookId' .== literal bookId)
|
||||
return channelId'
|
||||
channelQ = do
|
||||
userId :*: _ :*: username' :*: _ <- select (gen users)
|
||||
ch@(_ :*: channel' :*: owner) <- select (gen channels)
|
||||
restrict (username' .== literal username)
|
||||
restrict (owner .== userId)
|
||||
restrict (channel' .== literal channel)
|
||||
return ch
|
||||
|
||||
clearChannels :: (MonadMask m, MonadIO m, MonadSelda m) => BookID -> m Int
|
||||
clearChannels bookId = deleteFrom (gen bookChannels) (\(_ :*: bookId') -> bookId' .== literal bookId)
|
||||
|
62
src/Database/Tag.hs
Normal file
62
src/Database/Tag.hs
Normal file
@ -0,0 +1,62 @@
|
||||
{-# Language TypeApplications #-}
|
||||
{-# Language TypeOperators #-}
|
||||
{-# Language DataKinds #-}
|
||||
{-# Language DuplicateRecordFields #-}
|
||||
{-# Language NamedFieldPuns #-}
|
||||
module Database.Tag
|
||||
( def
|
||||
, booksTags
|
||||
, attachTag
|
||||
, upsertTag
|
||||
, clearTags
|
||||
, Tag(..) ) where
|
||||
|
||||
import ClassyPrelude
|
||||
import Database.Schema
|
||||
import Database
|
||||
import Database.Selda
|
||||
import Database.Selda.Generic
|
||||
|
||||
upsertTag :: (MonadMask m, MonadIO m, MonadSelda m) => Username -> Text -> m Tag
|
||||
upsertTag username tag = do
|
||||
-- I want this to error out if some data is invariant is wrong and roll back
|
||||
-- the transaction. Also as a side note, run this in a transaction plz
|
||||
[userId] <- query userQ
|
||||
void $ upsert (gen tags) (predicate userId) id [toRel (Tag def tag userId)]
|
||||
[t] <- fromRels <$> query (tagQ userId)
|
||||
return t
|
||||
where
|
||||
predicate userId (_ :*: tag' :*: owner) = tag' .== literal tag .&& owner .== literal userId
|
||||
tagQ userId = do
|
||||
t@(_ :*: tag' :*: owner) <- select (gen tags)
|
||||
restrict (tag' .== literal tag .&& owner .== literal userId)
|
||||
return t
|
||||
userQ = do
|
||||
userId :*: _ :*: username' :*: _ <- select (gen users)
|
||||
restrict (username' .== literal username)
|
||||
return userId
|
||||
|
||||
booksTags :: (MonadMask m, MonadIO m, MonadSelda m) => BookID -> m [Tag]
|
||||
booksTags bookId = fromRels <$> query q
|
||||
where
|
||||
q = do
|
||||
tagId :*: bookId' <- select (gen bookTags)
|
||||
tag@(tagId' :*: _) <- select (gen tags)
|
||||
restrict (tagId .== tagId')
|
||||
restrict (bookId' .== literal bookId)
|
||||
return tag
|
||||
|
||||
attachTag :: (MonadMask m, MonadIO m, MonadSelda m) => Username -> BookID -> Text -> m ()
|
||||
attachTag username bookId tag = do
|
||||
Tag{identifier} <- upsertTag username tag
|
||||
whenM (null <$> query (tagQ identifier)) $
|
||||
void $ insertGen bookTags [BookTag identifier bookId]
|
||||
where
|
||||
tagQ tagId = do
|
||||
(tagId' :*: bookId') <- select (gen bookTags)
|
||||
restrict (tagId' .== literal tagId .&& bookId' .== literal bookId)
|
||||
return tagId'
|
||||
|
||||
clearTags :: (MonadMask m, MonadIO m, MonadSelda m) => BookID -> m Int
|
||||
clearTags bookId = deleteFrom (gen bookTags) (\(_ :*: bookId') -> bookId' .== literal bookId)
|
||||
|
Loading…
Reference in New Issue
Block a user