{-# LANGUAGE GADTs #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE NoFieldSelectors #-} module WikiMusic.Free.AuthQuery ( AuthQuery (..), fetchUserForAuthCheck, fetchMe, fetchUserRoles, fetchUserFromToken, AuthQueryError (..), ) where import Free.AlaCarte import WikiMusic.Protolude data AuthQueryError = PersistenceError Text | LogicError Text | AuthError Text deriving (AuthQueryError -> AuthQueryError -> Bool (AuthQueryError -> AuthQueryError -> Bool) -> (AuthQueryError -> AuthQueryError -> Bool) -> Eq AuthQueryError forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: AuthQueryError -> AuthQueryError -> Bool == :: AuthQueryError -> AuthQueryError -> Bool $c/= :: AuthQueryError -> AuthQueryError -> Bool /= :: AuthQueryError -> AuthQueryError -> Bool Eq, Int -> AuthQueryError -> ShowS [AuthQueryError] -> ShowS AuthQueryError -> String (Int -> AuthQueryError -> ShowS) -> (AuthQueryError -> String) -> ([AuthQueryError] -> ShowS) -> Show AuthQueryError forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> AuthQueryError -> ShowS showsPrec :: Int -> AuthQueryError -> ShowS $cshow :: AuthQueryError -> String show :: AuthQueryError -> String $cshowList :: [AuthQueryError] -> ShowS showList :: [AuthQueryError] -> ShowS Show) type AuthQuery :: Type -> Type data AuthQuery a = FetchUserForAuthCheck Env Text (Either AuthQueryError (Maybe WikiMusicUser) -> a) | FetchUserFromToken Env Text (Either AuthQueryError (Maybe WikiMusicUser) -> a) | FetchMe Env UUID (Either AuthQueryError (Maybe WikiMusicUser) -> a) | FetchUserRoles Env UUID (Either AuthQueryError [UserRole] -> a) deriving ((forall a b. (a -> b) -> AuthQuery a -> AuthQuery b) -> (forall a b. a -> AuthQuery b -> AuthQuery a) -> Functor AuthQuery forall a b. a -> AuthQuery b -> AuthQuery a forall a b. (a -> b) -> AuthQuery a -> AuthQuery b forall (f :: * -> *). (forall a b. (a -> b) -> f a -> f b) -> (forall a b. a -> f b -> f a) -> Functor f $cfmap :: forall a b. (a -> b) -> AuthQuery a -> AuthQuery b fmap :: forall a b. (a -> b) -> AuthQuery a -> AuthQuery b $c<$ :: forall a b. a -> AuthQuery b -> AuthQuery a <$ :: forall a b. a -> AuthQuery b -> AuthQuery a Functor) fetchUserForAuthCheck :: (AuthQuery :<: f) => Env -> Text -> Free f (Either AuthQueryError (Maybe WikiMusicUser)) fetchUserForAuthCheck :: forall (f :: * -> *). (AuthQuery :<: f) => Env -> Text -> Free f (Either AuthQueryError (Maybe WikiMusicUser)) fetchUserForAuthCheck Env env Text token = AuthQuery (Free f (Either AuthQueryError (Maybe WikiMusicUser))) -> Free f (Either AuthQueryError (Maybe WikiMusicUser)) forall (g :: * -> *) (f :: * -> *) a. (g :<: f) => g (Free f a) -> Free f a injectFree (Env -> Text -> (Either AuthQueryError (Maybe WikiMusicUser) -> Free f (Either AuthQueryError (Maybe WikiMusicUser))) -> AuthQuery (Free f (Either AuthQueryError (Maybe WikiMusicUser))) forall a. Env -> Text -> (Either AuthQueryError (Maybe WikiMusicUser) -> a) -> AuthQuery a FetchUserForAuthCheck Env env Text token Either AuthQueryError (Maybe WikiMusicUser) -> Free f (Either AuthQueryError (Maybe WikiMusicUser)) forall (f :: * -> *) a. a -> Free f a Pure) fetchUserFromToken :: (AuthQuery :<: f) => Env -> Text -> Free f (Either AuthQueryError (Maybe WikiMusicUser)) fetchUserFromToken :: forall (f :: * -> *). (AuthQuery :<: f) => Env -> Text -> Free f (Either AuthQueryError (Maybe WikiMusicUser)) fetchUserFromToken Env env Text token = AuthQuery (Free f (Either AuthQueryError (Maybe WikiMusicUser))) -> Free f (Either AuthQueryError (Maybe WikiMusicUser)) forall (g :: * -> *) (f :: * -> *) a. (g :<: f) => g (Free f a) -> Free f a injectFree (Env -> Text -> (Either AuthQueryError (Maybe WikiMusicUser) -> Free f (Either AuthQueryError (Maybe WikiMusicUser))) -> AuthQuery (Free f (Either AuthQueryError (Maybe WikiMusicUser))) forall a. Env -> Text -> (Either AuthQueryError (Maybe WikiMusicUser) -> a) -> AuthQuery a FetchUserFromToken Env env Text token Either AuthQueryError (Maybe WikiMusicUser) -> Free f (Either AuthQueryError (Maybe WikiMusicUser)) forall (f :: * -> *) a. a -> Free f a Pure) fetchMe :: (AuthQuery :<: f) => Env -> UUID -> Free f (Either AuthQueryError (Maybe WikiMusicUser)) fetchMe :: forall (f :: * -> *). (AuthQuery :<: f) => Env -> UUID -> Free f (Either AuthQueryError (Maybe WikiMusicUser)) fetchMe Env env UUID uid = AuthQuery (Free f (Either AuthQueryError (Maybe WikiMusicUser))) -> Free f (Either AuthQueryError (Maybe WikiMusicUser)) forall (g :: * -> *) (f :: * -> *) a. (g :<: f) => g (Free f a) -> Free f a injectFree (Env -> UUID -> (Either AuthQueryError (Maybe WikiMusicUser) -> Free f (Either AuthQueryError (Maybe WikiMusicUser))) -> AuthQuery (Free f (Either AuthQueryError (Maybe WikiMusicUser))) forall a. Env -> UUID -> (Either AuthQueryError (Maybe WikiMusicUser) -> a) -> AuthQuery a FetchMe Env env UUID uid Either AuthQueryError (Maybe WikiMusicUser) -> Free f (Either AuthQueryError (Maybe WikiMusicUser)) forall (f :: * -> *) a. a -> Free f a Pure) fetchUserRoles :: (AuthQuery :<: f) => Env -> UUID -> Free f (Either AuthQueryError [UserRole]) fetchUserRoles :: forall (f :: * -> *). (AuthQuery :<: f) => Env -> UUID -> Free f (Either AuthQueryError [UserRole]) fetchUserRoles Env env UUID uid = AuthQuery (Free f (Either AuthQueryError [UserRole])) -> Free f (Either AuthQueryError [UserRole]) forall (g :: * -> *) (f :: * -> *) a. (g :<: f) => g (Free f a) -> Free f a injectFree (Env -> UUID -> (Either AuthQueryError [UserRole] -> Free f (Either AuthQueryError [UserRole])) -> AuthQuery (Free f (Either AuthQueryError [UserRole])) forall a. Env -> UUID -> (Either AuthQueryError [UserRole] -> a) -> AuthQuery a FetchUserRoles Env env UUID uid Either AuthQueryError [UserRole] -> Free f (Either AuthQueryError [UserRole]) forall (f :: * -> *) a. a -> Free f a Pure)