{-# LANGUAGE UndecidableInstances #-} module Conduit.Features.Account.Common.FindFollowersByID where import Prelude hiding (get, on) import Conduit.DB.Core (MonadDB(..), mapDBResult, sqlKey2ID) import Conduit.Errors (FeatureErrorMapper(..)) import Conduit.Features.Account.DB (Follow, UserId) import Conduit.Features.Account.Errors (AccountError(..)) import Conduit.Features.Account.Types (UserID(..)) import Database.Esqueleto.Experimental (Value(..), from, select, table, valkey, where_, (==.)) import UnliftIO (MonadUnliftIO) findFollowersByID :: (FeatureErrorMapper AccountError e, AquireFollowers m) => UserID -> m (Either e [UserID]) findFollowersByID :: forall e (m :: * -> *). (FeatureErrorMapper AccountError e, AquireFollowers m) => UserID -> m (Either e [UserID]) findFollowersByID UserID user = (AccountError -> e) -> Either AccountError [UserID] -> Either e [UserID] forall a b c. (a -> b) -> Either a c -> Either b c forall (p :: * -> * -> *) a b c. Bifunctor p => (a -> b) -> p a c -> p b c first AccountError -> e forall e1 e2. FeatureErrorMapper e1 e2 => e1 -> e2 mapFeatureError (Either AccountError [UserID] -> Either e [UserID]) -> m (Either AccountError [UserID]) -> m (Either e [UserID]) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> UserID -> m (Either AccountError [UserID]) forall (m :: * -> *). AquireFollowers m => UserID -> m (Either AccountError [UserID]) findFollowerIDsByID UserID user class (Monad m) => AquireFollowers m where findFollowerIDsByID :: UserID -> m (Either AccountError [UserID]) data UserInfo = UserInfo { UserInfo -> Text userName :: !Text , UserInfo -> Maybe Text userBio :: !(Maybe Text) , UserInfo -> Maybe Text userImage :: !(Maybe Text) , UserInfo -> Bool userFollowed :: !Bool } instance (Monad m, MonadUnliftIO m, MonadDB m) => AquireFollowers m where findFollowerIDsByID :: UserID -> m (Either AccountError [UserID]) findFollowerIDsByID :: UserID -> m (Either AccountError [UserID]) findFollowerIDsByID UserID userID = ([Value (Key User)] -> [UserID]) -> Either DBError [Value (Key User)] -> Either AccountError [UserID] forall e a b. FeatureError e => (a -> b) -> Either DBError a -> Either e b mapDBResult [Value (Key User)] -> [UserID] toUserIDs (Either DBError [Value (Key User)] -> Either AccountError [UserID]) -> m (Either DBError [Value (Key User)]) -> m (Either AccountError [UserID]) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> SqlPersistT m [Value (Key User)] -> m (Either DBError [Value (Key User)]) forall a. SqlPersistT m a -> m (Either DBError a) forall (m :: * -> *) a. MonadDB m => SqlPersistT m a -> m (Either DBError a) runDB do SqlQuery (SqlExpr (Value (Key User))) -> SqlPersistT m [Value (Key User)] forall a r (m :: * -> *) backend. (SqlSelect a r, MonadIO m, SqlBackendCanRead backend) => SqlQuery a -> ReaderT backend m [r] select (SqlQuery (SqlExpr (Value (Key User))) -> SqlPersistT m [Value (Key User)]) -> SqlQuery (SqlExpr (Value (Key User))) -> SqlPersistT m [Value (Key User)] forall a b. (a -> b) -> a -> b $ do SqlExpr (Entity Follow) f <- From (SqlExpr (Entity Follow)) -> SqlQuery (SqlExpr (Entity Follow)) forall a a'. ToFrom a a' => a -> SqlQuery a' from (From (SqlExpr (Entity Follow)) -> SqlQuery (SqlExpr (Entity Follow))) -> From (SqlExpr (Entity Follow)) -> SqlQuery (SqlExpr (Entity Follow)) forall a b. (a -> b) -> a -> b $ forall ent. PersistEntity ent => From (SqlExpr (Entity ent)) table @Follow SqlExpr (Value Bool) -> SqlQuery () where_ (SqlExpr (Entity Follow) f.followerID 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) SqlExpr (Value (Key User)) -> SqlQuery (SqlExpr (Value (Key User))) forall a. a -> SqlQuery a forall (f :: * -> *) a. Applicative f => a -> f a pure SqlExpr (Entity Follow) f.followedID toUserIDs :: [Value UserId] -> [UserID] toUserIDs :: [Value (Key User)] -> [UserID] toUserIDs = (Value (Key User) -> UserID) -> [Value (Key User)] -> [UserID] forall a b. (a -> b) -> [a] -> [b] map (\(Value Key User userID) -> Key User -> UserID forall t id. SqlKey t id => Key t -> id sqlKey2ID Key User userID)