Compare commits
	
		
			7 Commits
		
	
	
		
			sandbox/Ma
			...
			ce338f067b
		
	
	| Author | SHA1 | Date | |
|---|---|---|---|
| ce338f067b | |||
| f55a982f57 | |||
| 3f1b2d3588 | |||
| 83e39cbe6c | |||
| e50e234747 | |||
| 0037d4691e | |||
| e61fb66c06 | 
@@ -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
 | 
			
		||||
version:             0.1.0.0
 | 
			
		||||
-- synopsis:
 | 
			
		||||
 
 | 
			
		||||
							
								
								
									
										1
									
								
								migrations/V1.1__Channel_visibility.sql
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										1
									
								
								migrations/V1.1__Channel_visibility.sql
									
									
									
									
									
										Normal file
									
								
							@@ -0,0 +1 @@
 | 
			
		||||
alter table channels add column visibility text NOT NULL default 'Private';
 | 
			
		||||
@@ -96,30 +96,51 @@ instance ToNode (Catalog 1) where
 | 
			
		||||
 | 
			
		||||
class Monad m => VersionedCatalog m (v :: Nat) where
 | 
			
		||||
  getChannels :: SafeUser -> m (Catalog v)
 | 
			
		||||
  getBooks :: Channel.ChannelID -> SafeUser -> m (Catalog v)
 | 
			
		||||
 | 
			
		||||
instance VersionedCatalog AppM 1 where
 | 
			
		||||
  getChannels SafeUser{username} = do
 | 
			
		||||
    updated <- liftIO getCurrentTime
 | 
			
		||||
    let self = Rel ("/api/current/" <> selfUrl)
 | 
			
		||||
        -- 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 = pack . uriPath . linkURI $ safeLink (Proxy @(BaseAPI 1)) (Proxy @(RootCatalog 1))
 | 
			
		||||
        start = self
 | 
			
		||||
        pagination = Pagination Nothing Nothing
 | 
			
		||||
    entries <- map (fromChannel updated) <$> runDB (Channel.userChannels username)
 | 
			
		||||
    pure CatalogV1{..}
 | 
			
		||||
    where
 | 
			
		||||
      fromChannel :: UTCTime -> Channel.Channel -> Entry 1
 | 
			
		||||
      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)
 | 
			
		||||
  getChannels = getChannelsV1
 | 
			
		||||
  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
 | 
			
		||||
  let self = relUrl 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
 | 
			
		||||
      -- 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))
 | 
			
		||||
      start = self
 | 
			
		||||
      pagination = Pagination Nothing Nothing
 | 
			
		||||
  entries <- map (fromChannel updated) <$> runDB (Channel.userChannels username)
 | 
			
		||||
  pure CatalogV1{..}
 | 
			
		||||
  where
 | 
			
		||||
    fromChannel :: UTCTime -> Channel.Channel -> Entry 1
 | 
			
		||||
    fromChannel updated Channel.Channel{..} =
 | 
			
		||||
      let url = safeLink (Proxy @(BaseAPI 1)) (Proxy @(ChannelCatalog 1)) identifier
 | 
			
		||||
          self = relUrl url
 | 
			
		||||
      in EntryV1 channel channel updated channel (Left $ SubSection self)
 | 
			
		||||
 | 
			
		||||
type VersionedAPI (v :: Nat) = Auth '[SA.BasicAuth, SA.JWT] SafeUser :> BaseAPI v
 | 
			
		||||
 | 
			
		||||
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 CatalogContent = '[XML, OPDS]
 | 
			
		||||
 | 
			
		||||
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
 | 
			
		||||
                    :<|> ChannelCatalog v
 | 
			
		||||
 | 
			
		||||
@@ -127,6 +148,8 @@ handler :: forall v. VersionedCatalog AppM v => ServerT (VersionedAPI v) AppM
 | 
			
		||||
handler auth = catalogRoot :<|> catalogChannels
 | 
			
		||||
  where
 | 
			
		||||
    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)
 | 
			
		||||
    -- catalog root returns channels
 | 
			
		||||
    catalogRoot = flip requireLoggedIn auth getChannels
 | 
			
		||||
 
 | 
			
		||||
