Compare commits
2 Commits
ce338f067b
...
sandbox/Ma
Author | SHA1 | Date | |
---|---|---|---|
225e44d1a2 | |||
00a7e3d524 |
@ -1,3 +1,6 @@
|
|||||||
|
-- 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:
|
||||||
|
@ -96,34 +96,15 @@ 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 = getChannelsV1
|
getChannels SafeUser{username} = do
|
||||||
getBooks = getBooksV1
|
|
||||||
|
|
||||||
relUrl :: Link -> Rel
|
|
||||||
relUrl x = Rel ("/api/current/" <> (pack . uriPath . linkURI $ x))
|
|
||||||
|
|
||||||
getBooksV1 :: Channel.ChannelID -> SafeUser -> AppM (Catalog 1)
|
|
||||||
getBooksV1 identifier SafeUser{} = do
|
|
||||||
updated <- liftIO getCurrentTime
|
updated <- liftIO getCurrentTime
|
||||||
let self = relUrl selfUrl
|
let self = Rel ("/api/current/" <> selfUrl)
|
||||||
start = relUrl startUrl
|
|
||||||
selfUrl = safeLink (Proxy @(BaseAPI 1)) (Proxy @(ChannelCatalog 1)) identifier
|
|
||||||
startUrl = safeLink (Proxy @(BaseAPI 1)) (Proxy @(RootCatalog 1))
|
|
||||||
entries = mempty
|
|
||||||
pagination = Pagination Nothing Nothing
|
|
||||||
pure CatalogV1{..}
|
|
||||||
|
|
||||||
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 = safeLink (Proxy @(BaseAPI 1)) (Proxy @(RootCatalog 1))
|
selfUrl = pack . uriPath . linkURI $ 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)
|
||||||
@ -131,16 +112,14 @@ getChannelsV1 SafeUser{username} = do
|
|||||||
where
|
where
|
||||||
fromChannel :: UTCTime -> Channel.Channel -> Entry 1
|
fromChannel :: UTCTime -> Channel.Channel -> Entry 1
|
||||||
fromChannel updated Channel.Channel{..} =
|
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
|
self = Rel ("/api/current/" <> 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 CatalogContent = '[XML, OPDS]
|
type RootCatalog (v :: Nat) = "catalog" :> Get '[XML] (Catalog v)
|
||||||
|
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
|
||||||
|
|
||||||
@ -148,8 +127,6 @@ 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 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
|
||||||
|
@ -11,8 +11,6 @@
|
|||||||
{-# 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
|
||||||
@ -30,34 +28,17 @@ import Data.Generics.Product
|
|||||||
data JsonChannel = JsonChannel { channel :: Text
|
data JsonChannel = JsonChannel { channel :: Text
|
||||||
, visibility :: Visibility }
|
, visibility :: Visibility }
|
||||||
deriving (Show, Generic)
|
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 :> Post '[JSON] UpdateChannel
|
type BaseAPI = "channels" :> ReqBody '[JSON] JsonChannel :> Post '[JSON] JsonChannel
|
||||||
:<|> "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 :<|> updateChannelHandler user :<|> listChannelsHandler user
|
handler user = newChannelHandler 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 ->
|
||||||
@ -65,11 +46,8 @@ 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 UpdateChannel
|
newChannelHandler :: AuthResult SafeUser -> JsonChannel -> AppM JsonChannel
|
||||||
newChannelHandler auth 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)
|
||||||
mChannel <- fmap toChannel <$> runDB (insertChannel (view (field @"username") user) channel visibility)
|
runDB (insertChannel (view (field @"username") user) channel visibility)
|
||||||
maybe (throwM err403{errBody="Could not create the channel"}) return mChannel
|
return ch
|
||||||
|
|
||||||
toChannel :: Channel -> UpdateChannel
|
|
||||||
toChannel Channel{..} = UpdateChannel{..}
|
|
||||||
|
@ -4,15 +4,12 @@
|
|||||||
module Database.Channel
|
module Database.Channel
|
||||||
( userChannels
|
( userChannels
|
||||||
, insertChannel
|
, insertChannel
|
||||||
, channelExists
|
|
||||||
, isChannelOwner
|
|
||||||
, updateChannelPrivacy
|
|
||||||
, attachChannel
|
, attachChannel
|
||||||
, Visibility(..)
|
, Visibility(..)
|
||||||
, clearChannels
|
, clearChannels
|
||||||
, booksChannels
|
, booksChannels
|
||||||
, Channel(..)
|
, Channel(..)
|
||||||
, ChannelID(..) )
|
, ChannelID )
|
||||||
where
|
where
|
||||||
|
|
||||||
import ClassyPrelude
|
import ClassyPrelude
|
||||||
@ -21,30 +18,6 @@ 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
|
||||||
@ -55,25 +28,12 @@ userChannels username = fromRels <$> query q
|
|||||||
restrict (username' .== literal username)
|
restrict (username' .== literal username)
|
||||||
return channel
|
return channel
|
||||||
|
|
||||||
updateChannelPrivacy :: (MonadMask m, MonadIO m, MonadSelda m) => ChannelID -> Visibility -> m (Maybe Channel)
|
insertChannel :: (MonadMask m, MonadIO m) => Username -> Text -> Visibility -> SeldaT m ()
|
||||||
updateChannelPrivacy channelId visibility = do
|
insertChannel username channel visibility = do
|
||||||
void $ update (gen channels) predicate (\channel -> channel `with` [pVis := literal visibility])
|
mUserId <- listToMaybe <$> getUser
|
||||||
getChannel channelId
|
void $ forM mUserId $ \userId ->
|
||||||
|
insertUnless (gen channels) (doesNotExist userId) [ def :*: channel :*: userId :*: visibility ]
|
||||||
where
|
where
|
||||||
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
|
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)
|
||||||
|
@ -44,7 +44,7 @@ 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)
|
||||||
|
|
||||||
newtype ChannelID = ChannelID {unChannelID :: Int} deriving (Show, ToHttpApiData, FromHttpApiData, ToJSON, FromJSON)
|
newtype ChannelID = ChannelID {unChannelID :: Int} deriving (Show, ToHttpApiData, FromHttpApiData)
|
||||||
|
|
||||||
newtype TagID = TagID {unTagID :: Int} deriving (Show)
|
newtype TagID = TagID {unTagID :: Int} deriving (Show)
|
||||||
|
|
||||||
|
@ -1,11 +1,9 @@
|
|||||||
{-# 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
|
||||||
@ -18,22 +16,14 @@ 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