module WikiMusic.Free.GenreCommand
( GenreCommand (..),
insertGenres,
insertGenreComments,
insertGenreArtworks,
upsertGenreOpinions,
insertGenreExternalSources,
deleteGenres,
deleteGenreComments,
deleteGenreArtworks,
deleteGenreOpinions,
deleteCommentsOfGenres,
deleteGenreExternalSources,
deleteArtworksOfGenres,
deleteOpinionsOfGenres,
updateGenreArtworkOrder,
updateGenres,
updateGenreExternalSources,
newGenreFromRequest,
newGenreCommentFromRequest,
newGenreOpinionFromRequest,
newGenreArtworkFromRequest,
GenreCommandError (..),
incrementViewsByOne,
)
where
import Free.AlaCarte
import WikiMusic.Interaction.Model.Genre
import WikiMusic.Model.Genre
import WikiMusic.Protolude
data GenreCommandError = PersistenceError Text | LogicError Text
deriving (GenreCommandError -> GenreCommandError -> Bool
(GenreCommandError -> GenreCommandError -> Bool)
-> (GenreCommandError -> GenreCommandError -> Bool)
-> Eq GenreCommandError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GenreCommandError -> GenreCommandError -> Bool
== :: GenreCommandError -> GenreCommandError -> Bool
$c/= :: GenreCommandError -> GenreCommandError -> Bool
/= :: GenreCommandError -> GenreCommandError -> Bool
Eq, Int -> GenreCommandError -> ShowS
[GenreCommandError] -> ShowS
GenreCommandError -> String
(Int -> GenreCommandError -> ShowS)
-> (GenreCommandError -> String)
-> ([GenreCommandError] -> ShowS)
-> Show GenreCommandError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GenreCommandError -> ShowS
showsPrec :: Int -> GenreCommandError -> ShowS
$cshow :: GenreCommandError -> String
show :: GenreCommandError -> String
$cshowList :: [GenreCommandError] -> ShowS
showList :: [GenreCommandError] -> ShowS
Show)
type GenreCommand :: Type -> Type
data GenreCommand a
= InsertGenres Env [Genre] (Map UUID Genre -> a)
| Env [GenreComment] (Map UUID GenreComment -> a)
| InsertGenreArtworks Env [GenreArtwork] (Map UUID GenreArtwork -> a)
| UpsertGenreOpinions Env [GenreOpinion] (Map UUID GenreOpinion -> a)
| InsertGenreExternalSources Env [GenreExternalSources] (Map UUID GenreExternalSources -> a)
| DeleteGenres Env [UUID] (Either GenreCommandError () -> a)
| Env [UUID] (Either GenreCommandError () -> a)
| DeleteGenreArtworks Env [UUID] (Either GenreCommandError () -> a)
| DeleteGenreOpinions Env [UUID] (Either GenreCommandError () -> a)
| Env [UUID] (Either GenreCommandError () -> a)
| DeleteGenreExternalSources Env [UUID] (Either GenreCommandError () -> a)
| DeleteArtworksOfGenres Env [UUID] (Either GenreCommandError () -> a)
| DeleteOpinionsOfGenres Env [UUID] (Either GenreCommandError () -> a)
| UpdateGenreArtworkOrder Env [GenreArtworkOrderUpdate] (Either Text () -> a)
| UpdateGenres Env (Map UUID (Genre, Maybe GenreDelta)) (Either Text () -> a)
| UpdateGenreExternalSources Env (Map UUID (Genre, Maybe GenreDelta)) (Either Text () -> a)
| NewGenreFromRequest UUID InsertGenresRequestItem (Genre -> a)
|
UUID InsertGenreCommentsRequestItem (GenreComment -> a)
| NewGenreOpinionFromRequest UUID UpsertGenreOpinionsRequestItem (GenreOpinion -> a)
| NewGenreArtworkFromRequest UUID InsertGenreArtworksRequestItem (GenreArtwork -> a)
| IncrementViewsByOne Env [UUID] (Either GenreCommandError () -> a)
deriving ((forall a b. (a -> b) -> GenreCommand a -> GenreCommand b)
-> (forall a b. a -> GenreCommand b -> GenreCommand a)
-> Functor GenreCommand
forall a b. a -> GenreCommand b -> GenreCommand a
forall a b. (a -> b) -> GenreCommand a -> GenreCommand 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) -> GenreCommand a -> GenreCommand b
fmap :: forall a b. (a -> b) -> GenreCommand a -> GenreCommand b
$c<$ :: forall a b. a -> GenreCommand b -> GenreCommand a
<$ :: forall a b. a -> GenreCommand b -> GenreCommand a
Functor)
insertGenres :: (GenreCommand :<: f) => Env -> [Genre] -> Free f (Map UUID Genre)
insertGenres :: forall (f :: * -> *).
(GenreCommand :<: f) =>
Env -> [Genre] -> Free f (Map UUID Genre)
insertGenres Env
env [Genre]
genres = GenreCommand (Free f (Map UUID Genre)) -> Free f (Map UUID Genre)
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (Env
-> [Genre]
-> (Map UUID Genre -> Free f (Map UUID Genre))
-> GenreCommand (Free f (Map UUID Genre))
forall a. Env -> [Genre] -> (Map UUID Genre -> a) -> GenreCommand a
InsertGenres Env
env [Genre]
genres Map UUID Genre -> Free f (Map UUID Genre)
forall (f :: * -> *) a. a -> Free f a
Pure)
insertGenreComments :: (GenreCommand :<: f) => Env -> [GenreComment] -> Free f (Map UUID GenreComment)
Env
env [GenreComment]
genreComments = GenreCommand (Free f (Map UUID GenreComment))
-> Free f (Map UUID GenreComment)
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (Env
-> [GenreComment]
-> (Map UUID GenreComment -> Free f (Map UUID GenreComment))
-> GenreCommand (Free f (Map UUID GenreComment))
forall a.
Env
-> [GenreComment] -> (Map UUID GenreComment -> a) -> GenreCommand a
InsertGenreComments Env
env [GenreComment]
genreComments Map UUID GenreComment -> Free f (Map UUID GenreComment)
forall (f :: * -> *) a. a -> Free f a
Pure)
insertGenreArtworks :: (GenreCommand :<: f) => Env -> [GenreArtwork] -> Free f (Map UUID GenreArtwork)
insertGenreArtworks :: forall (f :: * -> *).
(GenreCommand :<: f) =>
Env -> [GenreArtwork] -> Free f (Map UUID GenreArtwork)
insertGenreArtworks Env
env [GenreArtwork]
genreArtworks = GenreCommand (Free f (Map UUID GenreArtwork))
-> Free f (Map UUID GenreArtwork)
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (Env
-> [GenreArtwork]
-> (Map UUID GenreArtwork -> Free f (Map UUID GenreArtwork))
-> GenreCommand (Free f (Map UUID GenreArtwork))
forall a.
Env
-> [GenreArtwork] -> (Map UUID GenreArtwork -> a) -> GenreCommand a
InsertGenreArtworks Env
env [GenreArtwork]
genreArtworks Map UUID GenreArtwork -> Free f (Map UUID GenreArtwork)
forall (f :: * -> *) a. a -> Free f a
Pure)
upsertGenreOpinions :: (GenreCommand :<: f) => Env -> [GenreOpinion] -> Free f (Map UUID GenreOpinion)
upsertGenreOpinions :: forall (f :: * -> *).
(GenreCommand :<: f) =>
Env -> [GenreOpinion] -> Free f (Map UUID GenreOpinion)
upsertGenreOpinions Env
env [GenreOpinion]
genreOpinions = GenreCommand (Free f (Map UUID GenreOpinion))
-> Free f (Map UUID GenreOpinion)
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (Env
-> [GenreOpinion]
-> (Map UUID GenreOpinion -> Free f (Map UUID GenreOpinion))
-> GenreCommand (Free f (Map UUID GenreOpinion))
forall a.
Env
-> [GenreOpinion] -> (Map UUID GenreOpinion -> a) -> GenreCommand a
UpsertGenreOpinions Env
env [GenreOpinion]
genreOpinions Map UUID GenreOpinion -> Free f (Map UUID GenreOpinion)
forall (f :: * -> *) a. a -> Free f a
Pure)
insertGenreExternalSources :: (GenreCommand :<: f) => Env -> [GenreExternalSources] -> Free f (Map UUID GenreExternalSources)
insertGenreExternalSources :: forall (f :: * -> *).
(GenreCommand :<: f) =>
Env
-> [GenreExternalSources] -> Free f (Map UUID GenreExternalSources)
insertGenreExternalSources Env
env [GenreExternalSources]
genreExternalSources = GenreCommand (Free f (Map UUID GenreExternalSources))
-> Free f (Map UUID GenreExternalSources)
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (Env
-> [GenreExternalSources]
-> (Map UUID GenreExternalSources
-> Free f (Map UUID GenreExternalSources))
-> GenreCommand (Free f (Map UUID GenreExternalSources))
forall a.
Env
-> [GenreExternalSources]
-> (Map UUID GenreExternalSources -> a)
-> GenreCommand a
InsertGenreExternalSources Env
env [GenreExternalSources]
genreExternalSources Map UUID GenreExternalSources
-> Free f (Map UUID GenreExternalSources)
forall (f :: * -> *) a. a -> Free f a
Pure)
deleteGenres :: (GenreCommand :<: f) => Env -> [UUID] -> Free f (Either GenreCommandError ())
deleteGenres :: forall (f :: * -> *).
(GenreCommand :<: f) =>
Env -> [UUID] -> Free f (Either GenreCommandError ())
deleteGenres Env
env [UUID]
uuids = GenreCommand (Free f (Either GenreCommandError ()))
-> Free f (Either GenreCommandError ())
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (Env
-> [UUID]
-> (Either GenreCommandError ()
-> Free f (Either GenreCommandError ()))
-> GenreCommand (Free f (Either GenreCommandError ()))
forall a.
Env
-> [UUID] -> (Either GenreCommandError () -> a) -> GenreCommand a
DeleteGenres Env
env [UUID]
uuids Either GenreCommandError () -> Free f (Either GenreCommandError ())
forall (f :: * -> *) a. a -> Free f a
Pure)
deleteGenreComments :: (GenreCommand :<: f) => Env -> [UUID] -> Free f (Either GenreCommandError ())
Env
env [UUID]
uuids = GenreCommand (Free f (Either GenreCommandError ()))
-> Free f (Either GenreCommandError ())
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (Env
-> [UUID]
-> (Either GenreCommandError ()
-> Free f (Either GenreCommandError ()))
-> GenreCommand (Free f (Either GenreCommandError ()))
forall a.
Env
-> [UUID] -> (Either GenreCommandError () -> a) -> GenreCommand a
DeleteGenreComments Env
env [UUID]
uuids Either GenreCommandError () -> Free f (Either GenreCommandError ())
forall (f :: * -> *) a. a -> Free f a
Pure)
deleteGenreArtworks :: (GenreCommand :<: f) => Env -> [UUID] -> Free f (Either GenreCommandError ())
deleteGenreArtworks :: forall (f :: * -> *).
(GenreCommand :<: f) =>
Env -> [UUID] -> Free f (Either GenreCommandError ())
deleteGenreArtworks Env
env [UUID]
uuids = GenreCommand (Free f (Either GenreCommandError ()))
-> Free f (Either GenreCommandError ())
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (Env
-> [UUID]
-> (Either GenreCommandError ()
-> Free f (Either GenreCommandError ()))
-> GenreCommand (Free f (Either GenreCommandError ()))
forall a.
Env
-> [UUID] -> (Either GenreCommandError () -> a) -> GenreCommand a
DeleteGenreArtworks Env
env [UUID]
uuids Either GenreCommandError () -> Free f (Either GenreCommandError ())
forall (f :: * -> *) a. a -> Free f a
Pure)
deleteGenreOpinions :: (GenreCommand :<: f) => Env -> [UUID] -> Free f (Either GenreCommandError ())
deleteGenreOpinions :: forall (f :: * -> *).
(GenreCommand :<: f) =>
Env -> [UUID] -> Free f (Either GenreCommandError ())
deleteGenreOpinions Env
env [UUID]
uuids = GenreCommand (Free f (Either GenreCommandError ()))
-> Free f (Either GenreCommandError ())
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (Env
-> [UUID]
-> (Either GenreCommandError ()
-> Free f (Either GenreCommandError ()))
-> GenreCommand (Free f (Either GenreCommandError ()))
forall a.
Env
-> [UUID] -> (Either GenreCommandError () -> a) -> GenreCommand a
DeleteGenreOpinions Env
env [UUID]
uuids Either GenreCommandError () -> Free f (Either GenreCommandError ())
forall (f :: * -> *) a. a -> Free f a
Pure)
deleteCommentsOfGenres :: (GenreCommand :<: f) => Env -> [UUID] -> Free f (Either GenreCommandError ())
Env
env [UUID]
uuids = GenreCommand (Free f (Either GenreCommandError ()))
-> Free f (Either GenreCommandError ())
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (Env
-> [UUID]
-> (Either GenreCommandError ()
-> Free f (Either GenreCommandError ()))
-> GenreCommand (Free f (Either GenreCommandError ()))
forall a.
Env
-> [UUID] -> (Either GenreCommandError () -> a) -> GenreCommand a
DeleteCommentsOfGenres Env
env [UUID]
uuids Either GenreCommandError () -> Free f (Either GenreCommandError ())
forall (f :: * -> *) a. a -> Free f a
Pure)
deleteGenreExternalSources :: (GenreCommand :<: f) => Env -> [UUID] -> Free f (Either GenreCommandError ())
deleteGenreExternalSources :: forall (f :: * -> *).
(GenreCommand :<: f) =>
Env -> [UUID] -> Free f (Either GenreCommandError ())
deleteGenreExternalSources Env
env [UUID]
uuids = GenreCommand (Free f (Either GenreCommandError ()))
-> Free f (Either GenreCommandError ())
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (Env
-> [UUID]
-> (Either GenreCommandError ()
-> Free f (Either GenreCommandError ()))
-> GenreCommand (Free f (Either GenreCommandError ()))
forall a.
Env
-> [UUID] -> (Either GenreCommandError () -> a) -> GenreCommand a
DeleteGenreExternalSources Env
env [UUID]
uuids Either GenreCommandError () -> Free f (Either GenreCommandError ())
forall (f :: * -> *) a. a -> Free f a
Pure)
deleteArtworksOfGenres :: (GenreCommand :<: f) => Env -> [UUID] -> Free f (Either GenreCommandError ())
deleteArtworksOfGenres :: forall (f :: * -> *).
(GenreCommand :<: f) =>
Env -> [UUID] -> Free f (Either GenreCommandError ())
deleteArtworksOfGenres Env
env [UUID]
uuids = GenreCommand (Free f (Either GenreCommandError ()))
-> Free f (Either GenreCommandError ())
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (Env
-> [UUID]
-> (Either GenreCommandError ()
-> Free f (Either GenreCommandError ()))
-> GenreCommand (Free f (Either GenreCommandError ()))
forall a.
Env
-> [UUID] -> (Either GenreCommandError () -> a) -> GenreCommand a
DeleteArtworksOfGenres Env
env [UUID]
uuids Either GenreCommandError () -> Free f (Either GenreCommandError ())
forall (f :: * -> *) a. a -> Free f a
Pure)
deleteOpinionsOfGenres :: (GenreCommand :<: f) => Env -> [UUID] -> Free f (Either GenreCommandError ())
deleteOpinionsOfGenres :: forall (f :: * -> *).
(GenreCommand :<: f) =>
Env -> [UUID] -> Free f (Either GenreCommandError ())
deleteOpinionsOfGenres Env
env [UUID]
uuids = GenreCommand (Free f (Either GenreCommandError ()))
-> Free f (Either GenreCommandError ())
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (Env
-> [UUID]
-> (Either GenreCommandError ()
-> Free f (Either GenreCommandError ()))
-> GenreCommand (Free f (Either GenreCommandError ()))
forall a.
Env
-> [UUID] -> (Either GenreCommandError () -> a) -> GenreCommand a
DeleteOpinionsOfGenres Env
env [UUID]
uuids Either GenreCommandError () -> Free f (Either GenreCommandError ())
forall (f :: * -> *) a. a -> Free f a
Pure)
updateGenreArtworkOrder :: (GenreCommand :<: f) => Env -> [GenreArtworkOrderUpdate] -> Free f (Either Text ())
updateGenreArtworkOrder :: forall (f :: * -> *).
(GenreCommand :<: f) =>
Env -> [GenreArtworkOrderUpdate] -> Free f (Either Text ())
updateGenreArtworkOrder Env
env [GenreArtworkOrderUpdate]
uuids = GenreCommand (Free f (Either Text ())) -> Free f (Either Text ())
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (Env
-> [GenreArtworkOrderUpdate]
-> (Either Text () -> Free f (Either Text ()))
-> GenreCommand (Free f (Either Text ()))
forall a.
Env
-> [GenreArtworkOrderUpdate]
-> (Either Text () -> a)
-> GenreCommand a
UpdateGenreArtworkOrder Env
env [GenreArtworkOrderUpdate]
uuids Either Text () -> Free f (Either Text ())
forall (f :: * -> *) a. a -> Free f a
Pure)
updateGenres :: (GenreCommand :<: f) => Env -> Map UUID (Genre, Maybe GenreDelta) -> Free f (Either Text ())
updateGenres :: forall (f :: * -> *).
(GenreCommand :<: f) =>
Env
-> Map UUID (Genre, Maybe GenreDelta) -> Free f (Either Text ())
updateGenres Env
env Map UUID (Genre, Maybe GenreDelta)
deltas = GenreCommand (Free f (Either Text ())) -> Free f (Either Text ())
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (Env
-> Map UUID (Genre, Maybe GenreDelta)
-> (Either Text () -> Free f (Either Text ()))
-> GenreCommand (Free f (Either Text ()))
forall a.
Env
-> Map UUID (Genre, Maybe GenreDelta)
-> (Either Text () -> a)
-> GenreCommand a
UpdateGenres Env
env Map UUID (Genre, Maybe GenreDelta)
deltas Either Text () -> Free f (Either Text ())
forall (f :: * -> *) a. a -> Free f a
Pure)
updateGenreExternalSources :: (GenreCommand :<: f) => Env -> Map UUID (Genre, Maybe GenreDelta) -> Free f (Either Text ())
updateGenreExternalSources :: forall (f :: * -> *).
(GenreCommand :<: f) =>
Env
-> Map UUID (Genre, Maybe GenreDelta) -> Free f (Either Text ())
updateGenreExternalSources Env
env Map UUID (Genre, Maybe GenreDelta)
deltas = GenreCommand (Free f (Either Text ())) -> Free f (Either Text ())
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (Env
-> Map UUID (Genre, Maybe GenreDelta)
-> (Either Text () -> Free f (Either Text ()))
-> GenreCommand (Free f (Either Text ()))
forall a.
Env
-> Map UUID (Genre, Maybe GenreDelta)
-> (Either Text () -> a)
-> GenreCommand a
UpdateGenreExternalSources Env
env Map UUID (Genre, Maybe GenreDelta)
deltas Either Text () -> Free f (Either Text ())
forall (f :: * -> *) a. a -> Free f a
Pure)
newGenreFromRequest :: (GenreCommand :<: f) => UUID -> InsertGenresRequestItem -> Free f Genre
newGenreFromRequest :: forall (f :: * -> *).
(GenreCommand :<: f) =>
UUID -> InsertGenresRequestItem -> Free f Genre
newGenreFromRequest UUID
uuid InsertGenresRequestItem
req = GenreCommand (Free f Genre) -> Free f Genre
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (UUID
-> InsertGenresRequestItem
-> (Genre -> Free f Genre)
-> GenreCommand (Free f Genre)
forall a.
UUID -> InsertGenresRequestItem -> (Genre -> a) -> GenreCommand a
NewGenreFromRequest UUID
uuid InsertGenresRequestItem
req Genre -> Free f Genre
forall (f :: * -> *) a. a -> Free f a
Pure)
newGenreCommentFromRequest :: (GenreCommand :<: f) => UUID -> InsertGenreCommentsRequestItem -> Free f GenreComment
UUID
uuid InsertGenreCommentsRequestItem
req = GenreCommand (Free f GenreComment) -> Free f GenreComment
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (UUID
-> InsertGenreCommentsRequestItem
-> (GenreComment -> Free f GenreComment)
-> GenreCommand (Free f GenreComment)
forall a.
UUID
-> InsertGenreCommentsRequestItem
-> (GenreComment -> a)
-> GenreCommand a
NewGenreCommentFromRequest UUID
uuid InsertGenreCommentsRequestItem
req GenreComment -> Free f GenreComment
forall (f :: * -> *) a. a -> Free f a
Pure)
newGenreOpinionFromRequest :: (GenreCommand :<: f) => UUID -> UpsertGenreOpinionsRequestItem -> Free f GenreOpinion
newGenreOpinionFromRequest :: forall (f :: * -> *).
(GenreCommand :<: f) =>
UUID -> UpsertGenreOpinionsRequestItem -> Free f GenreOpinion
newGenreOpinionFromRequest UUID
uuid UpsertGenreOpinionsRequestItem
req = GenreCommand (Free f GenreOpinion) -> Free f GenreOpinion
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (UUID
-> UpsertGenreOpinionsRequestItem
-> (GenreOpinion -> Free f GenreOpinion)
-> GenreCommand (Free f GenreOpinion)
forall a.
UUID
-> UpsertGenreOpinionsRequestItem
-> (GenreOpinion -> a)
-> GenreCommand a
NewGenreOpinionFromRequest UUID
uuid UpsertGenreOpinionsRequestItem
req GenreOpinion -> Free f GenreOpinion
forall (f :: * -> *) a. a -> Free f a
Pure)
newGenreArtworkFromRequest :: (GenreCommand :<: f) => UUID -> InsertGenreArtworksRequestItem -> Free f GenreArtwork
newGenreArtworkFromRequest :: forall (f :: * -> *).
(GenreCommand :<: f) =>
UUID -> InsertGenreArtworksRequestItem -> Free f GenreArtwork
newGenreArtworkFromRequest UUID
uuid InsertGenreArtworksRequestItem
req = GenreCommand (Free f GenreArtwork) -> Free f GenreArtwork
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (UUID
-> InsertGenreArtworksRequestItem
-> (GenreArtwork -> Free f GenreArtwork)
-> GenreCommand (Free f GenreArtwork)
forall a.
UUID
-> InsertGenreArtworksRequestItem
-> (GenreArtwork -> a)
-> GenreCommand a
NewGenreArtworkFromRequest UUID
uuid InsertGenreArtworksRequestItem
req GenreArtwork -> Free f GenreArtwork
forall (f :: * -> *) a. a -> Free f a
Pure)
incrementViewsByOne :: (GenreCommand :<: f) => Env -> [UUID] -> Free f (Either GenreCommandError ())
incrementViewsByOne :: forall (f :: * -> *).
(GenreCommand :<: f) =>
Env -> [UUID] -> Free f (Either GenreCommandError ())
incrementViewsByOne Env
env [UUID]
uuids = GenreCommand (Free f (Either GenreCommandError ()))
-> Free f (Either GenreCommandError ())
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (Env
-> [UUID]
-> (Either GenreCommandError ()
-> Free f (Either GenreCommandError ()))
-> GenreCommand (Free f (Either GenreCommandError ()))
forall a.
Env
-> [UUID] -> (Either GenreCommandError () -> a) -> GenreCommand a
IncrementViewsByOne Env
env [UUID]
uuids Either GenreCommandError () -> Free f (Either GenreCommandError ())
forall (f :: * -> *) a. a -> Free f a
Pure)