@@ -11,6 +11,8 @@
 | 
			
		||||
{-# Language FlexibleInstances #-}
 | 
			
		||||
{-# Language TypeApplications #-}
 | 
			
		||||
{-# Language DataKinds #-}
 | 
			
		||||
{-# Language DuplicateRecordFields #-}
 | 
			
		||||
{-# Language NamedFieldPuns #-}
 | 
			
		||||
module API.Channels (API, handler, JsonChannel(..)) where
 | 
			
		||||
 | 
			
		||||
import Servant
 | 
			
		||||
@@ -25,18 +27,37 @@ import Data.Aeson
 | 
			
		||||
import Control.Lens
 | 
			
		||||
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 FromJSON JsonChannel
 | 
			
		||||
instance ToJSON UpdateChannel
 | 
			
		||||
instance FromJSON UpdateChannel
 | 
			
		||||
 | 
			
		||||
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]
 | 
			
		||||
 | 
			
		||||
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 = requireLoggedIn $ \user ->
 | 
			
		||||
@@ -44,8 +65,11 @@ listChannelsHandler = requireLoggedIn $ \user ->
 | 
			
		||||
  -- use the 'channel' accessor somehow or export it
 | 
			
		||||
  fmap (\Channel{..} -> JsonChannel{..}) <$> runDB (userChannels (view (field @"username") user))
 | 
			
		||||
 | 
			
		||||
newChannelHandler :: AuthResult SafeUser -> JsonChannel -> AppM JsonChannel
 | 
			
		||||
newChannelHandler auth ch@JsonChannel{..} = flip requireLoggedIn auth $ \user -> do
 | 
			
		||||
newChannelHandler :: AuthResult SafeUser -> JsonChannel -> AppM UpdateChannel
 | 
			
		||||
newChannelHandler auth JsonChannel{..} = flip requireLoggedIn auth $ \user -> do
 | 
			
		||||
  $logInfo $ "Creating channel for user " <> pack (show user)
 | 
			
		||||
  runDB (insertChannel (view (field @"username") user) channel)
 | 
			
		||||
  return ch
 | 
			
		||||
  mChannel <- fmap toChannel <$> runDB (insertChannel (view (field @"username") user) channel visibility)
 | 
			
		||||
  maybe (throwM err403{errBody="Could not create the channel"}) return mChannel
 | 
			
		||||
 | 
			
		||||
toChannel :: Channel -> UpdateChannel
 | 
			
		||||
toChannel Channel{..} = UpdateChannel{..}
 | 
			
		||||
 
 | 
			
		||||
@@ -4,11 +4,15 @@
 | 
			
		||||
module Database.Channel
 | 
			
		||||
  ( userChannels
 | 
			
		||||
  , insertChannel
 | 
			
		||||
  , channelExists
 | 
			
		||||
  , isChannelOwner
 | 
			
		||||
  , updateChannelPrivacy
 | 
			
		||||
  , attachChannel
 | 
			
		||||
  , Visibility(..)
 | 
			
		||||
  , clearChannels
 | 
			
		||||
  , booksChannels
 | 
			
		||||
  , Channel(..)
 | 
			
		||||
  , ChannelID )
 | 
			
		||||
  , ChannelID(..) )
 | 
			
		||||
  where
 | 
			
		||||
 | 
			
		||||
import ClassyPrelude
 | 
			
		||||
@@ -17,23 +21,60 @@ import Database
 | 
			
		||||
import Database.Selda
 | 
			
		||||
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 username = fromRels <$> query q
 | 
			
		||||
  where
 | 
			
		||||
    q = do
 | 
			
		||||
      userId :*: _ :*: username' :*: _ <- select (gen users)
 | 
			
		||||
      channel@(_ :*: _ :*: owner) <- select (gen channels)
 | 
			
		||||
      channel@(_ :*: _ :*: owner :*: _) <- select (gen channels)
 | 
			
		||||
      restrict (owner .== userId)
 | 
			
		||||
      restrict (username' .== literal username)
 | 
			
		||||
      return channel
 | 
			
		||||
 | 
			
		||||
insertChannel :: (MonadMask m, MonadIO m) => Username -> Text -> SeldaT m ()
 | 
			
		||||
insertChannel username channel = do
 | 
			
		||||
  mUserId <- listToMaybe <$> getUser
 | 
			
		||||
  void $ forM mUserId $ \userId ->
 | 
			
		||||
    insertUnless (gen channels) (doesNotExist userId) [ def :*: channel :*: userId ]
 | 
			
		||||
updateChannelPrivacy :: (MonadMask m, MonadIO m, MonadSelda m) => ChannelID -> Visibility -> m (Maybe Channel)
 | 
			
		||||
updateChannelPrivacy channelId visibility = do
 | 
			
		||||
  void $ update (gen channels) predicate (\channel -> channel `with` [pVis := literal visibility])
 | 
			
		||||
  getChannel channelId
 | 
			
		||||
  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
 | 
			
		||||
      userId :*: _ :*: user :*: _ <- select (gen users)
 | 
			
		||||
      restrict (user .== literal username)
 | 
			
		||||
@@ -62,7 +103,7 @@ attachChannel username bookId channel = do
 | 
			
		||||
      return channelId'
 | 
			
		||||
    channelQ = do
 | 
			
		||||
      userId :*: _ :*: username' :*: _ <- select (gen users)
 | 
			
		||||
      ch@(_ :*: channel' :*: owner) <- select (gen channels)
 | 
			
		||||
      ch@(_ :*: channel' :*: owner :*: _) <- select (gen channels)
 | 
			
		||||
      restrict (username' .== literal username)
 | 
			
		||||
      restrict (owner .== userId)
 | 
			
		||||
      restrict (channel' .== literal channel)
 | 
			
		||||
 
 | 
			
		||||
@@ -44,7 +44,7 @@ newtype UserID = UserID {unUserID :: Int} deriving (Show)
 | 
			
		||||
 | 
			
		||||
newtype BookID = BookID {unBookID :: Int} deriving (Show, ToJSON, FromJSON, FromHttpApiData, Eq, Ord)
 | 
			
		||||
 | 
			
		||||
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)
 | 
			
		||||
 | 
			
		||||
@@ -124,9 +124,22 @@ data Tag = Tag { identifier :: TagID
 | 
			
		||||
               , owner :: UserID }
 | 
			
		||||
         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
 | 
			
		||||
                       , channel :: Text
 | 
			
		||||
                       , owner :: UserID }
 | 
			
		||||
                       , owner :: UserID
 | 
			
		||||
                       , visibility :: Visibility }
 | 
			
		||||
             deriving (Show, Generic)
 | 
			
		||||
 | 
			
		||||
tags :: GenTable Tag
 | 
			
		||||
 
 | 
			
		||||
@@ -1,9 +1,11 @@
 | 
			
		||||
{-# Language OverloadedStrings #-}
 | 
			
		||||
{-# Language FlexibleInstances #-}
 | 
			
		||||
{-# Language MultiParamTypeClasses #-}
 | 
			
		||||
{-# Language TypeApplications #-}
 | 
			
		||||
module Servant.XML
 | 
			
		||||
  ( ToNode(..)
 | 
			
		||||
  , XML
 | 
			
		||||
  , OPDS
 | 
			
		||||
  , Text.Hamlet.XML.xml
 | 
			
		||||
  , iso8601 )
 | 
			
		||||
  where
 | 
			
		||||
@@ -16,14 +18,22 @@ import Network.HTTP.Media.MediaType
 | 
			
		||||
 | 
			
		||||
data XML
 | 
			
		||||
 | 
			
		||||
data OPDS
 | 
			
		||||
 | 
			
		||||
instance (ToNode a) => MimeRender XML a where
 | 
			
		||||
  mimeRender _ a =
 | 
			
		||||
    let [NodeElement root] = toNode a
 | 
			
		||||
    in renderLBS def (Document (Prologue [] Nothing []) root [])
 | 
			
		||||
 | 
			
		||||
instance (ToNode a) => MimeRender OPDS a where
 | 
			
		||||
  mimeRender _ a = mimeRender (Proxy @XML) a
 | 
			
		||||
 | 
			
		||||
instance Accept XML where
 | 
			
		||||
  contentType _ = "application" // "xml" /: ("charset", "utf-8")
 | 
			
		||||
 | 
			
		||||
instance Accept OPDS where
 | 
			
		||||
  contentType _ = "application" // "atom+xml" /: ("charset", "utf-8") /: ("profile", "opds-catalog")
 | 
			
		||||
 | 
			
		||||
iso8601 :: UTCTime -> Text
 | 
			
		||||
iso8601 = pack . formatTime defaultTimeLocale "%Y-%m-%dT%H:%M:%SZ"
 | 
			
		||||
 | 
			
		||||
 
 | 
			
		||||
		Reference in New Issue
	
	Block a user