{-# LANGUAGE UndecidableInstances #-} module Conduit.Features.Articles.Favorites.UnfavoriteArticle where import Conduit.App.Monad (AppM, runService) import Conduit.DB.Core (MonadDB(..), mapDBError) import Conduit.Features.Account.Common.FindProfileByID (AcquireProfile) import Conduit.Features.Account.Types (UserID(..)) import Conduit.Features.Articles.Articles.GetArticle (AquireArticle, getArticle) import Conduit.Features.Articles.DB (Favorite) import Conduit.Features.Articles.Errors (ArticleError) import Conduit.Features.Articles.Slugs (extractIDFromSlug) import Conduit.Features.Articles.Types (ArticleID(..), OneArticle, Slug(..), inArticleObj) import Conduit.Identity.Auth (AuthedUser(..), withAuth) import Database.Esqueleto.Experimental (delete, from, table, valkey, where_, (&&.), (==.)) import UnliftIO (MonadUnliftIO) import Web.Scotty.Trans (ScottyT, captureParam, json) import Web.Scotty.Trans qualified as Scotty handleArticleUnfavorite :: ScottyT AppM () handleArticleUnfavorite :: ScottyT AppM () handleArticleUnfavorite = RoutePattern -> ActionT AppM () -> ScottyT AppM () forall (m :: * -> *). MonadUnliftIO m => RoutePattern -> ActionT m () -> ScottyT m () Scotty.delete RoutePattern "/api/articles/:slug/favorite" (ActionT AppM () -> ScottyT AppM ()) -> ActionT AppM () -> ScottyT AppM () forall a b. (a -> b) -> a -> b $ (AuthedUser -> ActionT AppM ()) -> ActionT AppM () forall (m :: * -> *) c. (MonadIO m, MonadReader c m, Has JWTInfo c m) => (AuthedUser -> ActionT m ()) -> ActionT m () withAuth \AuthedUser user -> do Slug slug <- Text -> ActionT AppM Text forall a (m :: * -> *). (Parsable a, Monad m) => Text -> ActionT m a captureParam Text "slug" ActionT AppM Text -> (Text -> Slug) -> ActionT AppM Slug forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b <&> Text -> Slug Slug OneArticle article <- AppM (Either ArticleError OneArticle) -> ActionT AppM OneArticle forall e a. FeatureError e => AppM (Either e a) -> ActionT AppM a runService (AppM (Either ArticleError OneArticle) -> ActionT AppM OneArticle) -> AppM (Either ArticleError OneArticle) -> ActionT AppM OneArticle forall a b. (a -> b) -> a -> b $ Slug -> UserID -> AppM (Either ArticleError OneArticle) forall (m :: * -> *). (DeleteFavorite m, AquireArticle m, AcquireProfile m) => Slug -> UserID -> m (Either ArticleError OneArticle) unfavoriteArticle Slug slug AuthedUser user.authedUserID InObj OneArticle -> ActionT AppM () forall a (m :: * -> *). (ToJSON a, MonadIO m) => a -> ActionT m () json (InObj OneArticle -> ActionT AppM ()) -> InObj OneArticle -> ActionT AppM () forall a b. (a -> b) -> a -> b $ OneArticle -> InObj OneArticle forall obj. obj -> InObj obj inArticleObj OneArticle article unfavoriteArticle :: (DeleteFavorite m, AquireArticle m, AcquireProfile m) => Slug -> UserID -> m (Either ArticleError OneArticle) unfavoriteArticle :: forall (m :: * -> *). (DeleteFavorite m, AquireArticle m, AcquireProfile m) => Slug -> UserID -> m (Either ArticleError OneArticle) unfavoriteArticle Slug slug UserID userID = ExceptT ArticleError m OneArticle -> m (Either ArticleError OneArticle) forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a) runExceptT do ArticleID articleID <- m (Either ArticleError ArticleID) -> ExceptT ArticleError m ArticleID forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a ExceptT (m (Either ArticleError ArticleID) -> ExceptT ArticleError m ArticleID) -> (Either ArticleError ArticleID -> m (Either ArticleError ArticleID)) -> Either ArticleError ArticleID -> ExceptT ArticleError m ArticleID forall b c a. (b -> c) -> (a -> b) -> a -> c . Either ArticleError ArticleID -> m (Either ArticleError ArticleID) forall a. a -> m a forall (f :: * -> *) a. Applicative f => a -> f a pure (Either ArticleError ArticleID -> ExceptT ArticleError m ArticleID) -> Either ArticleError ArticleID -> ExceptT ArticleError m ArticleID forall a b. (a -> b) -> a -> b $ Slug -> Either ArticleError ArticleID extractIDFromSlug Slug slug m (Either ArticleError ()) -> ExceptT ArticleError m () forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a ExceptT (m (Either ArticleError ()) -> ExceptT ArticleError m ()) -> m (Either ArticleError ()) -> ExceptT ArticleError m () forall a b. (a -> b) -> a -> b $ ArticleID -> UserID -> m (Either ArticleError ()) forall (m :: * -> *). DeleteFavorite m => ArticleID -> UserID -> m (Either ArticleError ()) deleteFavorite ArticleID articleID UserID userID m (Either ArticleError OneArticle) -> ExceptT ArticleError m OneArticle forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a ExceptT (m (Either ArticleError OneArticle) -> ExceptT ArticleError m OneArticle) -> m (Either ArticleError OneArticle) -> ExceptT ArticleError m OneArticle forall a b. (a -> b) -> a -> b $ Slug -> Maybe UserID -> m (Either ArticleError OneArticle) forall (m :: * -> *). (AquireArticle m, AcquireProfile m) => Slug -> Maybe UserID -> m (Either ArticleError OneArticle) getArticle Slug slug (UserID -> Maybe UserID forall a. a -> Maybe a Just UserID userID) class (Monad m) => DeleteFavorite m where deleteFavorite :: ArticleID -> UserID -> m (Either ArticleError ()) instance (Monad m, MonadDB m, MonadUnliftIO m) => DeleteFavorite m where deleteFavorite :: ArticleID -> UserID -> m (Either ArticleError ()) deleteFavorite :: ArticleID -> UserID -> m (Either ArticleError ()) deleteFavorite ArticleID articleID UserID userID = Either DBError () -> Either ArticleError () forall e a. FeatureError e => Either DBError a -> Either e a mapDBError (Either DBError () -> Either ArticleError ()) -> m (Either DBError ()) -> m (Either ArticleError ()) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> SqlPersistT m () -> m (Either DBError ()) forall a. SqlPersistT m a -> m (Either DBError a) forall (m :: * -> *) a. MonadDB m => SqlPersistT m a -> m (Either DBError a) runDB do SqlQuery () -> SqlPersistT m () forall (m :: * -> *) backend. (MonadIO m, SqlBackendCanWrite backend) => SqlQuery () -> ReaderT backend m () delete (SqlQuery () -> SqlPersistT m ()) -> SqlQuery () -> SqlPersistT m () forall a b. (a -> b) -> a -> b $ do SqlExpr (Entity Favorite) f <- From (SqlExpr (Entity Favorite)) -> SqlQuery (SqlExpr (Entity Favorite)) forall a a'. ToFrom a a' => a -> SqlQuery a' from (From (SqlExpr (Entity Favorite)) -> SqlQuery (SqlExpr (Entity Favorite))) -> From (SqlExpr (Entity Favorite)) -> SqlQuery (SqlExpr (Entity Favorite)) forall a b. (a -> b) -> a -> b $ forall ent. PersistEntity ent => From (SqlExpr (Entity ent)) table @Favorite SqlExpr (Value Bool) -> SqlQuery () where_ (SqlExpr (Value Bool) -> SqlQuery ()) -> SqlExpr (Value Bool) -> SqlQuery () forall a b. (a -> b) -> a -> b $ (SqlExpr (Entity Favorite) f.article SqlExpr (Value (Key Article)) -> SqlExpr (Value (Key Article)) -> SqlExpr (Value Bool) forall typ. PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool) ==. Int64 -> SqlExpr (Value (Key Article)) forall entity. (ToBackendKey SqlBackend entity, PersistField (Key entity)) => Int64 -> SqlExpr (Value (Key entity)) valkey ArticleID articleID.unID) SqlExpr (Value Bool) -> SqlExpr (Value Bool) -> SqlExpr (Value Bool) &&. (SqlExpr (Entity Favorite) f.user SqlExpr (Value (Key User)) -> SqlExpr (Value (Key User)) -> SqlExpr (Value Bool) forall typ. PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool) ==. Int64 -> SqlExpr (Value (Key User)) forall entity. (ToBackendKey SqlBackend entity, PersistField (Key entity)) => Int64 -> SqlExpr (Value (Key entity)) valkey UserID userID.unID)