module WikiMusic.Free.ArtistCommand
( ArtistCommand (..),
insertArtists,
insertArtistComments,
insertArtistArtworks,
upsertArtistOpinions,
insertArtistExternalSources,
deleteArtists,
deleteArtistComments,
deleteArtistArtworks,
deleteArtistOpinions,
deleteCommentsOfArtists,
deleteArtistExternalSources,
deleteArtworksOfArtists,
deleteOpinionsOfArtists,
updateArtistArtworkOrder,
updateArtists,
updateArtistExternalSources,
newArtistFromRequest,
newArtistCommentFromRequest,
newArtistOpinionFromRequest,
newArtistArtworkFromRequest,
ArtistCommandError (..),
incrementViewsByOne,
)
where
import WikiMusic.Interaction.Model.Artist
import WikiMusic.Model.Artist
import WikiMusic.Protolude
data ArtistCommandError = PersistenceError Text | LogicError Text
deriving (ArtistCommandError -> ArtistCommandError -> Bool
(ArtistCommandError -> ArtistCommandError -> Bool)
-> (ArtistCommandError -> ArtistCommandError -> Bool)
-> Eq ArtistCommandError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ArtistCommandError -> ArtistCommandError -> Bool
== :: ArtistCommandError -> ArtistCommandError -> Bool
$c/= :: ArtistCommandError -> ArtistCommandError -> Bool
/= :: ArtistCommandError -> ArtistCommandError -> Bool
Eq, Int -> ArtistCommandError -> ShowS
[ArtistCommandError] -> ShowS
ArtistCommandError -> String
(Int -> ArtistCommandError -> ShowS)
-> (ArtistCommandError -> String)
-> ([ArtistCommandError] -> ShowS)
-> Show ArtistCommandError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ArtistCommandError -> ShowS
showsPrec :: Int -> ArtistCommandError -> ShowS
$cshow :: ArtistCommandError -> String
show :: ArtistCommandError -> String
$cshowList :: [ArtistCommandError] -> ShowS
showList :: [ArtistCommandError] -> ShowS
Show)
type ArtistCommand :: Type -> Type
data ArtistCommand a
= InsertArtists Env [Artist] (() -> a)
| Env [ArtistComment] (() -> a)
| InsertArtistArtworks Env [ArtistArtwork] (Map UUID ArtistArtwork -> a)
| UpsertArtistOpinions Env [ArtistOpinion] (Map UUID ArtistOpinion -> a)
| InsertArtistExternalSources Env [ArtistExternalSources] (Map UUID ArtistExternalSources -> a)
| DeleteArtists Env [UUID] (Either ArtistCommandError () -> a)
| Env [UUID] (Either ArtistCommandError () -> a)
| DeleteArtistArtworks Env [UUID] (Either ArtistCommandError () -> a)
| DeleteArtistOpinions Env [UUID] (Either ArtistCommandError () -> a)
| Env [UUID] (Either ArtistCommandError () -> a)
| DeleteArtistExternalSources Env [UUID] (Either ArtistCommandError () -> a)
| DeleteArtworksOfArtists Env [UUID] (Either ArtistCommandError () -> a)
| DeleteOpinionsOfArtists Env [UUID] (Either ArtistCommandError () -> a)
| UpdateArtistArtworkOrder Env [ArtistArtworkOrderUpdate] (Either Text () -> a)
| UpdateArtists Env (Map UUID (Artist, Maybe ArtistDelta)) (Either Text () -> a)
| UpdateArtistExternalSources Env (Map UUID (Artist, Maybe ArtistDelta)) (Either Text () -> a)
| NewArtistFromRequest UUID InsertArtistsRequestItem (Artist -> a)
| UUID InsertArtistCommentsRequestItem (ArtistComment -> a)
| NewArtistOpinionFromRequest UUID UpsertArtistOpinionsRequestItem (ArtistOpinion -> a)
| NewArtistArtworkFromRequest UUID InsertArtistArtworksRequestItem (ArtistArtwork -> a)
| IncrementViewsByOne Env [UUID] (Either ArtistCommandError () -> a)
deriving ((forall a b. (a -> b) -> ArtistCommand a -> ArtistCommand b)
-> (forall a b. a -> ArtistCommand b -> ArtistCommand a)
-> Functor ArtistCommand
forall a b. a -> ArtistCommand b -> ArtistCommand a
forall a b. (a -> b) -> ArtistCommand a -> ArtistCommand 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) -> ArtistCommand a -> ArtistCommand b
fmap :: forall a b. (a -> b) -> ArtistCommand a -> ArtistCommand b
$c<$ :: forall a b. a -> ArtistCommand b -> ArtistCommand a
<$ :: forall a b. a -> ArtistCommand b -> ArtistCommand a
Functor)
insertArtists :: (ArtistCommand :<: f) => Env -> [Artist] -> Free f ()
insertArtists :: forall (f :: * -> *).
(ArtistCommand :<: f) =>
Env -> [Artist] -> Free f ()
insertArtists Env
env [Artist]
artists = ArtistCommand (Free f ()) -> Free f ()
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (Env -> [Artist] -> (() -> Free f ()) -> ArtistCommand (Free f ())
forall a. Env -> [Artist] -> (() -> a) -> ArtistCommand a
InsertArtists Env
env [Artist]
artists () -> Free f ()
forall (f :: * -> *) a. a -> Free f a
Pure)
insertArtistComments :: (ArtistCommand :<: f) => Env -> [ArtistComment] -> Free f ()
Env
env [ArtistComment]
artistComments = ArtistCommand (Free f ()) -> Free f ()
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (Env
-> [ArtistComment]
-> (() -> Free f ())
-> ArtistCommand (Free f ())
forall a. Env -> [ArtistComment] -> (() -> a) -> ArtistCommand a
InsertArtistComments Env
env [ArtistComment]
artistComments () -> Free f ()
forall (f :: * -> *) a. a -> Free f a
Pure)
insertArtistArtworks :: (ArtistCommand :<: f) => Env -> [ArtistArtwork] -> Free f (Map UUID ArtistArtwork)
insertArtistArtworks :: forall (f :: * -> *).
(ArtistCommand :<: f) =>
Env -> [ArtistArtwork] -> Free f (Map UUID ArtistArtwork)
insertArtistArtworks Env
env [ArtistArtwork]
artistArtworks = ArtistCommand (Free f (Map UUID ArtistArtwork))
-> Free f (Map UUID ArtistArtwork)
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (Env
-> [ArtistArtwork]
-> (Map UUID ArtistArtwork -> Free f (Map UUID ArtistArtwork))
-> ArtistCommand (Free f (Map UUID ArtistArtwork))
forall a.
Env
-> [ArtistArtwork]
-> (Map UUID ArtistArtwork -> a)
-> ArtistCommand a
InsertArtistArtworks Env
env [ArtistArtwork]
artistArtworks Map UUID ArtistArtwork -> Free f (Map UUID ArtistArtwork)
forall (f :: * -> *) a. a -> Free f a
Pure)
upsertArtistOpinions :: (ArtistCommand :<: f) => Env -> [ArtistOpinion] -> Free f (Map UUID ArtistOpinion)
upsertArtistOpinions :: forall (f :: * -> *).
(ArtistCommand :<: f) =>
Env -> [ArtistOpinion] -> Free f (Map UUID ArtistOpinion)
upsertArtistOpinions Env
env [ArtistOpinion]
artistOpinions = ArtistCommand (Free f (Map UUID ArtistOpinion))
-> Free f (Map UUID ArtistOpinion)
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (Env
-> [ArtistOpinion]
-> (Map UUID ArtistOpinion -> Free f (Map UUID ArtistOpinion))
-> ArtistCommand (Free f (Map UUID ArtistOpinion))
forall a.
Env
-> [ArtistOpinion]
-> (Map UUID ArtistOpinion -> a)
-> ArtistCommand a
UpsertArtistOpinions Env
env [ArtistOpinion]
artistOpinions Map UUID ArtistOpinion -> Free f (Map UUID ArtistOpinion)
forall (f :: * -> *) a. a -> Free f a
Pure)
insertArtistExternalSources :: (ArtistCommand :<: f) => Env -> [ArtistExternalSources] -> Free f (Map UUID ArtistExternalSources)
insertArtistExternalSources :: forall (f :: * -> *).
(ArtistCommand :<: f) =>
Env
-> [ArtistExternalSources]
-> Free f (Map UUID ArtistExternalSources)
insertArtistExternalSources Env
env [ArtistExternalSources]
artistExternalSources = ArtistCommand (Free f (Map UUID ArtistExternalSources))
-> Free f (Map UUID ArtistExternalSources)
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (Env
-> [ArtistExternalSources]
-> (Map UUID ArtistExternalSources
-> Free f (Map UUID ArtistExternalSources))
-> ArtistCommand (Free f (Map UUID ArtistExternalSources))
forall a.
Env
-> [ArtistExternalSources]
-> (Map UUID ArtistExternalSources -> a)
-> ArtistCommand a
InsertArtistExternalSources Env
env [ArtistExternalSources]
artistExternalSources Map UUID ArtistExternalSources
-> Free f (Map UUID ArtistExternalSources)
forall (f :: * -> *) a. a -> Free f a
Pure)
deleteArtists :: (ArtistCommand :<: f) => Env -> [UUID] -> Free f (Either ArtistCommandError ())
deleteArtists :: forall (f :: * -> *).
(ArtistCommand :<: f) =>
Env -> [UUID] -> Free f (Either ArtistCommandError ())
deleteArtists Env
env [UUID]
uuids = ArtistCommand (Free f (Either ArtistCommandError ()))
-> Free f (Either ArtistCommandError ())
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (Env
-> [UUID]
-> (Either ArtistCommandError ()
-> Free f (Either ArtistCommandError ()))
-> ArtistCommand (Free f (Either ArtistCommandError ()))
forall a.
Env
-> [UUID] -> (Either ArtistCommandError () -> a) -> ArtistCommand a
DeleteArtists Env
env [UUID]
uuids Either ArtistCommandError ()
-> Free f (Either ArtistCommandError ())
forall (f :: * -> *) a. a -> Free f a
Pure)
deleteArtistComments :: (ArtistCommand :<: f) => Env -> [UUID] -> Free f (Either ArtistCommandError ())
Env
env [UUID]
uuids = ArtistCommand (Free f (Either ArtistCommandError ()))
-> Free f (Either ArtistCommandError ())
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (Env
-> [UUID]
-> (Either ArtistCommandError ()
-> Free f (Either ArtistCommandError ()))
-> ArtistCommand (Free f (Either ArtistCommandError ()))
forall a.
Env
-> [UUID] -> (Either ArtistCommandError () -> a) -> ArtistCommand a
DeleteArtistComments Env
env [UUID]
uuids Either ArtistCommandError ()
-> Free f (Either ArtistCommandError ())
forall (f :: * -> *) a. a -> Free f a
Pure)
deleteArtistArtworks :: (ArtistCommand :<: f) => Env -> [UUID] -> Free f (Either ArtistCommandError ())
deleteArtistArtworks :: forall (f :: * -> *).
(ArtistCommand :<: f) =>
Env -> [UUID] -> Free f (Either ArtistCommandError ())
deleteArtistArtworks Env
env [UUID]
uuids = ArtistCommand (Free f (Either ArtistCommandError ()))
-> Free f (Either ArtistCommandError ())
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (Env
-> [UUID]
-> (Either ArtistCommandError ()
-> Free f (Either ArtistCommandError ()))
-> ArtistCommand (Free f (Either ArtistCommandError ()))
forall a.
Env
-> [UUID] -> (Either ArtistCommandError () -> a) -> ArtistCommand a
DeleteArtistArtworks Env
env [UUID]
uuids Either ArtistCommandError ()
-> Free f (Either ArtistCommandError ())
forall (f :: * -> *) a. a -> Free f a
Pure)
deleteArtistOpinions :: (ArtistCommand :<: f) => Env -> [UUID] -> Free f (Either ArtistCommandError ())
deleteArtistOpinions :: forall (f :: * -> *).
(ArtistCommand :<: f) =>
Env -> [UUID] -> Free f (Either ArtistCommandError ())
deleteArtistOpinions Env
env [UUID]
uuids = ArtistCommand (Free f (Either ArtistCommandError ()))
-> Free f (Either ArtistCommandError ())
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (Env
-> [UUID]
-> (Either ArtistCommandError ()
-> Free f (Either ArtistCommandError ()))
-> ArtistCommand (Free f (Either ArtistCommandError ()))
forall a.
Env
-> [UUID] -> (Either ArtistCommandError () -> a) -> ArtistCommand a
DeleteArtistOpinions Env
env [UUID]
uuids Either ArtistCommandError ()
-> Free f (Either ArtistCommandError ())
forall (f :: * -> *) a. a -> Free f a
Pure)
deleteCommentsOfArtists :: (ArtistCommand :<: f) => Env -> [UUID] -> Free f (Either ArtistCommandError ())
Env
env [UUID]
uuids = ArtistCommand (Free f (Either ArtistCommandError ()))
-> Free f (Either ArtistCommandError ())
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (Env
-> [UUID]
-> (Either ArtistCommandError ()
-> Free f (Either ArtistCommandError ()))
-> ArtistCommand (Free f (Either ArtistCommandError ()))
forall a.
Env
-> [UUID] -> (Either ArtistCommandError () -> a) -> ArtistCommand a
DeleteCommentsOfArtists Env
env [UUID]
uuids Either ArtistCommandError ()
-> Free f (Either ArtistCommandError ())
forall (f :: * -> *) a. a -> Free f a
Pure)
deleteArtistExternalSources :: (ArtistCommand :<: f) => Env -> [UUID] -> Free f (Either ArtistCommandError ())
deleteArtistExternalSources :: forall (f :: * -> *).
(ArtistCommand :<: f) =>
Env -> [UUID] -> Free f (Either ArtistCommandError ())
deleteArtistExternalSources Env
env [UUID]
uuids = ArtistCommand (Free f (Either ArtistCommandError ()))
-> Free f (Either ArtistCommandError ())
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (Env
-> [UUID]
-> (Either ArtistCommandError ()
-> Free f (Either ArtistCommandError ()))
-> ArtistCommand (Free f (Either ArtistCommandError ()))
forall a.
Env
-> [UUID] -> (Either ArtistCommandError () -> a) -> ArtistCommand a
DeleteArtistExternalSources Env
env [UUID]
uuids Either ArtistCommandError ()
-> Free f (Either ArtistCommandError ())
forall (f :: * -> *) a. a -> Free f a
Pure)
deleteArtworksOfArtists :: (ArtistCommand :<: f) => Env -> [UUID] -> Free f (Either ArtistCommandError ())
deleteArtworksOfArtists :: forall (f :: * -> *).
(ArtistCommand :<: f) =>
Env -> [UUID] -> Free f (Either ArtistCommandError ())
deleteArtworksOfArtists Env
env [UUID]
uuids = ArtistCommand (Free f (Either ArtistCommandError ()))
-> Free f (Either ArtistCommandError ())
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (Env
-> [UUID]
-> (Either ArtistCommandError ()
-> Free f (Either ArtistCommandError ()))
-> ArtistCommand (Free f (Either ArtistCommandError ()))
forall a.
Env
-> [UUID] -> (Either ArtistCommandError () -> a) -> ArtistCommand a
DeleteArtworksOfArtists Env
env [UUID]
uuids Either ArtistCommandError ()
-> Free f (Either ArtistCommandError ())
forall (f :: * -> *) a. a -> Free f a
Pure)
deleteOpinionsOfArtists :: (ArtistCommand :<: f) => Env -> [UUID] -> Free f (Either ArtistCommandError ())
deleteOpinionsOfArtists :: forall (f :: * -> *).
(ArtistCommand :<: f) =>
Env -> [UUID] -> Free f (Either ArtistCommandError ())
deleteOpinionsOfArtists Env
env [UUID]
uuids = ArtistCommand (Free f (Either ArtistCommandError ()))
-> Free f (Either ArtistCommandError ())
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (Env
-> [UUID]
-> (Either ArtistCommandError ()
-> Free f (Either ArtistCommandError ()))
-> ArtistCommand (Free f (Either ArtistCommandError ()))
forall a.
Env
-> [UUID] -> (Either ArtistCommandError () -> a) -> ArtistCommand a
DeleteOpinionsOfArtists Env
env [UUID]
uuids Either ArtistCommandError ()
-> Free f (Either ArtistCommandError ())
forall (f :: * -> *) a. a -> Free f a
Pure)
updateArtistArtworkOrder :: (ArtistCommand :<: f) => Env -> [ArtistArtworkOrderUpdate] -> Free f (Either Text ())
updateArtistArtworkOrder :: forall (f :: * -> *).
(ArtistCommand :<: f) =>
Env -> [ArtistArtworkOrderUpdate] -> Free f (Either Text ())
updateArtistArtworkOrder Env
env [ArtistArtworkOrderUpdate]
uuids = ArtistCommand (Free f (Either Text ())) -> Free f (Either Text ())
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (Env
-> [ArtistArtworkOrderUpdate]
-> (Either Text () -> Free f (Either Text ()))
-> ArtistCommand (Free f (Either Text ()))
forall a.
Env
-> [ArtistArtworkOrderUpdate]
-> (Either Text () -> a)
-> ArtistCommand a
UpdateArtistArtworkOrder Env
env [ArtistArtworkOrderUpdate]
uuids Either Text () -> Free f (Either Text ())
forall (f :: * -> *) a. a -> Free f a
Pure)
updateArtists :: (ArtistCommand :<: f) => Env -> Map UUID (Artist, Maybe ArtistDelta) -> Free f (Either Text ())
updateArtists :: forall (f :: * -> *).
(ArtistCommand :<: f) =>
Env
-> Map UUID (Artist, Maybe ArtistDelta) -> Free f (Either Text ())
updateArtists Env
env Map UUID (Artist, Maybe ArtistDelta)
deltas = ArtistCommand (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 (Artist, Maybe ArtistDelta)
-> (Either Text () -> Free f (Either Text ()))
-> ArtistCommand (Free f (Either Text ()))
forall a.
Env
-> Map UUID (Artist, Maybe ArtistDelta)
-> (Either Text () -> a)
-> ArtistCommand a
UpdateArtists Env
env Map UUID (Artist, Maybe ArtistDelta)
deltas Either Text () -> Free f (Either Text ())
forall (f :: * -> *) a. a -> Free f a
Pure)
updateArtistExternalSources :: (ArtistCommand :<: f) => Env -> Map UUID (Artist, Maybe ArtistDelta) -> Free f (Either Text ())
updateArtistExternalSources :: forall (f :: * -> *).
(ArtistCommand :<: f) =>
Env
-> Map UUID (Artist, Maybe ArtistDelta) -> Free f (Either Text ())
updateArtistExternalSources Env
env Map UUID (Artist, Maybe ArtistDelta)
deltas = ArtistCommand (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 (Artist, Maybe ArtistDelta)
-> (Either Text () -> Free f (Either Text ()))
-> ArtistCommand (Free f (Either Text ()))
forall a.
Env
-> Map UUID (Artist, Maybe ArtistDelta)
-> (Either Text () -> a)
-> ArtistCommand a
UpdateArtistExternalSources Env
env Map UUID (Artist, Maybe ArtistDelta)
deltas Either Text () -> Free f (Either Text ())
forall (f :: * -> *) a. a -> Free f a
Pure)
newArtistFromRequest :: (ArtistCommand :<: f) => UUID -> InsertArtistsRequestItem -> Free f Artist
newArtistFromRequest :: forall (f :: * -> *).
(ArtistCommand :<: f) =>
UUID -> InsertArtistsRequestItem -> Free f Artist
newArtistFromRequest UUID
uuid InsertArtistsRequestItem
req = ArtistCommand (Free f Artist) -> Free f Artist
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (UUID
-> InsertArtistsRequestItem
-> (Artist -> Free f Artist)
-> ArtistCommand (Free f Artist)
forall a.
UUID
-> InsertArtistsRequestItem -> (Artist -> a) -> ArtistCommand a
NewArtistFromRequest UUID
uuid InsertArtistsRequestItem
req Artist -> Free f Artist
forall (f :: * -> *) a. a -> Free f a
Pure)
newArtistCommentFromRequest :: (ArtistCommand :<: f) => UUID -> InsertArtistCommentsRequestItem -> Free f ArtistComment
UUID
uuid InsertArtistCommentsRequestItem
req = ArtistCommand (Free f ArtistComment) -> Free f ArtistComment
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (UUID
-> InsertArtistCommentsRequestItem
-> (ArtistComment -> Free f ArtistComment)
-> ArtistCommand (Free f ArtistComment)
forall a.
UUID
-> InsertArtistCommentsRequestItem
-> (ArtistComment -> a)
-> ArtistCommand a
NewArtistCommentFromRequest UUID
uuid InsertArtistCommentsRequestItem
req ArtistComment -> Free f ArtistComment
forall (f :: * -> *) a. a -> Free f a
Pure)
newArtistOpinionFromRequest :: (ArtistCommand :<: f) => UUID -> UpsertArtistOpinionsRequestItem -> Free f ArtistOpinion
newArtistOpinionFromRequest :: forall (f :: * -> *).
(ArtistCommand :<: f) =>
UUID -> UpsertArtistOpinionsRequestItem -> Free f ArtistOpinion
newArtistOpinionFromRequest UUID
uuid UpsertArtistOpinionsRequestItem
req = ArtistCommand (Free f ArtistOpinion) -> Free f ArtistOpinion
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (UUID
-> UpsertArtistOpinionsRequestItem
-> (ArtistOpinion -> Free f ArtistOpinion)
-> ArtistCommand (Free f ArtistOpinion)
forall a.
UUID
-> UpsertArtistOpinionsRequestItem
-> (ArtistOpinion -> a)
-> ArtistCommand a
NewArtistOpinionFromRequest UUID
uuid UpsertArtistOpinionsRequestItem
req ArtistOpinion -> Free f ArtistOpinion
forall (f :: * -> *) a. a -> Free f a
Pure)
newArtistArtworkFromRequest :: (ArtistCommand :<: f) => UUID -> InsertArtistArtworksRequestItem -> Free f ArtistArtwork
newArtistArtworkFromRequest :: forall (f :: * -> *).
(ArtistCommand :<: f) =>
UUID -> InsertArtistArtworksRequestItem -> Free f ArtistArtwork
newArtistArtworkFromRequest UUID
uuid InsertArtistArtworksRequestItem
req = ArtistCommand (Free f ArtistArtwork) -> Free f ArtistArtwork
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (UUID
-> InsertArtistArtworksRequestItem
-> (ArtistArtwork -> Free f ArtistArtwork)
-> ArtistCommand (Free f ArtistArtwork)
forall a.
UUID
-> InsertArtistArtworksRequestItem
-> (ArtistArtwork -> a)
-> ArtistCommand a
NewArtistArtworkFromRequest UUID
uuid InsertArtistArtworksRequestItem
req ArtistArtwork -> Free f ArtistArtwork
forall (f :: * -> *) a. a -> Free f a
Pure)
incrementViewsByOne :: (ArtistCommand :<: f) => Env -> [UUID] -> Free f (Either ArtistCommandError ())
incrementViewsByOne :: forall (f :: * -> *).
(ArtistCommand :<: f) =>
Env -> [UUID] -> Free f (Either ArtistCommandError ())
incrementViewsByOne Env
env [UUID]
uuids = ArtistCommand (Free f (Either ArtistCommandError ()))
-> Free f (Either ArtistCommandError ())
forall (g :: * -> *) (f :: * -> *) a.
(g :<: f) =>
g (Free f a) -> Free f a
injectFree (Env
-> [UUID]
-> (Either ArtistCommandError ()
-> Free f (Either ArtistCommandError ()))
-> ArtistCommand (Free f (Either ArtistCommandError ()))
forall a.
Env
-> [UUID] -> (Either ArtistCommandError () -> a) -> ArtistCommand a
IncrementViewsByOne Env
env [UUID]
uuids Either ArtistCommandError ()
-> Free f (Either ArtistCommandError ())
forall (f :: * -> *) a. a -> Free f a
Pure)