{-# LANGUAGE OverloadedLabels #-}
module WikiMusic.Interaction.Artist
( fetchArtistsAction,
insertArtistsAction,
insertArtistCommentsAction,
insertArtistArtworksAction,
upsertArtistOpinionsAction,
deleteArtistsByIdentifierAction,
deleteArtistCommentsByIdentifierAction,
deleteArtistOpinionsByIdentifierAction,
deleteArtistArtworksByIdentifierAction,
updateArtistArtworksOrderAction,
updateArtistAction,
fetchArtistAction,
searchArtistsAction,
)
where
import Data.Map qualified as Map
import Data.Text (pack, take, unpack)
import Relude
import WikiMusic.Free.ArtistCommand
import WikiMusic.Free.ArtistQuery
import WikiMusic.Interaction.Model.Artist
import WikiMusic.Model.Artist
import WikiMusic.Model.Other
import WikiMusic.Protolude
import WikiMusic.Sqlite.ArtistCommand ()
import WikiMusic.Sqlite.ArtistQuery ()
fetchArtistsAction ::
(ArtistQuery :<: f, ArtistCommand :<: f) =>
Env ->
WikiMusicUser ->
Limit ->
Offset ->
Maybe Text ->
Maybe Text ->
Free f (Either ArtistError GetArtistsQueryResponse)
fetchArtistsAction :: forall (f :: * -> *).
(ArtistQuery :<: f, ArtistCommand :<: f) =>
Env
-> WikiMusicUser
-> Limit
-> Offset
-> Maybe Text
-> Maybe Text
-> Free f (Either ArtistError GetArtistsQueryResponse)
fetchArtistsAction Env
env WikiMusicUser
authUser Limit
limit Offset
offset Maybe Text
maybeSortOrder Maybe Text
maybeInclude =
WikiMusicUser
-> ([UserRole] -> Bool)
-> ArtistError
-> Free f (Either ArtistError GetArtistsQueryResponse)
-> Free f (Either ArtistError GetArtistsQueryResponse)
forall (f :: * -> *) p b.
Applicative f =>
WikiMusicUser
-> ([UserRole] -> Bool) -> p -> f (Either p b) -> f (Either p b)
doWithRoles' WikiMusicUser
authUser [UserRole] -> Bool
isAtLeastDemo ArtistError
AccessUnauthorizedError (Free f (Either ArtistError GetArtistsQueryResponse)
-> Free f (Either ArtistError GetArtistsQueryResponse))
-> Free f (Either ArtistError GetArtistsQueryResponse)
-> Free f (Either ArtistError GetArtistsQueryResponse)
forall a b. (a -> b) -> a -> b
$ do
(Map UUID Artist
artistMap, [UUID]
sortOrderList) <- Env
-> ArtistSortOrder
-> Limit
-> Offset
-> Free f (Map UUID Artist, [UUID])
forall (f :: * -> *).
(ArtistQuery :<: f) =>
Env
-> ArtistSortOrder
-> Limit
-> Offset
-> Free f (Map UUID Artist, [UUID])
fetchArtists Env
env ArtistSortOrder
sortOrder Limit
limit Offset
offset
Map UUID Artist
enrichedArtists <-
Env
-> Map UUID Artist
-> EnrichArtistParams
-> Free f (Map UUID Artist)
forall (f :: * -> *).
(ArtistQuery :<: f) =>
Env
-> Map UUID Artist
-> EnrichArtistParams
-> Free f (Map UUID Artist)
enrichedArtistResponse
Env
env
Map UUID Artist
artistMap
(EnrichArtistParams
-> (Text -> EnrichArtistParams) -> Maybe Text -> EnrichArtistParams
forall b a. b -> (a -> b) -> Maybe a -> b
maybe EnrichArtistParams
noEnrichment Text -> EnrichArtistParams
parseInclude Maybe Text
maybeInclude)
Either ArtistError GetArtistsQueryResponse
-> Free f (Either ArtistError GetArtistsQueryResponse)
forall a. a -> Free f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either ArtistError GetArtistsQueryResponse
-> Free f (Either ArtistError GetArtistsQueryResponse))
-> (GetArtistsQueryResponse
-> Either ArtistError GetArtistsQueryResponse)
-> GetArtistsQueryResponse
-> Free f (Either ArtistError GetArtistsQueryResponse)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GetArtistsQueryResponse
-> Either ArtistError GetArtistsQueryResponse
forall a b. b -> Either a b
Right (GetArtistsQueryResponse
-> Free f (Either ArtistError GetArtistsQueryResponse))
-> GetArtistsQueryResponse
-> Free f (Either ArtistError GetArtistsQueryResponse)
forall a b. (a -> b) -> a -> b
$ GetArtistsQueryResponse {$sel:artists:GetArtistsQueryResponse :: Map UUID Artist
artists = Map UUID Artist
enrichedArtists, $sel:sortOrder:GetArtistsQueryResponse :: [UUID]
sortOrder = [UUID]
sortOrderList}
where
sortOrder :: ArtistSortOrder
sortOrder = ArtistSortOrder -> Maybe ArtistSortOrder -> ArtistSortOrder
forall a. a -> Maybe a -> a
fromMaybe ArtistSortOrder
DescCreatedAt (String -> Maybe ArtistSortOrder
forall a. Read a => String -> Maybe a
readMaybe (String -> Maybe ArtistSortOrder)
-> (Text -> String) -> Text -> Maybe ArtistSortOrder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
unpack (Text -> Maybe ArtistSortOrder)
-> Maybe Text -> Maybe ArtistSortOrder
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Maybe Text
maybeSortOrder)
searchArtistsAction ::
(ArtistQuery :<: f, ArtistCommand :<: f) =>
Env ->
WikiMusicUser ->
Limit ->
Offset ->
Maybe Text ->
Maybe Text ->
Text ->
Free f (Either ArtistError GetArtistsQueryResponse)
searchArtistsAction :: forall (f :: * -> *).
(ArtistQuery :<: f, ArtistCommand :<: f) =>
Env
-> WikiMusicUser
-> Limit
-> Offset
-> Maybe Text
-> Maybe Text
-> Text
-> Free f (Either ArtistError GetArtistsQueryResponse)
searchArtistsAction Env
env WikiMusicUser
authUser Limit
limit Offset
offset Maybe Text
maybeSortOrder Maybe Text
maybeInclude Text
searchInput =
WikiMusicUser
-> ([UserRole] -> Bool)
-> ArtistError
-> Free f (Either ArtistError GetArtistsQueryResponse)
-> Free f (Either ArtistError GetArtistsQueryResponse)
forall (f :: * -> *) p b.
Applicative f =>
WikiMusicUser
-> ([UserRole] -> Bool) -> p -> f (Either p b) -> f (Either p b)
doWithRoles' WikiMusicUser
authUser [UserRole] -> Bool
isAtLeastDemo ArtistError
AccessUnauthorizedError (Free f (Either ArtistError GetArtistsQueryResponse)
-> Free f (Either ArtistError GetArtistsQueryResponse))
-> Free f (Either ArtistError GetArtistsQueryResponse)
-> Free f (Either ArtistError GetArtistsQueryResponse)
forall a b. (a -> b) -> a -> b
$ do
(Map UUID Artist
artistMap, [UUID]
sortOrderList) <- Env
-> SearchInput
-> ArtistSortOrder
-> Limit
-> Offset
-> Free f (Map UUID Artist, [UUID])
forall (f :: * -> *).
(ArtistQuery :<: f) =>
Env
-> SearchInput
-> ArtistSortOrder
-> Limit
-> Offset
-> Free f (Map UUID Artist, [UUID])
searchArtists Env
env (Text -> SearchInput
SearchInput Text
searchInput) ArtistSortOrder
sortOrder Limit
limit Offset
offset
Map UUID Artist
enrichedArtists <-
Env
-> Map UUID Artist
-> EnrichArtistParams
-> Free f (Map UUID Artist)
forall (f :: * -> *).
(ArtistQuery :<: f) =>
Env
-> Map UUID Artist
-> EnrichArtistParams
-> Free f (Map UUID Artist)
enrichedArtistResponse
Env
env
Map UUID Artist
artistMap
(EnrichArtistParams
-> (Text -> EnrichArtistParams) -> Maybe Text -> EnrichArtistParams
forall b a. b -> (a -> b) -> Maybe a -> b
maybe EnrichArtistParams
noEnrichment Text -> EnrichArtistParams
parseInclude Maybe Text
maybeInclude)
Either ArtistError GetArtistsQueryResponse
-> Free f (Either ArtistError GetArtistsQueryResponse)
forall a. a -> Free f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either ArtistError GetArtistsQueryResponse
-> Free f (Either ArtistError GetArtistsQueryResponse))
-> (GetArtistsQueryResponse
-> Either ArtistError GetArtistsQueryResponse)
-> GetArtistsQueryResponse
-> Free f (Either ArtistError GetArtistsQueryResponse)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GetArtistsQueryResponse
-> Either ArtistError GetArtistsQueryResponse
forall a b. b -> Either a b
Right (GetArtistsQueryResponse
-> Free f (Either ArtistError GetArtistsQueryResponse))
-> GetArtistsQueryResponse
-> Free f (Either ArtistError GetArtistsQueryResponse)
forall a b. (a -> b) -> a -> b
$ GetArtistsQueryResponse {$sel:artists:GetArtistsQueryResponse :: Map UUID Artist
artists = Map UUID Artist
enrichedArtists, $sel:sortOrder:GetArtistsQueryResponse :: [UUID]
sortOrder = [UUID]
sortOrderList}
where
sortOrder :: ArtistSortOrder
sortOrder = ArtistSortOrder -> Maybe ArtistSortOrder -> ArtistSortOrder
forall a. a -> Maybe a -> a
fromMaybe ArtistSortOrder
DescCreatedAt (String -> Maybe ArtistSortOrder
forall a. Read a => String -> Maybe a
readMaybe (String -> Maybe ArtistSortOrder)
-> (Text -> String) -> Text -> Maybe ArtistSortOrder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
unpack (Text -> Maybe ArtistSortOrder)
-> Maybe Text -> Maybe ArtistSortOrder
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Maybe Text
maybeSortOrder)
fetchArtistAction ::
(ArtistQuery :<: f, ArtistCommand :<: f) =>
Env ->
WikiMusicUser ->
UUID ->
Maybe Text ->
Maybe Text ->
Free f (Either ArtistError GetArtistsQueryResponse)
fetchArtistAction :: forall (f :: * -> *).
(ArtistQuery :<: f, ArtistCommand :<: f) =>
Env
-> WikiMusicUser
-> UUID
-> Maybe Text
-> Maybe Text
-> Free f (Either ArtistError GetArtistsQueryResponse)
fetchArtistAction Env
env WikiMusicUser
authUser UUID
identifier Maybe Text
maybeSortOrder Maybe Text
maybeInclude =
WikiMusicUser
-> ([UserRole] -> Bool)
-> ArtistError
-> Free f (Either ArtistError GetArtistsQueryResponse)
-> Free f (Either ArtistError GetArtistsQueryResponse)
forall (f :: * -> *) p b.
Applicative f =>
WikiMusicUser
-> ([UserRole] -> Bool) -> p -> f (Either p b) -> f (Either p b)
doWithRoles' WikiMusicUser
authUser [UserRole] -> Bool
isAtLeastDemo ArtistError
AccessUnauthorizedError (Free f (Either ArtistError GetArtistsQueryResponse)
-> Free f (Either ArtistError GetArtistsQueryResponse))
-> Free f (Either ArtistError GetArtistsQueryResponse)
-> Free f (Either ArtistError GetArtistsQueryResponse)
forall a b. (a -> b) -> a -> b
$ do
(Map UUID Artist
artistMap, [UUID]
sortOrderList) <- Env
-> ArtistSortOrder -> [UUID] -> Free f (Map UUID Artist, [UUID])
forall (f :: * -> *).
(ArtistQuery :<: f) =>
Env
-> ArtistSortOrder -> [UUID] -> Free f (Map UUID Artist, [UUID])
fetchArtistsByUUID Env
env ArtistSortOrder
sortOrder [UUID
identifier]
Map UUID Artist
enrichedArtists <-
Env
-> Map UUID Artist
-> EnrichArtistParams
-> Free f (Map UUID Artist)
forall (f :: * -> *).
(ArtistQuery :<: f) =>
Env
-> Map UUID Artist
-> EnrichArtistParams
-> Free f (Map UUID Artist)
enrichedArtistResponse
Env
env
Map UUID Artist
artistMap
(EnrichArtistParams
-> (Text -> EnrichArtistParams) -> Maybe Text -> EnrichArtistParams
forall b a. b -> (a -> b) -> Maybe a -> b
maybe EnrichArtistParams
noEnrichment Text -> EnrichArtistParams
parseInclude Maybe Text
maybeInclude)
Either ArtistCommandError ()
_ <- Env -> [UUID] -> Free f (Either ArtistCommandError ())
forall (f :: * -> *).
(ArtistCommand :<: f) =>
Env -> [UUID] -> Free f (Either ArtistCommandError ())
incrementViewsByOne Env
env (Map UUID Artist -> [UUID]
forall k a. Map k a -> [k]
Map.keys Map UUID Artist
artistMap)
Either ArtistError GetArtistsQueryResponse
-> Free f (Either ArtistError GetArtistsQueryResponse)
forall a. a -> Free f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either ArtistError GetArtistsQueryResponse
-> Free f (Either ArtistError GetArtistsQueryResponse))
-> (GetArtistsQueryResponse
-> Either ArtistError GetArtistsQueryResponse)
-> GetArtistsQueryResponse
-> Free f (Either ArtistError GetArtistsQueryResponse)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GetArtistsQueryResponse
-> Either ArtistError GetArtistsQueryResponse
forall a b. b -> Either a b
Right (GetArtistsQueryResponse
-> Free f (Either ArtistError GetArtistsQueryResponse))
-> GetArtistsQueryResponse
-> Free f (Either ArtistError GetArtistsQueryResponse)
forall a b. (a -> b) -> a -> b
$ GetArtistsQueryResponse {$sel:artists:GetArtistsQueryResponse :: Map UUID Artist
artists = Map UUID Artist
enrichedArtists, $sel:sortOrder:GetArtistsQueryResponse :: [UUID]
sortOrder = [UUID]
sortOrderList}
where
sortOrder :: ArtistSortOrder
sortOrder = ArtistSortOrder -> Maybe ArtistSortOrder -> ArtistSortOrder
forall a. a -> Maybe a -> a
fromMaybe ArtistSortOrder
DescCreatedAt (String -> Maybe ArtistSortOrder
forall a. Read a => String -> Maybe a
readMaybe (String -> Maybe ArtistSortOrder)
-> (Text -> String) -> Text -> Maybe ArtistSortOrder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
unpack (Text -> Maybe ArtistSortOrder)
-> Maybe Text -> Maybe ArtistSortOrder
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Maybe Text
maybeSortOrder)
insertArtistsAction ::
(ArtistCommand :<: f, ArtistQuery :<: f) =>
Env ->
WikiMusicUser ->
InsertArtistsRequest ->
Free f (Either ArtistError InsertArtistsCommandResponse)
insertArtistsAction :: forall (f :: * -> *).
(ArtistCommand :<: f, ArtistQuery :<: f) =>
Env
-> WikiMusicUser
-> InsertArtistsRequest
-> Free f (Either ArtistError InsertArtistsCommandResponse)
insertArtistsAction Env
env WikiMusicUser
authUser InsertArtistsRequest
request =
WikiMusicUser
-> ([UserRole] -> Bool)
-> ArtistError
-> Free f (Either ArtistError InsertArtistsCommandResponse)
-> Free f (Either ArtistError InsertArtistsCommandResponse)
forall (f :: * -> *) p b.
Applicative f =>
WikiMusicUser
-> ([UserRole] -> Bool) -> p -> f (Either p b) -> f (Either p b)
doWithRoles' WikiMusicUser
authUser [UserRole] -> Bool
isAtLeastLowRank ArtistError
AccessUnauthorizedError (Free f (Either ArtistError InsertArtistsCommandResponse)
-> Free f (Either ArtistError InsertArtistsCommandResponse))
-> Free f (Either ArtistError InsertArtistsCommandResponse)
-> Free f (Either ArtistError InsertArtistsCommandResponse)
forall a b. (a -> b) -> a -> b
$ do
[Artist]
newArtists <- (InsertArtistsRequestItem -> Free f Artist)
-> [InsertArtistsRequestItem] -> Free f [Artist]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (UUID -> InsertArtistsRequestItem -> Free f Artist
forall (f :: * -> *).
(ArtistCommand :<: f) =>
UUID -> InsertArtistsRequestItem -> Free f Artist
newArtistFromRequest (WikiMusicUser
authUser WikiMusicUser -> Optic' A_Lens NoIx WikiMusicUser UUID -> UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx WikiMusicUser UUID
#identifier)) (InsertArtistsRequest
request InsertArtistsRequest
-> Optic'
An_Iso NoIx InsertArtistsRequest [InsertArtistsRequestItem]
-> [InsertArtistsRequestItem]
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' An_Iso NoIx InsertArtistsRequest [InsertArtistsRequestItem]
#artists)
let entityValidation :: Artist -> (Text, Validation [Text])
entityValidation Artist
x = (Artist
x Artist -> Optic' A_Lens NoIx Artist Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Artist Text
#displayName, Artist -> Validation [Text]
validateArtist Artist
x)
validationResults :: Map Text (Validation [Text])
validationResults = [Item (Map Text (Validation [Text]))]
-> Map Text (Validation [Text])
forall l. IsList l => [Item l] -> l
fromList ([Item (Map Text (Validation [Text]))]
-> Map Text (Validation [Text]))
-> [Item (Map Text (Validation [Text]))]
-> Map Text (Validation [Text])
forall a b. (a -> b) -> a -> b
$ (Artist -> (Text, Validation [Text]))
-> [Artist] -> [(Text, Validation [Text])]
forall a b. (a -> b) -> [a] -> [b]
map Artist -> (Text, Validation [Text])
entityValidation [Artist]
newArtists
newArtistIdentifiers :: [UUID]
newArtistIdentifiers = (Artist -> UUID) -> [Artist] -> [UUID]
forall a b. (a -> b) -> [a] -> [b]
map (Artist -> Optic' A_Lens NoIx Artist UUID -> UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Artist UUID
#identifier) [Artist]
newArtists
Map Text (Validation [Text])
-> Free f (Either ArtistError InsertArtistsCommandResponse)
-> Free f (Either ArtistError InsertArtistsCommandResponse)
forall (f :: * -> *) b.
Applicative f =>
Map Text (Validation [Text])
-> f (Either ArtistError b) -> f (Either ArtistError b)
ifAllValid Map Text (Validation [Text])
validationResults (Free f (Either ArtistError InsertArtistsCommandResponse)
-> Free f (Either ArtistError InsertArtistsCommandResponse))
-> Free f (Either ArtistError InsertArtistsCommandResponse)
-> Free f (Either ArtistError InsertArtistsCommandResponse)
forall a b. (a -> b) -> a -> b
$ do
()
_ <- Env -> [Artist] -> Free f ()
forall (f :: * -> *).
(ArtistCommand :<: f) =>
Env -> [Artist] -> Free f ()
insertArtists Env
env [Artist]
newArtists
(Map UUID Artist
artistMap, [UUID]
sortOrder) <- Env
-> ArtistSortOrder -> [UUID] -> Free f (Map UUID Artist, [UUID])
forall (f :: * -> *).
(ArtistQuery :<: f) =>
Env
-> ArtistSortOrder -> [UUID] -> Free f (Map UUID Artist, [UUID])
fetchArtistsByUUID Env
env ArtistSortOrder
DescCreatedAt [UUID]
newArtistIdentifiers
Map UUID Artist
enrichedInsertedArtists <- Env
-> Map UUID Artist
-> EnrichArtistParams
-> Free f (Map UUID Artist)
forall (f :: * -> *).
(ArtistQuery :<: f) =>
Env
-> Map UUID Artist
-> EnrichArtistParams
-> Free f (Map UUID Artist)
enrichedArtistResponse Env
env Map UUID Artist
artistMap EnrichArtistParams
fullEnrichment
Either ArtistError InsertArtistsCommandResponse
-> Free f (Either ArtistError InsertArtistsCommandResponse)
forall a. a -> Free f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
(Either ArtistError InsertArtistsCommandResponse
-> Free f (Either ArtistError InsertArtistsCommandResponse))
-> (InsertArtistsCommandResponse
-> Either ArtistError InsertArtistsCommandResponse)
-> InsertArtistsCommandResponse
-> Free f (Either ArtistError InsertArtistsCommandResponse)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InsertArtistsCommandResponse
-> Either ArtistError InsertArtistsCommandResponse
forall a b. b -> Either a b
Right
(InsertArtistsCommandResponse
-> Free f (Either ArtistError InsertArtistsCommandResponse))
-> InsertArtistsCommandResponse
-> Free f (Either ArtistError InsertArtistsCommandResponse)
forall a b. (a -> b) -> a -> b
$ InsertArtistsQueryResponse
{ $sel:artists:InsertArtistsQueryResponse :: Map UUID Artist
artists = Map UUID Artist
enrichedInsertedArtists,
$sel:sortOrder:InsertArtistsQueryResponse :: [UUID]
sortOrder = [UUID]
sortOrder,
$sel:validationResults:InsertArtistsQueryResponse :: Map Text (Validation [Text])
validationResults = Map Text (Validation [Text])
validationResults
}
insertArtistCommentsAction ::
(ArtistCommand :<: f) =>
Env ->
WikiMusicUser ->
InsertArtistCommentsRequest ->
Free f (Either ArtistError InsertArtistCommentsCommandResponse)
Env
env WikiMusicUser
authUser InsertArtistCommentsRequest
request =
WikiMusicUser
-> ([UserRole] -> Bool)
-> ArtistError
-> Free f (Either ArtistError InsertArtistCommentsCommandResponse)
-> Free f (Either ArtistError InsertArtistCommentsCommandResponse)
forall (f :: * -> *) p b.
Applicative f =>
WikiMusicUser
-> ([UserRole] -> Bool) -> p -> f (Either p b) -> f (Either p b)
doWithRoles' WikiMusicUser
authUser [UserRole] -> Bool
isAtLeastDemo ArtistError
AccessUnauthorizedError (Free f (Either ArtistError InsertArtistCommentsCommandResponse)
-> Free f (Either ArtistError InsertArtistCommentsCommandResponse))
-> Free f (Either ArtistError InsertArtistCommentsCommandResponse)
-> Free f (Either ArtistError InsertArtistCommentsCommandResponse)
forall a b. (a -> b) -> a -> b
$ do
[ArtistComment]
newComments <- (InsertArtistCommentsRequestItem -> Free f ArtistComment)
-> [InsertArtistCommentsRequestItem] -> Free f [ArtistComment]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (UUID -> InsertArtistCommentsRequestItem -> Free f ArtistComment
forall (f :: * -> *).
(ArtistCommand :<: f) =>
UUID -> InsertArtistCommentsRequestItem -> Free f ArtistComment
newArtistCommentFromRequest (WikiMusicUser
authUser WikiMusicUser -> Optic' A_Lens NoIx WikiMusicUser UUID -> UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx WikiMusicUser UUID
#identifier)) (InsertArtistCommentsRequest
request InsertArtistCommentsRequest
-> Optic'
An_Iso
NoIx
InsertArtistCommentsRequest
[InsertArtistCommentsRequestItem]
-> [InsertArtistCommentsRequestItem]
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic'
An_Iso
NoIx
InsertArtistCommentsRequest
[InsertArtistCommentsRequestItem]
#artistComments)
let entityValidation :: ArtistComment -> (Text, Validation [Text])
entityValidation ArtistComment
x = (Int -> Text -> Text
Data.Text.take Int
20 (ArtistComment
x ArtistComment -> Optic' A_Lens NoIx ArtistComment Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic A_Lens NoIx ArtistComment ArtistComment Comment Comment
#comment Optic A_Lens NoIx ArtistComment ArtistComment Comment Comment
-> Optic A_Lens NoIx Comment Comment Text Text
-> Optic' A_Lens NoIx ArtistComment Text
forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% Optic A_Lens NoIx Comment Comment Text Text
#contents), ArtistComment -> Validation [Text]
validateArtistComment ArtistComment
x)
validationResults :: Map Text (Validation [Text])
validationResults = [Item (Map Text (Validation [Text]))]
-> Map Text (Validation [Text])
forall l. IsList l => [Item l] -> l
fromList ([Item (Map Text (Validation [Text]))]
-> Map Text (Validation [Text]))
-> [Item (Map Text (Validation [Text]))]
-> Map Text (Validation [Text])
forall a b. (a -> b) -> a -> b
$ (ArtistComment -> (Text, Validation [Text]))
-> [ArtistComment] -> [(Text, Validation [Text])]
forall a b. (a -> b) -> [a] -> [b]
map ArtistComment -> (Text, Validation [Text])
entityValidation [ArtistComment]
newComments
Map Text (Validation [Text])
-> Free f (Either ArtistError InsertArtistCommentsCommandResponse)
-> Free f (Either ArtistError InsertArtistCommentsCommandResponse)
forall (f :: * -> *) b.
Applicative f =>
Map Text (Validation [Text])
-> f (Either ArtistError b) -> f (Either ArtistError b)
ifAllValid Map Text (Validation [Text])
validationResults (Free f (Either ArtistError InsertArtistCommentsCommandResponse)
-> Free f (Either ArtistError InsertArtistCommentsCommandResponse))
-> Free f (Either ArtistError InsertArtistCommentsCommandResponse)
-> Free f (Either ArtistError InsertArtistCommentsCommandResponse)
forall a b. (a -> b) -> a -> b
$ do
()
_ <- Env -> [ArtistComment] -> Free f ()
forall (f :: * -> *).
(ArtistCommand :<: f) =>
Env -> [ArtistComment] -> Free f ()
insertArtistComments Env
env [ArtistComment]
newComments
Either ArtistError InsertArtistCommentsCommandResponse
-> Free f (Either ArtistError InsertArtistCommentsCommandResponse)
forall a. a -> Free f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
(Either ArtistError InsertArtistCommentsCommandResponse
-> Free f (Either ArtistError InsertArtistCommentsCommandResponse))
-> (InsertArtistCommentsCommandResponse
-> Either ArtistError InsertArtistCommentsCommandResponse)
-> InsertArtistCommentsCommandResponse
-> Free f (Either ArtistError InsertArtistCommentsCommandResponse)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InsertArtistCommentsCommandResponse
-> Either ArtistError InsertArtistCommentsCommandResponse
forall a b. b -> Either a b
Right
(InsertArtistCommentsCommandResponse
-> Free f (Either ArtistError InsertArtistCommentsCommandResponse))
-> InsertArtistCommentsCommandResponse
-> Free f (Either ArtistError InsertArtistCommentsCommandResponse)
forall a b. (a -> b) -> a -> b
$ InsertArtistCommentsCommandResponse
{ $sel:artistComments:InsertArtistCommentsCommandResponse :: Map UUID ArtistComment
artistComments = Map UUID ArtistComment
forall k a. Map k a
Map.empty,
$sel:validationResults:InsertArtistCommentsCommandResponse :: Map Text (Validation [Text])
validationResults = Map Text (Validation [Text])
validationResults
}
upsertArtistOpinionsAction ::
(ArtistCommand :<: f) =>
Env ->
WikiMusicUser ->
UpsertArtistOpinionsRequest ->
Free f (Either ArtistError UpsertArtistOpinionsCommandResponse)
upsertArtistOpinionsAction :: forall (f :: * -> *).
(ArtistCommand :<: f) =>
Env
-> WikiMusicUser
-> UpsertArtistOpinionsRequest
-> Free f (Either ArtistError UpsertArtistOpinionsCommandResponse)
upsertArtistOpinionsAction Env
env WikiMusicUser
authUser UpsertArtistOpinionsRequest
request =
WikiMusicUser
-> ([UserRole] -> Bool)
-> ArtistError
-> Free f (Either ArtistError UpsertArtistOpinionsCommandResponse)
-> Free f (Either ArtistError UpsertArtistOpinionsCommandResponse)
forall (f :: * -> *) p b.
Applicative f =>
WikiMusicUser
-> ([UserRole] -> Bool) -> p -> f (Either p b) -> f (Either p b)
doWithRoles' WikiMusicUser
authUser [UserRole] -> Bool
isAtLeastDemo ArtistError
AccessUnauthorizedError (Free f (Either ArtistError UpsertArtistOpinionsCommandResponse)
-> Free f (Either ArtistError UpsertArtistOpinionsCommandResponse))
-> Free f (Either ArtistError UpsertArtistOpinionsCommandResponse)
-> Free f (Either ArtistError UpsertArtistOpinionsCommandResponse)
forall a b. (a -> b) -> a -> b
$ do
[ArtistOpinion]
newOpinions <- (UpsertArtistOpinionsRequestItem -> Free f ArtistOpinion)
-> [UpsertArtistOpinionsRequestItem] -> Free f [ArtistOpinion]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (UUID -> UpsertArtistOpinionsRequestItem -> Free f ArtistOpinion
forall (f :: * -> *).
(ArtistCommand :<: f) =>
UUID -> UpsertArtistOpinionsRequestItem -> Free f ArtistOpinion
newArtistOpinionFromRequest (WikiMusicUser
authUser WikiMusicUser -> Optic' A_Lens NoIx WikiMusicUser UUID -> UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx WikiMusicUser UUID
#identifier)) (UpsertArtistOpinionsRequest
request UpsertArtistOpinionsRequest
-> Optic'
An_Iso
NoIx
UpsertArtistOpinionsRequest
[UpsertArtistOpinionsRequestItem]
-> [UpsertArtistOpinionsRequestItem]
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic'
An_Iso
NoIx
UpsertArtistOpinionsRequest
[UpsertArtistOpinionsRequestItem]
#artistOpinions)
let entityValidation :: ArtistOpinion -> (UUID, Validation [Text])
entityValidation ArtistOpinion
x = (ArtistOpinion
x ArtistOpinion -> Optic' A_Lens NoIx ArtistOpinion UUID -> UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx ArtistOpinion UUID
#artistIdentifier, ArtistOpinion -> Validation [Text]
validateArtistOpinion ArtistOpinion
x)
validationResults :: Map Text (Validation [Text])
validationResults = [Item (Map Text (Validation [Text]))]
-> Map Text (Validation [Text])
forall l. IsList l => [Item l] -> l
fromList ([Item (Map Text (Validation [Text]))]
-> Map Text (Validation [Text]))
-> [Item (Map Text (Validation [Text]))]
-> Map Text (Validation [Text])
forall a b. (a -> b) -> a -> b
$ (ArtistOpinion -> (Text, Validation [Text]))
-> [ArtistOpinion] -> [(Text, Validation [Text])]
forall a b. (a -> b) -> [a] -> [b]
map ((UUID -> Text)
-> (UUID, Validation [Text]) -> (Text, Validation [Text])
forall a b c. (a -> b) -> (a, c) -> (b, c)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (String -> Text
pack (String -> Text) -> (UUID -> String) -> UUID -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UUID -> String
forall b a. (Show a, IsString b) => a -> b
Relude.show) ((UUID, Validation [Text]) -> (Text, Validation [Text]))
-> (ArtistOpinion -> (UUID, Validation [Text]))
-> ArtistOpinion
-> (Text, Validation [Text])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ArtistOpinion -> (UUID, Validation [Text])
entityValidation) [ArtistOpinion]
newOpinions
Map Text (Validation [Text])
-> Free f (Either ArtistError UpsertArtistOpinionsCommandResponse)
-> Free f (Either ArtistError UpsertArtistOpinionsCommandResponse)
forall (f :: * -> *) b.
Applicative f =>
Map Text (Validation [Text])
-> f (Either ArtistError b) -> f (Either ArtistError b)
ifAllValid Map Text (Validation [Text])
validationResults (Free f (Either ArtistError UpsertArtistOpinionsCommandResponse)
-> Free f (Either ArtistError UpsertArtistOpinionsCommandResponse))
-> Free f (Either ArtistError UpsertArtistOpinionsCommandResponse)
-> Free f (Either ArtistError UpsertArtistOpinionsCommandResponse)
forall a b. (a -> b) -> a -> b
$ do
Map UUID ArtistOpinion
upsertedOpinions <- Env -> [ArtistOpinion] -> Free f (Map UUID ArtistOpinion)
forall (f :: * -> *).
(ArtistCommand :<: f) =>
Env -> [ArtistOpinion] -> Free f (Map UUID ArtistOpinion)
upsertArtistOpinions Env
env [ArtistOpinion]
newOpinions
Either ArtistError UpsertArtistOpinionsCommandResponse
-> Free f (Either ArtistError UpsertArtistOpinionsCommandResponse)
forall a. a -> Free f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
(Either ArtistError UpsertArtistOpinionsCommandResponse
-> Free f (Either ArtistError UpsertArtistOpinionsCommandResponse))
-> (UpsertArtistOpinionsCommandResponse
-> Either ArtistError UpsertArtistOpinionsCommandResponse)
-> UpsertArtistOpinionsCommandResponse
-> Free f (Either ArtistError UpsertArtistOpinionsCommandResponse)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UpsertArtistOpinionsCommandResponse
-> Either ArtistError UpsertArtistOpinionsCommandResponse
forall a b. b -> Either a b
Right
(UpsertArtistOpinionsCommandResponse
-> Free f (Either ArtistError UpsertArtistOpinionsCommandResponse))
-> UpsertArtistOpinionsCommandResponse
-> Free f (Either ArtistError UpsertArtistOpinionsCommandResponse)
forall a b. (a -> b) -> a -> b
$ UpsertArtistOpinionsCommandResponse
{ $sel:artistOpinions:UpsertArtistOpinionsCommandResponse :: Map UUID ArtistOpinion
artistOpinions = Map UUID ArtistOpinion
upsertedOpinions,
$sel:validationResults:UpsertArtistOpinionsCommandResponse :: Map Text (Validation [Text])
validationResults = Map Text (Validation [Text])
validationResults
}
insertArtistArtworksAction ::
(ArtistCommand :<: f) =>
Env ->
WikiMusicUser ->
InsertArtistArtworksRequest ->
Free f (Either ArtistError InsertArtistArtworksCommandResponse)
insertArtistArtworksAction :: forall (f :: * -> *).
(ArtistCommand :<: f) =>
Env
-> WikiMusicUser
-> InsertArtistArtworksRequest
-> Free f (Either ArtistError InsertArtistArtworksCommandResponse)
insertArtistArtworksAction Env
env WikiMusicUser
authUser InsertArtistArtworksRequest
request =
WikiMusicUser
-> ([UserRole] -> Bool)
-> ArtistError
-> Free f (Either ArtistError InsertArtistArtworksCommandResponse)
-> Free f (Either ArtistError InsertArtistArtworksCommandResponse)
forall (f :: * -> *) p b.
Applicative f =>
WikiMusicUser
-> ([UserRole] -> Bool) -> p -> f (Either p b) -> f (Either p b)
doWithRoles' WikiMusicUser
authUser [UserRole] -> Bool
isAtLeastLowRank ArtistError
AccessUnauthorizedError (Free f (Either ArtistError InsertArtistArtworksCommandResponse)
-> Free f (Either ArtistError InsertArtistArtworksCommandResponse))
-> Free f (Either ArtistError InsertArtistArtworksCommandResponse)
-> Free f (Either ArtistError InsertArtistArtworksCommandResponse)
forall a b. (a -> b) -> a -> b
$ do
[ArtistArtwork]
newArtworks <- (InsertArtistArtworksRequestItem -> Free f ArtistArtwork)
-> [InsertArtistArtworksRequestItem] -> Free f [ArtistArtwork]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (UUID -> InsertArtistArtworksRequestItem -> Free f ArtistArtwork
forall (f :: * -> *).
(ArtistCommand :<: f) =>
UUID -> InsertArtistArtworksRequestItem -> Free f ArtistArtwork
newArtistArtworkFromRequest (WikiMusicUser
authUser WikiMusicUser -> Optic' A_Lens NoIx WikiMusicUser UUID -> UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx WikiMusicUser UUID
#identifier)) (InsertArtistArtworksRequest
request InsertArtistArtworksRequest
-> Optic'
An_Iso
NoIx
InsertArtistArtworksRequest
[InsertArtistArtworksRequestItem]
-> [InsertArtistArtworksRequestItem]
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic'
An_Iso
NoIx
InsertArtistArtworksRequest
[InsertArtistArtworksRequestItem]
#artistArtworks)
let entityValidation :: ArtistArtwork -> (UUID, Validation [Text])
entityValidation ArtistArtwork
x = (ArtistArtwork
x ArtistArtwork -> Optic' A_Lens NoIx ArtistArtwork UUID -> UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx ArtistArtwork UUID
#artistIdentifier, ArtistArtwork -> Validation [Text]
validateArtistArtwork ArtistArtwork
x)
validationResults :: Map Text (Validation [Text])
validationResults = [Item (Map Text (Validation [Text]))]
-> Map Text (Validation [Text])
forall l. IsList l => [Item l] -> l
fromList ([Item (Map Text (Validation [Text]))]
-> Map Text (Validation [Text]))
-> [Item (Map Text (Validation [Text]))]
-> Map Text (Validation [Text])
forall a b. (a -> b) -> a -> b
$ (ArtistArtwork -> (Text, Validation [Text]))
-> [ArtistArtwork] -> [(Text, Validation [Text])]
forall a b. (a -> b) -> [a] -> [b]
map ((UUID -> Text)
-> (UUID, Validation [Text]) -> (Text, Validation [Text])
forall a b c. (a -> b) -> (a, c) -> (b, c)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (String -> Text
pack (String -> Text) -> (UUID -> String) -> UUID -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UUID -> String
forall b a. (Show a, IsString b) => a -> b
Relude.show) ((UUID, Validation [Text]) -> (Text, Validation [Text]))
-> (ArtistArtwork -> (UUID, Validation [Text]))
-> ArtistArtwork
-> (Text, Validation [Text])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ArtistArtwork -> (UUID, Validation [Text])
entityValidation) [ArtistArtwork]
newArtworks
Map Text (Validation [Text])
-> Free f (Either ArtistError InsertArtistArtworksCommandResponse)
-> Free f (Either ArtistError InsertArtistArtworksCommandResponse)
forall (f :: * -> *) b.
Applicative f =>
Map Text (Validation [Text])
-> f (Either ArtistError b) -> f (Either ArtistError b)
ifAllValid Map Text (Validation [Text])
validationResults (Free f (Either ArtistError InsertArtistArtworksCommandResponse)
-> Free f (Either ArtistError InsertArtistArtworksCommandResponse))
-> Free f (Either ArtistError InsertArtistArtworksCommandResponse)
-> Free f (Either ArtistError InsertArtistArtworksCommandResponse)
forall a b. (a -> b) -> a -> b
$ do
Map UUID ArtistArtwork
insertedArtworks <- Env -> [ArtistArtwork] -> Free f (Map UUID ArtistArtwork)
forall (f :: * -> *).
(ArtistCommand :<: f) =>
Env -> [ArtistArtwork] -> Free f (Map UUID ArtistArtwork)
insertArtistArtworks Env
env [ArtistArtwork]
newArtworks
Either ArtistError InsertArtistArtworksCommandResponse
-> Free f (Either ArtistError InsertArtistArtworksCommandResponse)
forall a. a -> Free f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
(Either ArtistError InsertArtistArtworksCommandResponse
-> Free f (Either ArtistError InsertArtistArtworksCommandResponse))
-> (InsertArtistArtworksCommandResponse
-> Either ArtistError InsertArtistArtworksCommandResponse)
-> InsertArtistArtworksCommandResponse
-> Free f (Either ArtistError InsertArtistArtworksCommandResponse)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InsertArtistArtworksCommandResponse
-> Either ArtistError InsertArtistArtworksCommandResponse
forall a b. b -> Either a b
Right
(InsertArtistArtworksCommandResponse
-> Free f (Either ArtistError InsertArtistArtworksCommandResponse))
-> InsertArtistArtworksCommandResponse
-> Free f (Either ArtistError InsertArtistArtworksCommandResponse)
forall a b. (a -> b) -> a -> b
$ InsertArtistArtworksCommandResponse
{ $sel:artistArtworks:InsertArtistArtworksCommandResponse :: Map UUID ArtistArtwork
artistArtworks = Map UUID ArtistArtwork
insertedArtworks,
$sel:validationResults:InsertArtistArtworksCommandResponse :: Map Text (Validation [Text])
validationResults = Map Text (Validation [Text])
validationResults
}
deleteArtistsByIdentifierAction ::
(ArtistCommand :<: f) =>
Env ->
WikiMusicUser ->
UUID ->
Free f (Either ArtistError ())
deleteArtistsByIdentifierAction :: forall (f :: * -> *).
(ArtistCommand :<: f) =>
Env -> WikiMusicUser -> UUID -> Free f (Either ArtistError ())
deleteArtistsByIdentifierAction Env
env WikiMusicUser
authUser UUID
identifier =
WikiMusicUser
-> ([UserRole] -> Bool)
-> ArtistError
-> Free f (Either ArtistError ())
-> Free f (Either ArtistError ())
forall (f :: * -> *) p b.
Applicative f =>
WikiMusicUser
-> ([UserRole] -> Bool) -> p -> f (Either p b) -> f (Either p b)
doWithRoles' WikiMusicUser
authUser [UserRole] -> Bool
isAtLeastMaintainer ArtistError
AccessUnauthorizedError (Free f (Either ArtistError ()) -> Free f (Either ArtistError ()))
-> Free f (Either ArtistError ()) -> Free f (Either ArtistError ())
forall a b. (a -> b) -> a -> b
$ do
Either ArtistCommandError ()
operationResults <- Env -> [UUID] -> Free f (Either ArtistCommandError ())
forall (f :: * -> *).
(ArtistCommand :<: f) =>
Env -> [UUID] -> Free f (Either ArtistCommandError ())
deleteArtists Env
env [UUID
identifier]
Either ArtistError () -> Free f (Either ArtistError ())
forall a. a -> Free f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either ArtistError () -> Free f (Either ArtistError ()))
-> (Either ArtistCommandError () -> Either ArtistError ())
-> Either ArtistCommandError ()
-> Free f (Either ArtistError ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ArtistCommandError -> ArtistError)
-> Either ArtistCommandError () -> Either ArtistError ()
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 (Text -> ArtistError
SomeError (Text -> ArtistError)
-> (ArtistCommandError -> Text)
-> ArtistCommandError
-> ArtistError
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
pack (String -> Text)
-> (ArtistCommandError -> String) -> ArtistCommandError -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ArtistCommandError -> String
forall b a. (Show a, IsString b) => a -> b
Relude.show) (Either ArtistCommandError () -> Free f (Either ArtistError ()))
-> Either ArtistCommandError () -> Free f (Either ArtistError ())
forall a b. (a -> b) -> a -> b
$ Either ArtistCommandError ()
operationResults
deleteArtistCommentsByIdentifierAction ::
(ArtistCommand :<: f) =>
Env ->
WikiMusicUser ->
UUID ->
Free f (Either ArtistError ())
Env
env WikiMusicUser
authUser UUID
identifier =
WikiMusicUser
-> ([UserRole] -> Bool)
-> ArtistError
-> Free f (Either ArtistError ())
-> Free f (Either ArtistError ())
forall (f :: * -> *) p b.
Applicative f =>
WikiMusicUser
-> ([UserRole] -> Bool) -> p -> f (Either p b) -> f (Either p b)
doWithRoles' WikiMusicUser
authUser [UserRole] -> Bool
isAtLeastMaintainer ArtistError
AccessUnauthorizedError (Free f (Either ArtistError ()) -> Free f (Either ArtistError ()))
-> Free f (Either ArtistError ()) -> Free f (Either ArtistError ())
forall a b. (a -> b) -> a -> b
$ do
Either ArtistCommandError ()
operationResults <- Env -> [UUID] -> Free f (Either ArtistCommandError ())
forall (f :: * -> *).
(ArtistCommand :<: f) =>
Env -> [UUID] -> Free f (Either ArtistCommandError ())
deleteArtistComments Env
env [UUID
identifier]
Either ArtistError () -> Free f (Either ArtistError ())
forall a. a -> Free f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either ArtistError () -> Free f (Either ArtistError ()))
-> (Either ArtistCommandError () -> Either ArtistError ())
-> Either ArtistCommandError ()
-> Free f (Either ArtistError ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ArtistCommandError -> ArtistError)
-> Either ArtistCommandError () -> Either ArtistError ()
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 (Text -> ArtistError
SomeError (Text -> ArtistError)
-> (ArtistCommandError -> Text)
-> ArtistCommandError
-> ArtistError
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
pack (String -> Text)
-> (ArtistCommandError -> String) -> ArtistCommandError -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ArtistCommandError -> String
forall b a. (Show a, IsString b) => a -> b
Relude.show) (Either ArtistCommandError () -> Free f (Either ArtistError ()))
-> Either ArtistCommandError () -> Free f (Either ArtistError ())
forall a b. (a -> b) -> a -> b
$ Either ArtistCommandError ()
operationResults
deleteArtistOpinionsByIdentifierAction ::
(ArtistCommand :<: f) =>
Env ->
WikiMusicUser ->
UUID ->
Free f (Either ArtistError ())
deleteArtistOpinionsByIdentifierAction :: forall (f :: * -> *).
(ArtistCommand :<: f) =>
Env -> WikiMusicUser -> UUID -> Free f (Either ArtistError ())
deleteArtistOpinionsByIdentifierAction Env
env WikiMusicUser
authUser UUID
identifier =
WikiMusicUser
-> ([UserRole] -> Bool)
-> ArtistError
-> Free f (Either ArtistError ())
-> Free f (Either ArtistError ())
forall (f :: * -> *) p b.
Applicative f =>
WikiMusicUser
-> ([UserRole] -> Bool) -> p -> f (Either p b) -> f (Either p b)
doWithRoles' WikiMusicUser
authUser [UserRole] -> Bool
isAtLeastMaintainer ArtistError
AccessUnauthorizedError (Free f (Either ArtistError ()) -> Free f (Either ArtistError ()))
-> Free f (Either ArtistError ()) -> Free f (Either ArtistError ())
forall a b. (a -> b) -> a -> b
$ do
Either ArtistCommandError ()
operationResults <- Env -> [UUID] -> Free f (Either ArtistCommandError ())
forall (f :: * -> *).
(ArtistCommand :<: f) =>
Env -> [UUID] -> Free f (Either ArtistCommandError ())
deleteArtistOpinions Env
env [UUID
identifier]
Either ArtistError () -> Free f (Either ArtistError ())
forall a. a -> Free f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either ArtistError () -> Free f (Either ArtistError ()))
-> (Either ArtistCommandError () -> Either ArtistError ())
-> Either ArtistCommandError ()
-> Free f (Either ArtistError ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ArtistCommandError -> ArtistError)
-> Either ArtistCommandError () -> Either ArtistError ()
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 (Text -> ArtistError
SomeError (Text -> ArtistError)
-> (ArtistCommandError -> Text)
-> ArtistCommandError
-> ArtistError
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
pack (String -> Text)
-> (ArtistCommandError -> String) -> ArtistCommandError -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ArtistCommandError -> String
forall b a. (Show a, IsString b) => a -> b
Relude.show) (Either ArtistCommandError () -> Free f (Either ArtistError ()))
-> Either ArtistCommandError () -> Free f (Either ArtistError ())
forall a b. (a -> b) -> a -> b
$ Either ArtistCommandError ()
operationResults
deleteArtistArtworksByIdentifierAction ::
(ArtistCommand :<: f) =>
Env ->
WikiMusicUser ->
UUID ->
Free f (Either ArtistError ())
deleteArtistArtworksByIdentifierAction :: forall (f :: * -> *).
(ArtistCommand :<: f) =>
Env -> WikiMusicUser -> UUID -> Free f (Either ArtistError ())
deleteArtistArtworksByIdentifierAction Env
env WikiMusicUser
authUser UUID
identifier =
WikiMusicUser
-> ([UserRole] -> Bool)
-> ArtistError
-> Free f (Either ArtistError ())
-> Free f (Either ArtistError ())
forall (f :: * -> *) p b.
Applicative f =>
WikiMusicUser
-> ([UserRole] -> Bool) -> p -> f (Either p b) -> f (Either p b)
doWithRoles' WikiMusicUser
authUser [UserRole] -> Bool
isAtLeastMaintainer ArtistError
AccessUnauthorizedError (Free f (Either ArtistError ()) -> Free f (Either ArtistError ()))
-> Free f (Either ArtistError ()) -> Free f (Either ArtistError ())
forall a b. (a -> b) -> a -> b
$ do
Either ArtistCommandError ()
operationResults <- Env -> [UUID] -> Free f (Either ArtistCommandError ())
forall (f :: * -> *).
(ArtistCommand :<: f) =>
Env -> [UUID] -> Free f (Either ArtistCommandError ())
deleteArtistArtworks Env
env [UUID
identifier]
Either ArtistError () -> Free f (Either ArtistError ())
forall a. a -> Free f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either ArtistError () -> Free f (Either ArtistError ()))
-> (Either ArtistCommandError () -> Either ArtistError ())
-> Either ArtistCommandError ()
-> Free f (Either ArtistError ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ArtistCommandError -> ArtistError)
-> Either ArtistCommandError () -> Either ArtistError ()
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 (Text -> ArtistError
SomeError (Text -> ArtistError)
-> (ArtistCommandError -> Text)
-> ArtistCommandError
-> ArtistError
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
pack (String -> Text)
-> (ArtistCommandError -> String) -> ArtistCommandError -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ArtistCommandError -> String
forall b a. (Show a, IsString b) => a -> b
Relude.show) (Either ArtistCommandError () -> Free f (Either ArtistError ()))
-> Either ArtistCommandError () -> Free f (Either ArtistError ())
forall a b. (a -> b) -> a -> b
$ Either ArtistCommandError ()
operationResults
updateArtistArtworksOrderAction ::
(ArtistCommand :<: f) =>
Env ->
WikiMusicUser ->
ArtistArtworkOrderUpdateRequest ->
Free f (Either ArtistError ())
updateArtistArtworksOrderAction :: forall (f :: * -> *).
(ArtistCommand :<: f) =>
Env
-> WikiMusicUser
-> ArtistArtworkOrderUpdateRequest
-> Free f (Either ArtistError ())
updateArtistArtworksOrderAction Env
env WikiMusicUser
authUser ArtistArtworkOrderUpdateRequest
request =
WikiMusicUser
-> ([UserRole] -> Bool)
-> ArtistError
-> Free f (Either ArtistError ())
-> Free f (Either ArtistError ())
forall (f :: * -> *) p b.
Applicative f =>
WikiMusicUser
-> ([UserRole] -> Bool) -> p -> f (Either p b) -> f (Either p b)
doWithRoles' WikiMusicUser
authUser [UserRole] -> Bool
isAtLeastLowRank ArtistError
AccessUnauthorizedError (Free f (Either ArtistError ()) -> Free f (Either ArtistError ()))
-> Free f (Either ArtistError ()) -> Free f (Either ArtistError ())
forall a b. (a -> b) -> a -> b
$ do
let artistArtworkOrderUpdates :: [ArtistArtworkOrderUpdate]
artistArtworkOrderUpdates = ArtistArtworkOrderUpdateRequest
request ArtistArtworkOrderUpdateRequest
-> Optic'
An_Iso
NoIx
ArtistArtworkOrderUpdateRequest
[ArtistArtworkOrderUpdate]
-> [ArtistArtworkOrderUpdate]
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic'
An_Iso
NoIx
ArtistArtworkOrderUpdateRequest
[ArtistArtworkOrderUpdate]
#artistArtworkOrders
entityValidation :: ArtistArtworkOrderUpdate -> (UUID, Validation [Text])
entityValidation ArtistArtworkOrderUpdate
x = (ArtistArtworkOrderUpdate
x ArtistArtworkOrderUpdate
-> Optic' A_Lens NoIx ArtistArtworkOrderUpdate UUID -> UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx ArtistArtworkOrderUpdate UUID
#identifier, ArtistArtworkOrderUpdate -> Validation [Text]
validateArtistArtworkOrderUpdate ArtistArtworkOrderUpdate
x)
validationResults :: Map Text (Validation [Text])
validationResults =
[Item (Map Text (Validation [Text]))]
-> Map Text (Validation [Text])
forall l. IsList l => [Item l] -> l
fromList
([Item (Map Text (Validation [Text]))]
-> Map Text (Validation [Text]))
-> [Item (Map Text (Validation [Text]))]
-> Map Text (Validation [Text])
forall a b. (a -> b) -> a -> b
$ (ArtistArtworkOrderUpdate -> (Text, Validation [Text]))
-> [ArtistArtworkOrderUpdate] -> [(Text, Validation [Text])]
forall a b. (a -> b) -> [a] -> [b]
map ((UUID -> Text)
-> (UUID, Validation [Text]) -> (Text, Validation [Text])
forall a b c. (a -> b) -> (a, c) -> (b, c)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (String -> Text
pack (String -> Text) -> (UUID -> String) -> UUID -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UUID -> String
forall b a. (Show a, IsString b) => a -> b
Relude.show) ((UUID, Validation [Text]) -> (Text, Validation [Text]))
-> (ArtistArtworkOrderUpdate -> (UUID, Validation [Text]))
-> ArtistArtworkOrderUpdate
-> (Text, Validation [Text])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ArtistArtworkOrderUpdate -> (UUID, Validation [Text])
entityValidation) [ArtistArtworkOrderUpdate]
artistArtworkOrderUpdates
Map Text (Validation [Text])
-> Free f (Either ArtistError ()) -> Free f (Either ArtistError ())
forall (f :: * -> *) b.
Applicative f =>
Map Text (Validation [Text])
-> f (Either ArtistError b) -> f (Either ArtistError b)
ifAllValid Map Text (Validation [Text])
validationResults (Free f (Either ArtistError ()) -> Free f (Either ArtistError ()))
-> Free f (Either ArtistError ()) -> Free f (Either ArtistError ())
forall a b. (a -> b) -> a -> b
$ do
Either Text ()
operationResults <- Env -> [ArtistArtworkOrderUpdate] -> Free f (Either Text ())
forall (f :: * -> *).
(ArtistCommand :<: f) =>
Env -> [ArtistArtworkOrderUpdate] -> Free f (Either Text ())
updateArtistArtworkOrder Env
env [ArtistArtworkOrderUpdate]
artistArtworkOrderUpdates
Either ArtistError () -> Free f (Either ArtistError ())
forall a. a -> Free f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either ArtistError () -> Free f (Either ArtistError ()))
-> (Either Text () -> Either ArtistError ())
-> Either Text ()
-> Free f (Either ArtistError ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> ArtistError) -> Either Text () -> Either ArtistError ()
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 Text -> ArtistError
SomeError (Either Text () -> Free f (Either ArtistError ()))
-> Either Text () -> Free f (Either ArtistError ())
forall a b. (a -> b) -> a -> b
$ Either Text ()
operationResults
updateArtistAction ::
(ArtistCommand :<: f, ArtistQuery :<: f) =>
Env ->
WikiMusicUser ->
ArtistDeltaRequest ->
Free f (Either ArtistError ())
updateArtistAction :: forall (f :: * -> *).
(ArtistCommand :<: f, ArtistQuery :<: f) =>
Env
-> WikiMusicUser
-> ArtistDeltaRequest
-> Free f (Either ArtistError ())
updateArtistAction Env
env WikiMusicUser
authUser ArtistDeltaRequest
request =
WikiMusicUser
-> ([UserRole] -> Bool)
-> ArtistError
-> Free f (Either ArtistError ())
-> Free f (Either ArtistError ())
forall (f :: * -> *) p b.
Applicative f =>
WikiMusicUser
-> ([UserRole] -> Bool) -> p -> f (Either p b) -> f (Either p b)
doWithRoles' WikiMusicUser
authUser [UserRole] -> Bool
isAtLeastLowRank ArtistError
AccessUnauthorizedError (Free f (Either ArtistError ()) -> Free f (Either ArtistError ()))
-> Free f (Either ArtistError ()) -> Free f (Either ArtistError ())
forall a b. (a -> b) -> a -> b
$ do
let entityValidation :: ArtistDelta -> (UUID, Validation [Text])
entityValidation ArtistDelta
x = (ArtistDelta
x ArtistDelta -> Optic' A_Lens NoIx ArtistDelta UUID -> UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx ArtistDelta UUID
#identifier, ArtistDelta -> Validation [Text]
validateArtistDelta ArtistDelta
x)
deltas :: [ArtistDelta]
deltas = ArtistDeltaRequest
request ArtistDeltaRequest
-> Optic' An_Iso NoIx ArtistDeltaRequest [ArtistDelta]
-> [ArtistDelta]
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' An_Iso NoIx ArtistDeltaRequest [ArtistDelta]
#artistDeltas
validationResults :: Map Text (Validation [Text])
validationResults = [(Text, Validation [Text])] -> Map Text (Validation [Text])
[Item (Map Text (Validation [Text]))]
-> Map Text (Validation [Text])
forall l. IsList l => [Item l] -> l
fromList ([(Text, Validation [Text])] -> Map Text (Validation [Text]))
-> ([ArtistDelta] -> [(Text, Validation [Text])])
-> [ArtistDelta]
-> Map Text (Validation [Text])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ArtistDelta -> (Text, Validation [Text]))
-> [ArtistDelta] -> [(Text, Validation [Text])]
forall a b. (a -> b) -> [a] -> [b]
map ((UUID -> Text)
-> (UUID, Validation [Text]) -> (Text, Validation [Text])
forall a b c. (a -> b) -> (a, c) -> (b, c)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (String -> Text
pack (String -> Text) -> (UUID -> String) -> UUID -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UUID -> String
forall b a. (Show a, IsString b) => a -> b
Relude.show) ((UUID, Validation [Text]) -> (Text, Validation [Text]))
-> (ArtistDelta -> (UUID, Validation [Text]))
-> ArtistDelta
-> (Text, Validation [Text])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ArtistDelta -> (UUID, Validation [Text])
entityValidation) ([ArtistDelta] -> Map Text (Validation [Text]))
-> [ArtistDelta] -> Map Text (Validation [Text])
forall a b. (a -> b) -> a -> b
$ [ArtistDelta]
deltas
Map Text (Validation [Text])
-> Free f (Either ArtistError ()) -> Free f (Either ArtistError ())
forall (f :: * -> *) b.
Applicative f =>
Map Text (Validation [Text])
-> f (Either ArtistError b) -> f (Either ArtistError b)
ifAllValid Map Text (Validation [Text])
validationResults (Free f (Either ArtistError ()) -> Free f (Either ArtistError ()))
-> Free f (Either ArtistError ()) -> Free f (Either ArtistError ())
forall a b. (a -> b) -> a -> b
$ do
let artistIds :: [UUID]
artistIds = (ArtistDelta -> UUID) -> [ArtistDelta] -> [UUID]
forall a b. (a -> b) -> [a] -> [b]
map (ArtistDelta -> Optic' A_Lens NoIx ArtistDelta UUID -> UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx ArtistDelta UUID
#identifier) [ArtistDelta]
deltas
deltaMap :: Map UUID ArtistDelta
deltaMap = [Item (Map UUID ArtistDelta)] -> Map UUID ArtistDelta
forall l. IsList l => [Item l] -> l
fromList ([Item (Map UUID ArtistDelta)] -> Map UUID ArtistDelta)
-> [Item (Map UUID ArtistDelta)] -> Map UUID ArtistDelta
forall a b. (a -> b) -> a -> b
$ (ArtistDelta -> (UUID, ArtistDelta))
-> [ArtistDelta] -> [(UUID, ArtistDelta)]
forall a b. (a -> b) -> [a] -> [b]
map (\ArtistDelta
x -> (ArtistDelta
x ArtistDelta -> Optic' A_Lens NoIx ArtistDelta UUID -> UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx ArtistDelta UUID
#identifier, ArtistDelta
x)) [ArtistDelta]
deltas
Map UUID Artist
artistRecords <- (Map UUID Artist, [UUID]) -> Map UUID Artist
forall a b. (a, b) -> a
fst ((Map UUID Artist, [UUID]) -> Map UUID Artist)
-> Free f (Map UUID Artist, [UUID]) -> Free f (Map UUID Artist)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Env
-> ArtistSortOrder -> [UUID] -> Free f (Map UUID Artist, [UUID])
forall (f :: * -> *).
(ArtistQuery :<: f) =>
Env
-> ArtistSortOrder -> [UUID] -> Free f (Map UUID Artist, [UUID])
fetchArtistsByUUID Env
env ArtistSortOrder
DescCreatedAt [UUID]
artistIds
let artistRecordAndDeltaPairMap :: Map UUID (Artist, Maybe ArtistDelta)
artistRecordAndDeltaPairMap = (UUID -> Artist -> (Artist, Maybe ArtistDelta))
-> Map UUID Artist -> Map UUID (Artist, Maybe ArtistDelta)
forall k a b. (k -> a -> b) -> Map k a -> Map k b
Map.mapWithKey (\UUID
k Artist
v -> (Artist
v, Map UUID ArtistDelta
deltaMap Map UUID ArtistDelta -> UUID -> Maybe ArtistDelta
forall k a. Ord k => Map k a -> k -> Maybe a
Map.!? UUID
k)) Map UUID Artist
artistRecords
Either Text ()
operationResults <- Env
-> Map UUID (Artist, Maybe ArtistDelta) -> Free f (Either Text ())
forall (f :: * -> *).
(ArtistCommand :<: f) =>
Env
-> Map UUID (Artist, Maybe ArtistDelta) -> Free f (Either Text ())
updateArtists Env
env Map UUID (Artist, Maybe ArtistDelta)
artistRecordAndDeltaPairMap
Either ArtistError () -> Free f (Either ArtistError ())
forall a. a -> Free f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either ArtistError () -> Free f (Either ArtistError ()))
-> (Either Text () -> Either ArtistError ())
-> Either Text ()
-> Free f (Either ArtistError ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> ArtistError) -> Either Text () -> Either ArtistError ()
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 Text -> ArtistError
SomeError (Either Text () -> Free f (Either ArtistError ()))
-> Either Text () -> Free f (Either ArtistError ())
forall a b. (a -> b) -> a -> b
$ Either Text ()
operationResults