Compare commits
1 Commits
sandbox/Ma
...
13e8da4eea
Author | SHA1 | Date | |
---|---|---|---|
13e8da4eea |
@ -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:
|
||||||
@ -28,7 +25,6 @@ executable ebook-manager
|
|||||||
, Database
|
, Database
|
||||||
, Database.Book
|
, Database.Book
|
||||||
, Database.Channel
|
, Database.Channel
|
||||||
, Database.Tag
|
|
||||||
, Database.Schema
|
, Database.Schema
|
||||||
, Database.User
|
, Database.User
|
||||||
, Datastore
|
, Datastore
|
||||||
|
@ -1 +0,0 @@
|
|||||||
alter table channels add column visibility text NOT NULL default 'Private';
|
|
@ -21,9 +21,9 @@ import ClassyPrelude
|
|||||||
import Server.Auth
|
import Server.Auth
|
||||||
import Servant.Auth as SA
|
import Servant.Auth as SA
|
||||||
import Data.Aeson
|
import Data.Aeson
|
||||||
|
import API.Channels (JsonChannel(..))
|
||||||
import Database.Book
|
import Database.Book
|
||||||
import Database.Channel
|
import Database.Channel
|
||||||
import Database.Tag
|
|
||||||
import Database
|
import Database
|
||||||
import Control.Lens
|
import Control.Lens
|
||||||
import Data.Generics.Product
|
import Data.Generics.Product
|
||||||
@ -38,15 +38,13 @@ data JsonBook = JsonBook { identifier :: BookID
|
|||||||
, contentType :: Text
|
, contentType :: Text
|
||||||
, title :: Maybe Text
|
, title :: Maybe Text
|
||||||
, description :: Maybe Text
|
, description :: Maybe Text
|
||||||
, channels :: [Text]
|
, channels :: [JsonChannel] }
|
||||||
, tags :: [Text] }
|
|
||||||
deriving (Generic, Show)
|
deriving (Generic, Show)
|
||||||
|
|
||||||
data PostBook = PostBook { contentType :: Text
|
data PostBook = PostBook { contentType :: Text
|
||||||
, title :: Maybe Text
|
, title :: Maybe Text
|
||||||
, description :: Maybe Text
|
, description :: Maybe Text
|
||||||
, channels :: [Text]
|
, channels :: [JsonChannel] }
|
||||||
, tags :: [Text] }
|
|
||||||
deriving (Generic, Show)
|
deriving (Generic, Show)
|
||||||
|
|
||||||
|
|
||||||
@ -97,9 +95,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 JsonBook{..}
|
putBookMetaHandler auth bookId b@JsonBook{..}
|
||||||
| bookId == identifier = requireBookOwner auth bookId $ \SafeUser{username=owner} ->
|
| bookId == identifier = requireBookOwner auth bookId $ \SafeUser{username=owner} ->
|
||||||
maybe (throwM err403) (return . view (super @JsonBook)) =<< runDB (updateBook UpdateBook{..})
|
maybe (throwM err403) (const (return b)) =<< runDB (updateBook UpdateBook{..})
|
||||||
| otherwise = throwM err403
|
| otherwise = throwM err403
|
||||||
|
|
||||||
listBooksHandler :: AuthResult SafeUser -> AppM [JsonBook]
|
listBooksHandler :: AuthResult SafeUser -> AppM [JsonBook]
|
||||||
@ -107,6 +105,5 @@ listBooksHandler = requireLoggedIn $ \user -> do
|
|||||||
runDB (usersBooks (view (field @"username") user) >>= mapM augment)
|
runDB (usersBooks (view (field @"username") user) >>= mapM augment)
|
||||||
where
|
where
|
||||||
augment Book{identifier=bookId,contentType,title,description} = do
|
augment Book{identifier=bookId,contentType,title,description} = do
|
||||||
channels <- fmap (view (field @"channel")) <$> booksChannels bookId
|
channels <- fmap (\Channel{..} -> JsonChannel{..}) <$> booksChannels bookId
|
||||||
tags <- fmap (view (field @"tag")) <$> booksTags bookId
|
|
||||||
pure JsonBook{identifier=bookId,..}
|
pure JsonBook{identifier=bookId,..}
|
||||||
|
@ -98,28 +98,33 @@ class Monad m => VersionedCatalog m (v :: Nat) where
|
|||||||
getChannels :: SafeUser -> m (Catalog v)
|
getChannels :: SafeUser -> m (Catalog v)
|
||||||
|
|
||||||
instance VersionedCatalog AppM 1 where
|
instance VersionedCatalog AppM 1 where
|
||||||
getChannels SafeUser{username} = do
|
getChannels = getChannelsV1
|
||||||
updated <- liftIO getCurrentTime
|
|
||||||
let self = Rel ("/api/current/" <> selfUrl)
|
getChannelsV1 :: SafeUser -> AppM (Catalog 1)
|
||||||
-- I'm not sure if this safe link approach is really useable with this
|
getChannelsV1 SafeUser{username} = do
|
||||||
-- api hierarchy since I can't access the topmost api from here. Also
|
updated <- liftIO getCurrentTime
|
||||||
-- authentication would bring a little bit of extra effort as well
|
let self = Rel ("/api/current/" <> selfUrl)
|
||||||
selfUrl = pack . uriPath . linkURI $ safeLink (Proxy @(BaseAPI 1)) (Proxy @(RootCatalog 1))
|
-- I'm not sure if this safe link approach is really useable with this
|
||||||
start = self
|
-- api hierarchy since I can't access the topmost api from here. Also
|
||||||
pagination = Pagination Nothing Nothing
|
-- authentication would bring a little bit of extra effort as well
|
||||||
entries <- map (fromChannel updated) <$> runDB (Channel.userChannels username)
|
selfUrl = pack . uriPath . linkURI $ safeLink (Proxy @(BaseAPI 1)) (Proxy @(RootCatalog 1))
|
||||||
pure CatalogV1{..}
|
start = self
|
||||||
where
|
pagination = Pagination Nothing Nothing
|
||||||
fromChannel :: UTCTime -> Channel.Channel -> Entry 1
|
entries <- map (fromChannel updated) <$> runDB (Channel.userChannels username)
|
||||||
fromChannel updated Channel.Channel{..} =
|
pure CatalogV1{..}
|
||||||
let url = pack . uriPath . linkURI $ safeLink (Proxy @(BaseAPI 1)) (Proxy @(ChannelCatalog 1)) identifier
|
where
|
||||||
self = Rel ("/api/current/" <> url)
|
fromChannel :: UTCTime -> Channel.Channel -> Entry 1
|
||||||
in EntryV1 channel channel updated channel (Left $ SubSection self)
|
fromChannel updated Channel.Channel{..} =
|
||||||
|
let url = pack . uriPath . linkURI $ safeLink (Proxy @(BaseAPI 1)) (Proxy @(ChannelCatalog 1)) identifier
|
||||||
|
self = Rel ("/api/current/" <> url)
|
||||||
|
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 +132,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)
|
||||||
|
-- Channel specific catalog returns tags inside the catalog
|
||||||
catalogChannels _ = throwM err403{errBody="Not implemented"}
|
catalogChannels _ = throwM err403{errBody="Not implemented"}
|
||||||
catalogRoot :: AppM (Catalog v)
|
catalogRoot :: AppM (Catalog v)
|
||||||
|
-- catalog root returns channels
|
||||||
catalogRoot = flip requireLoggedIn auth getChannels
|
catalogRoot = flip requireLoggedIn auth getChannels
|
||||||
|
@ -25,16 +25,14 @@ import Data.Aeson
|
|||||||
import Control.Lens
|
import Control.Lens
|
||||||
import Data.Generics.Product
|
import Data.Generics.Product
|
||||||
|
|
||||||
data JsonChannel = JsonChannel { channel :: Text
|
data JsonChannel = JsonChannel { channel :: Text } deriving (Show, Generic)
|
||||||
, visibility :: Visibility }
|
|
||||||
deriving (Show, Generic)
|
|
||||||
|
|
||||||
instance ToJSON JsonChannel
|
instance ToJSON JsonChannel
|
||||||
instance FromJSON JsonChannel
|
instance FromJSON JsonChannel
|
||||||
|
|
||||||
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 :> Post '[JSON] JsonChannel
|
type BaseAPI = "channels" :> ReqBody '[JSON] JsonChannel :> Put '[JSON] JsonChannel
|
||||||
:<|> "channels" :> Get '[JSON] [JsonChannel]
|
:<|> "channels" :> Get '[JSON] [JsonChannel]
|
||||||
|
|
||||||
handler :: ServerT API AppM
|
handler :: ServerT API AppM
|
||||||
@ -49,5 +47,5 @@ listChannelsHandler = requireLoggedIn $ \user ->
|
|||||||
newChannelHandler :: AuthResult SafeUser -> JsonChannel -> AppM JsonChannel
|
newChannelHandler :: AuthResult SafeUser -> JsonChannel -> AppM JsonChannel
|
||||||
newChannelHandler auth ch@JsonChannel{..} = flip requireLoggedIn auth $ \user -> do
|
newChannelHandler auth ch@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 visibility)
|
runDB (insertChannel (view (field @"username") user) channel)
|
||||||
return ch
|
return ch
|
||||||
|
@ -11,7 +11,6 @@ module Database
|
|||||||
, fromRel
|
, fromRel
|
||||||
, fromRels
|
, fromRels
|
||||||
, toRel
|
, toRel
|
||||||
, transaction
|
|
||||||
, SeldaT )
|
, SeldaT )
|
||||||
where
|
where
|
||||||
|
|
||||||
@ -19,7 +18,7 @@ import Data.Generics.Product
|
|||||||
import Control.Lens (view)
|
import Control.Lens (view)
|
||||||
import Data.Pool (Pool, withResource)
|
import Data.Pool (Pool, withResource)
|
||||||
import Database.Selda.Backend (SeldaConnection, runSeldaT, SeldaT)
|
import Database.Selda.Backend (SeldaConnection, runSeldaT, SeldaT)
|
||||||
import Database.Selda (query, select, transaction)
|
import Database.Selda (query, select)
|
||||||
import Database.Selda.Generic (gen, fromRel, fromRels, toRel)
|
import Database.Selda.Generic (gen, fromRel, fromRels, toRel)
|
||||||
import ClassyPrelude
|
import ClassyPrelude
|
||||||
|
|
||||||
|
@ -18,17 +18,11 @@ module Database.Book
|
|||||||
, BookID) where
|
, BookID) where
|
||||||
|
|
||||||
import ClassyPrelude
|
import ClassyPrelude
|
||||||
import Database.Schema (books, users, Username, Book(..), BookID(..), UserID, HashDigest(..))
|
import Database.Schema
|
||||||
import Database
|
import Database
|
||||||
import Database.Selda
|
import Database.Selda
|
||||||
import Database.Selda.Generic
|
import Database.Selda.Generic
|
||||||
|
|
||||||
import Control.Lens (view)
|
|
||||||
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
|
||||||
where
|
where
|
||||||
@ -70,10 +64,7 @@ data UpdateBook = UpdateBook { identifier :: BookID
|
|||||||
, contentType :: Text
|
, contentType :: Text
|
||||||
, title :: Maybe Text
|
, title :: Maybe Text
|
||||||
, description :: Maybe Text
|
, description :: Maybe Text
|
||||||
, owner :: Username
|
, owner :: Username }
|
||||||
, tags :: [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
|
||||||
@ -96,32 +87,17 @@ 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 UpdateBook{..} = do
|
updateBook book@UpdateBook{..} = do
|
||||||
clearTags identifier >> connectTags
|
mUserId <- query (bookOwner' identifier owner)
|
||||||
clearChannels identifier >> connectChannels
|
forM (listToMaybe mUserId) $ \_userId -> do
|
||||||
updateBook'
|
update_ (gen books) predicate (\b -> b `with` [ pContentType := literal contentType
|
||||||
getUpdateBook identifier owner
|
, pTitle := literal title
|
||||||
|
, pDescription := literal description ])
|
||||||
|
return book
|
||||||
where
|
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 ])
|
|
||||||
_ :*: _ :*: 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)
|
||||||
|
@ -1,12 +1,8 @@
|
|||||||
{-# Language TypeApplications #-}
|
{-# Language TypeApplications #-}
|
||||||
{-# Language DataKinds #-}
|
{-# Language DataKinds #-}
|
||||||
{-# Language NamedFieldPuns #-}
|
|
||||||
module Database.Channel
|
module Database.Channel
|
||||||
( userChannels
|
( userChannels
|
||||||
, insertChannel
|
, insertChannel
|
||||||
, attachChannel
|
|
||||||
, Visibility(..)
|
|
||||||
, clearChannels
|
|
||||||
, booksChannels
|
, booksChannels
|
||||||
, Channel(..)
|
, Channel(..)
|
||||||
, ChannelID )
|
, ChannelID )
|
||||||
@ -16,58 +12,35 @@ import ClassyPrelude
|
|||||||
import Database.Schema
|
import Database.Schema
|
||||||
import Database
|
import Database
|
||||||
import Database.Selda
|
import Database.Selda
|
||||||
import Database.Selda.Generic
|
|
||||||
|
|
||||||
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 -> Visibility -> SeldaT m ()
|
insertChannel :: (MonadMask m, MonadIO m) => Username -> Text -> SeldaT m ()
|
||||||
insertChannel username channel visibility = do
|
insertChannel username channel = do
|
||||||
mUserId <- listToMaybe <$> getUser
|
mUserId <- listToMaybe <$> getUser
|
||||||
void $ forM mUserId $ \userId ->
|
void $ forM mUserId $ \userId ->
|
||||||
insertUnless (gen channels) (doesNotExist userId) [ def :*: channel :*: userId :*: visibility ]
|
insertUnless (gen channels) (doesNotExist userId) [ def :*: channel :*: userId ]
|
||||||
where
|
where
|
||||||
doesNotExist userId (_ :*: channel' :*: userId' :*: _) = channel' .== literal channel .&& userId' .== literal userId
|
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 :: (MonadSelda m, MonadMask m, MonadIO m) => BookID -> m [Channel]
|
booksChannels :: (MonadMask m, MonadIO m) => BookID -> SeldaT m [Channel]
|
||||||
booksChannels bookId = fromRels <$> query q
|
booksChannels contentHash = fromRels <$> query q
|
||||||
where
|
where
|
||||||
q = do
|
q = do
|
||||||
channelId :*: bookId' <- select (gen bookChannels)
|
channelId :*: contentHash' <- select (gen bookChannels)
|
||||||
ch@(channelId' :*: _) <- select (gen channels)
|
ch@(channelId' :*: _) <- select (gen channels)
|
||||||
restrict (channelId .== channelId')
|
restrict (channelId .== channelId')
|
||||||
restrict (bookId' .== literal bookId)
|
restrict (contentHash' .== literal contentHash)
|
||||||
return ch
|
return ch
|
||||||
|
|
||||||
attachChannel :: (MonadMask m, MonadIO m, MonadSelda m) => Username -> BookID -> Text -> m ()
|
|
||||||
attachChannel username bookId channel = do
|
|
||||||
mCh <- fromRels <$> query channelQ
|
|
||||||
forM_ mCh $ \Channel{identifier} ->
|
|
||||||
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)
|
|
||||||
|
@ -124,22 +124,9 @@ 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
|
||||||
|
@ -1,61 +0,0 @@
|
|||||||
{-# 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
|
|
||||||
import Control.Monad.Trans.Maybe
|
|
||||||
|
|
||||||
upsertTag :: (MonadMask m, MonadIO m, MonadSelda m) => Username -> Text -> m (Maybe Tag)
|
|
||||||
upsertTag username tag = runMaybeT $ do
|
|
||||||
userId <- MaybeT (listToMaybe <$> query userQ)
|
|
||||||
void $ lift $ upsert (gen tags) (predicate userId) id [toRel (Tag def tag userId)]
|
|
||||||
MaybeT (listToMaybe . fromRels <$> query (tagQ userId))
|
|
||||||
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
|
|
||||||
maybeT <- upsertTag username tag
|
|
||||||
forM_ maybeT $ \Tag{identifier} -> do
|
|
||||||
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)
|
|
||||||
|
|
@ -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"
|
||||||
|
|
||||||
|
Reference in New Issue
Block a user