{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE NoFieldSelectors #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module WikiMusic.Interaction.Model.Song
  ( Song (..),
    SongArtworkOrderUpdateRequest (..),
    SongArtwork (..),
    SongComment (..),
    SongOpinion (..),
    GetSongsQueryResponse (..),
    InsertSongsCommandResponse (..),
    InsertSongsRequest (..),
    InsertSongsRequestItem (..),
    InsertSongCommentsCommandResponse (..),
    InsertSongCommentsRequest (..),
    InsertSongCommentsRequestItem (..),
    UpsertSongOpinionsCommandResponse (..),
    UpsertSongOpinionsRequest (..),
    UpsertSongOpinionsRequestItem (..),
    InsertSongArtworksCommandResponse (..),
    InsertSongArtworksRequest (..),
    InsertSongArtworksRequestItem (..),
    parseInclude,
    InsertArtistsOfSongsRequest (..),
    InsertArtistsOfSongsRequestItem (..),
    InsertArtistsOfSongCommandResponse (..),
    SongDeltaRequest (..),
    ifAllValid,
    SongError (..),
    SongContentDeltaRequest (..),
    InsertSongContentsRequestItem (..),
    InsertSongContentsRequest (..),
    InsertSongContentsCommandResponse (..),
  )
where
import Data.Aeson hiding (Success)
import Data.OpenApi
import Data.UUID hiding (null)
import Keuringsdienst
import Keuringsdienst.Helpers
import Optics
import Relude
import WikiMusic.Model.Song
instance ToSchema (Validation [Text])
data GetSongsQueryResponse = GetSongsQueryResponse
  { GetSongsQueryResponse -> Map UUID Song
songs :: Map UUID Song,
    GetSongsQueryResponse -> [UUID]
sortOrder :: [UUID]
  }
  deriving (GetSongsQueryResponse -> GetSongsQueryResponse -> Bool
(GetSongsQueryResponse -> GetSongsQueryResponse -> Bool)
-> (GetSongsQueryResponse -> GetSongsQueryResponse -> Bool)
-> Eq GetSongsQueryResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GetSongsQueryResponse -> GetSongsQueryResponse -> Bool
== :: GetSongsQueryResponse -> GetSongsQueryResponse -> Bool
$c/= :: GetSongsQueryResponse -> GetSongsQueryResponse -> Bool
/= :: GetSongsQueryResponse -> GetSongsQueryResponse -> Bool
Eq, Int -> GetSongsQueryResponse -> ShowS
[GetSongsQueryResponse] -> ShowS
GetSongsQueryResponse -> String
(Int -> GetSongsQueryResponse -> ShowS)
-> (GetSongsQueryResponse -> String)
-> ([GetSongsQueryResponse] -> ShowS)
-> Show GetSongsQueryResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GetSongsQueryResponse -> ShowS
showsPrec :: Int -> GetSongsQueryResponse -> ShowS
$cshow :: GetSongsQueryResponse -> String
show :: GetSongsQueryResponse -> String
$cshowList :: [GetSongsQueryResponse] -> ShowS
showList :: [GetSongsQueryResponse] -> ShowS
Show, (forall x. GetSongsQueryResponse -> Rep GetSongsQueryResponse x)
-> (forall x. Rep GetSongsQueryResponse x -> GetSongsQueryResponse)
-> Generic GetSongsQueryResponse
forall x. Rep GetSongsQueryResponse x -> GetSongsQueryResponse
forall x. GetSongsQueryResponse -> Rep GetSongsQueryResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GetSongsQueryResponse -> Rep GetSongsQueryResponse x
from :: forall x. GetSongsQueryResponse -> Rep GetSongsQueryResponse x
$cto :: forall x. Rep GetSongsQueryResponse x -> GetSongsQueryResponse
to :: forall x. Rep GetSongsQueryResponse x -> GetSongsQueryResponse
Generic, Maybe GetSongsQueryResponse
Value -> Parser [GetSongsQueryResponse]
Value -> Parser GetSongsQueryResponse
(Value -> Parser GetSongsQueryResponse)
-> (Value -> Parser [GetSongsQueryResponse])
-> Maybe GetSongsQueryResponse
-> FromJSON GetSongsQueryResponse
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser GetSongsQueryResponse
parseJSON :: Value -> Parser GetSongsQueryResponse
$cparseJSONList :: Value -> Parser [GetSongsQueryResponse]
parseJSONList :: Value -> Parser [GetSongsQueryResponse]
$comittedField :: Maybe GetSongsQueryResponse
omittedField :: Maybe GetSongsQueryResponse
FromJSON, [GetSongsQueryResponse] -> Value
[GetSongsQueryResponse] -> Encoding
GetSongsQueryResponse -> Bool
GetSongsQueryResponse -> Value
GetSongsQueryResponse -> Encoding
(GetSongsQueryResponse -> Value)
-> (GetSongsQueryResponse -> Encoding)
-> ([GetSongsQueryResponse] -> Value)
-> ([GetSongsQueryResponse] -> Encoding)
-> (GetSongsQueryResponse -> Bool)
-> ToJSON GetSongsQueryResponse
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: GetSongsQueryResponse -> Value
toJSON :: GetSongsQueryResponse -> Value
$ctoEncoding :: GetSongsQueryResponse -> Encoding
toEncoding :: GetSongsQueryResponse -> Encoding
$ctoJSONList :: [GetSongsQueryResponse] -> Value
toJSONList :: [GetSongsQueryResponse] -> Value
$ctoEncodingList :: [GetSongsQueryResponse] -> Encoding
toEncodingList :: [GetSongsQueryResponse] -> Encoding
$comitField :: GetSongsQueryResponse -> Bool
omitField :: GetSongsQueryResponse -> Bool
ToJSON, Typeable GetSongsQueryResponse
Typeable GetSongsQueryResponse =>
(Proxy GetSongsQueryResponse
 -> Declare (Definitions Schema) NamedSchema)
-> ToSchema GetSongsQueryResponse
Proxy GetSongsQueryResponse
-> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy GetSongsQueryResponse
-> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy GetSongsQueryResponse
-> Declare (Definitions Schema) NamedSchema
ToSchema)
makeFieldLabelsNoPrefix ''GetSongsQueryResponse
data InsertSongsCommandResponse = InsertSongsQueryResponse
  { InsertSongsCommandResponse -> Map UUID Song
songs :: Map UUID Song,
    InsertSongsCommandResponse -> [UUID]
sortOrder :: [UUID],
    InsertSongsCommandResponse -> Map Text (Validation [Text])
validationResults :: Map Text ValidationResult
  }
  deriving (InsertSongsCommandResponse -> InsertSongsCommandResponse -> Bool
(InsertSongsCommandResponse -> InsertSongsCommandResponse -> Bool)
-> (InsertSongsCommandResponse
    -> InsertSongsCommandResponse -> Bool)
-> Eq InsertSongsCommandResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InsertSongsCommandResponse -> InsertSongsCommandResponse -> Bool
== :: InsertSongsCommandResponse -> InsertSongsCommandResponse -> Bool
$c/= :: InsertSongsCommandResponse -> InsertSongsCommandResponse -> Bool
/= :: InsertSongsCommandResponse -> InsertSongsCommandResponse -> Bool
Eq, Int -> InsertSongsCommandResponse -> ShowS
[InsertSongsCommandResponse] -> ShowS
InsertSongsCommandResponse -> String
(Int -> InsertSongsCommandResponse -> ShowS)
-> (InsertSongsCommandResponse -> String)
-> ([InsertSongsCommandResponse] -> ShowS)
-> Show InsertSongsCommandResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InsertSongsCommandResponse -> ShowS
showsPrec :: Int -> InsertSongsCommandResponse -> ShowS
$cshow :: InsertSongsCommandResponse -> String
show :: InsertSongsCommandResponse -> String
$cshowList :: [InsertSongsCommandResponse] -> ShowS
showList :: [InsertSongsCommandResponse] -> ShowS
Show, (forall x.
 InsertSongsCommandResponse -> Rep InsertSongsCommandResponse x)
-> (forall x.
    Rep InsertSongsCommandResponse x -> InsertSongsCommandResponse)
-> Generic InsertSongsCommandResponse
forall x.
Rep InsertSongsCommandResponse x -> InsertSongsCommandResponse
forall x.
InsertSongsCommandResponse -> Rep InsertSongsCommandResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
InsertSongsCommandResponse -> Rep InsertSongsCommandResponse x
from :: forall x.
InsertSongsCommandResponse -> Rep InsertSongsCommandResponse x
$cto :: forall x.
Rep InsertSongsCommandResponse x -> InsertSongsCommandResponse
to :: forall x.
Rep InsertSongsCommandResponse x -> InsertSongsCommandResponse
Generic, Maybe InsertSongsCommandResponse
Value -> Parser [InsertSongsCommandResponse]
Value -> Parser InsertSongsCommandResponse
(Value -> Parser InsertSongsCommandResponse)
-> (Value -> Parser [InsertSongsCommandResponse])
-> Maybe InsertSongsCommandResponse
-> FromJSON InsertSongsCommandResponse
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser InsertSongsCommandResponse
parseJSON :: Value -> Parser InsertSongsCommandResponse
$cparseJSONList :: Value -> Parser [InsertSongsCommandResponse]
parseJSONList :: Value -> Parser [InsertSongsCommandResponse]
$comittedField :: Maybe InsertSongsCommandResponse
omittedField :: Maybe InsertSongsCommandResponse
FromJSON, [InsertSongsCommandResponse] -> Value
[InsertSongsCommandResponse] -> Encoding
InsertSongsCommandResponse -> Bool
InsertSongsCommandResponse -> Value
InsertSongsCommandResponse -> Encoding
(InsertSongsCommandResponse -> Value)
-> (InsertSongsCommandResponse -> Encoding)
-> ([InsertSongsCommandResponse] -> Value)
-> ([InsertSongsCommandResponse] -> Encoding)
-> (InsertSongsCommandResponse -> Bool)
-> ToJSON InsertSongsCommandResponse
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: InsertSongsCommandResponse -> Value
toJSON :: InsertSongsCommandResponse -> Value
$ctoEncoding :: InsertSongsCommandResponse -> Encoding
toEncoding :: InsertSongsCommandResponse -> Encoding
$ctoJSONList :: [InsertSongsCommandResponse] -> Value
toJSONList :: [InsertSongsCommandResponse] -> Value
$ctoEncodingList :: [InsertSongsCommandResponse] -> Encoding
toEncodingList :: [InsertSongsCommandResponse] -> Encoding
$comitField :: InsertSongsCommandResponse -> Bool
omitField :: InsertSongsCommandResponse -> Bool
ToJSON, Typeable InsertSongsCommandResponse
Typeable InsertSongsCommandResponse =>
(Proxy InsertSongsCommandResponse
 -> Declare (Definitions Schema) NamedSchema)
-> ToSchema InsertSongsCommandResponse
Proxy InsertSongsCommandResponse
-> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy InsertSongsCommandResponse
-> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy InsertSongsCommandResponse
-> Declare (Definitions Schema) NamedSchema
ToSchema)
makeFieldLabelsNoPrefix ''InsertSongsCommandResponse
data InsertSongsRequestItem = InsertSongsRequestItem
  { InsertSongsRequestItem -> Text
displayName :: Text,
    InsertSongsRequestItem -> Maybe Text
musicKey :: Maybe Text,
    InsertSongsRequestItem -> Maybe Text
musicTuning :: Maybe Text,
    InsertSongsRequestItem -> Maybe Text
musicCreationDate :: Maybe Text,
    InsertSongsRequestItem -> Maybe Text
albumName :: Maybe Text,
    InsertSongsRequestItem -> Maybe Text
albumInfoLink :: Maybe Text,
    InsertSongsRequestItem -> Maybe Text
spotifyUrl :: Maybe Text,
    InsertSongsRequestItem -> Maybe Text
youtubeUrl :: Maybe Text,
    InsertSongsRequestItem -> Maybe Text
soundcloudUrl :: Maybe Text,
    InsertSongsRequestItem -> Maybe Text
wikipediaUrl :: Maybe Text,
    InsertSongsRequestItem -> Maybe Text
description :: Maybe Text
  }
  deriving (InsertSongsRequestItem -> InsertSongsRequestItem -> Bool
(InsertSongsRequestItem -> InsertSongsRequestItem -> Bool)
-> (InsertSongsRequestItem -> InsertSongsRequestItem -> Bool)
-> Eq InsertSongsRequestItem
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InsertSongsRequestItem -> InsertSongsRequestItem -> Bool
== :: InsertSongsRequestItem -> InsertSongsRequestItem -> Bool
$c/= :: InsertSongsRequestItem -> InsertSongsRequestItem -> Bool
/= :: InsertSongsRequestItem -> InsertSongsRequestItem -> Bool
Eq, Int -> InsertSongsRequestItem -> ShowS
[InsertSongsRequestItem] -> ShowS
InsertSongsRequestItem -> String
(Int -> InsertSongsRequestItem -> ShowS)
-> (InsertSongsRequestItem -> String)
-> ([InsertSongsRequestItem] -> ShowS)
-> Show InsertSongsRequestItem
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InsertSongsRequestItem -> ShowS
showsPrec :: Int -> InsertSongsRequestItem -> ShowS
$cshow :: InsertSongsRequestItem -> String
show :: InsertSongsRequestItem -> String
$cshowList :: [InsertSongsRequestItem] -> ShowS
showList :: [InsertSongsRequestItem] -> ShowS
Show, (forall x. InsertSongsRequestItem -> Rep InsertSongsRequestItem x)
-> (forall x.
    Rep InsertSongsRequestItem x -> InsertSongsRequestItem)
-> Generic InsertSongsRequestItem
forall x. Rep InsertSongsRequestItem x -> InsertSongsRequestItem
forall x. InsertSongsRequestItem -> Rep InsertSongsRequestItem x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. InsertSongsRequestItem -> Rep InsertSongsRequestItem x
from :: forall x. InsertSongsRequestItem -> Rep InsertSongsRequestItem x
$cto :: forall x. Rep InsertSongsRequestItem x -> InsertSongsRequestItem
to :: forall x. Rep InsertSongsRequestItem x -> InsertSongsRequestItem
Generic, Maybe InsertSongsRequestItem
Value -> Parser [InsertSongsRequestItem]
Value -> Parser InsertSongsRequestItem
(Value -> Parser InsertSongsRequestItem)
-> (Value -> Parser [InsertSongsRequestItem])
-> Maybe InsertSongsRequestItem
-> FromJSON InsertSongsRequestItem
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser InsertSongsRequestItem
parseJSON :: Value -> Parser InsertSongsRequestItem
$cparseJSONList :: Value -> Parser [InsertSongsRequestItem]
parseJSONList :: Value -> Parser [InsertSongsRequestItem]
$comittedField :: Maybe InsertSongsRequestItem
omittedField :: Maybe InsertSongsRequestItem
FromJSON, [InsertSongsRequestItem] -> Value
[InsertSongsRequestItem] -> Encoding
InsertSongsRequestItem -> Bool
InsertSongsRequestItem -> Value
InsertSongsRequestItem -> Encoding
(InsertSongsRequestItem -> Value)
-> (InsertSongsRequestItem -> Encoding)
-> ([InsertSongsRequestItem] -> Value)
-> ([InsertSongsRequestItem] -> Encoding)
-> (InsertSongsRequestItem -> Bool)
-> ToJSON InsertSongsRequestItem
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: InsertSongsRequestItem -> Value
toJSON :: InsertSongsRequestItem -> Value
$ctoEncoding :: InsertSongsRequestItem -> Encoding
toEncoding :: InsertSongsRequestItem -> Encoding
$ctoJSONList :: [InsertSongsRequestItem] -> Value
toJSONList :: [InsertSongsRequestItem] -> Value
$ctoEncodingList :: [InsertSongsRequestItem] -> Encoding
toEncodingList :: [InsertSongsRequestItem] -> Encoding
$comitField :: InsertSongsRequestItem -> Bool
omitField :: InsertSongsRequestItem -> Bool
ToJSON, Typeable InsertSongsRequestItem
Typeable InsertSongsRequestItem =>
(Proxy InsertSongsRequestItem
 -> Declare (Definitions Schema) NamedSchema)
-> ToSchema InsertSongsRequestItem
Proxy InsertSongsRequestItem
-> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy InsertSongsRequestItem
-> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy InsertSongsRequestItem
-> Declare (Definitions Schema) NamedSchema
ToSchema)
newtype InsertSongsRequest = InsertSongsRequest
  { InsertSongsRequest -> [InsertSongsRequestItem]
songs :: [InsertSongsRequestItem]
  }
  deriving (InsertSongsRequest -> InsertSongsRequest -> Bool
(InsertSongsRequest -> InsertSongsRequest -> Bool)
-> (InsertSongsRequest -> InsertSongsRequest -> Bool)
-> Eq InsertSongsRequest
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InsertSongsRequest -> InsertSongsRequest -> Bool
== :: InsertSongsRequest -> InsertSongsRequest -> Bool
$c/= :: InsertSongsRequest -> InsertSongsRequest -> Bool
/= :: InsertSongsRequest -> InsertSongsRequest -> Bool
Eq, Int -> InsertSongsRequest -> ShowS
[InsertSongsRequest] -> ShowS
InsertSongsRequest -> String
(Int -> InsertSongsRequest -> ShowS)
-> (InsertSongsRequest -> String)
-> ([InsertSongsRequest] -> ShowS)
-> Show InsertSongsRequest
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InsertSongsRequest -> ShowS
showsPrec :: Int -> InsertSongsRequest -> ShowS
$cshow :: InsertSongsRequest -> String
show :: InsertSongsRequest -> String
$cshowList :: [InsertSongsRequest] -> ShowS
showList :: [InsertSongsRequest] -> ShowS
Show, (forall x. InsertSongsRequest -> Rep InsertSongsRequest x)
-> (forall x. Rep InsertSongsRequest x -> InsertSongsRequest)
-> Generic InsertSongsRequest
forall x. Rep InsertSongsRequest x -> InsertSongsRequest
forall x. InsertSongsRequest -> Rep InsertSongsRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. InsertSongsRequest -> Rep InsertSongsRequest x
from :: forall x. InsertSongsRequest -> Rep InsertSongsRequest x
$cto :: forall x. Rep InsertSongsRequest x -> InsertSongsRequest
to :: forall x. Rep InsertSongsRequest x -> InsertSongsRequest
Generic)
  deriving anyclass (Maybe InsertSongsRequest
Value -> Parser [InsertSongsRequest]
Value -> Parser InsertSongsRequest
(Value -> Parser InsertSongsRequest)
-> (Value -> Parser [InsertSongsRequest])
-> Maybe InsertSongsRequest
-> FromJSON InsertSongsRequest
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser InsertSongsRequest
parseJSON :: Value -> Parser InsertSongsRequest
$cparseJSONList :: Value -> Parser [InsertSongsRequest]
parseJSONList :: Value -> Parser [InsertSongsRequest]
$comittedField :: Maybe InsertSongsRequest
omittedField :: Maybe InsertSongsRequest
FromJSON, [InsertSongsRequest] -> Value
[InsertSongsRequest] -> Encoding
InsertSongsRequest -> Bool
InsertSongsRequest -> Value
InsertSongsRequest -> Encoding
(InsertSongsRequest -> Value)
-> (InsertSongsRequest -> Encoding)
-> ([InsertSongsRequest] -> Value)
-> ([InsertSongsRequest] -> Encoding)
-> (InsertSongsRequest -> Bool)
-> ToJSON InsertSongsRequest
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: InsertSongsRequest -> Value
toJSON :: InsertSongsRequest -> Value
$ctoEncoding :: InsertSongsRequest -> Encoding
toEncoding :: InsertSongsRequest -> Encoding
$ctoJSONList :: [InsertSongsRequest] -> Value
toJSONList :: [InsertSongsRequest] -> Value
$ctoEncodingList :: [InsertSongsRequest] -> Encoding
toEncodingList :: [InsertSongsRequest] -> Encoding
$comitField :: InsertSongsRequest -> Bool
omitField :: InsertSongsRequest -> Bool
ToJSON, Typeable InsertSongsRequest
Typeable InsertSongsRequest =>
(Proxy InsertSongsRequest
 -> Declare (Definitions Schema) NamedSchema)
-> ToSchema InsertSongsRequest
Proxy InsertSongsRequest
-> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy InsertSongsRequest
-> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy InsertSongsRequest
-> Declare (Definitions Schema) NamedSchema
ToSchema)
makeFieldLabelsNoPrefix ''InsertSongsRequest
makeFieldLabelsNoPrefix ''InsertSongsRequestItem
data InsertSongCommentsCommandResponse = InsertSongCommentsCommandResponse
  { InsertSongCommentsCommandResponse -> Map UUID SongComment
songComments :: Map UUID SongComment,
    InsertSongCommentsCommandResponse -> Map Text (Validation [Text])
validationResults :: Map Text ValidationResult
  }
  deriving (InsertSongCommentsCommandResponse
-> InsertSongCommentsCommandResponse -> Bool
(InsertSongCommentsCommandResponse
 -> InsertSongCommentsCommandResponse -> Bool)
-> (InsertSongCommentsCommandResponse
    -> InsertSongCommentsCommandResponse -> Bool)
-> Eq InsertSongCommentsCommandResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InsertSongCommentsCommandResponse
-> InsertSongCommentsCommandResponse -> Bool
== :: InsertSongCommentsCommandResponse
-> InsertSongCommentsCommandResponse -> Bool
$c/= :: InsertSongCommentsCommandResponse
-> InsertSongCommentsCommandResponse -> Bool
/= :: InsertSongCommentsCommandResponse
-> InsertSongCommentsCommandResponse -> Bool
Eq, Int -> InsertSongCommentsCommandResponse -> ShowS
[InsertSongCommentsCommandResponse] -> ShowS
InsertSongCommentsCommandResponse -> String
(Int -> InsertSongCommentsCommandResponse -> ShowS)
-> (InsertSongCommentsCommandResponse -> String)
-> ([InsertSongCommentsCommandResponse] -> ShowS)
-> Show InsertSongCommentsCommandResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InsertSongCommentsCommandResponse -> ShowS
showsPrec :: Int -> InsertSongCommentsCommandResponse -> ShowS
$cshow :: InsertSongCommentsCommandResponse -> String
show :: InsertSongCommentsCommandResponse -> String
$cshowList :: [InsertSongCommentsCommandResponse] -> ShowS
showList :: [InsertSongCommentsCommandResponse] -> ShowS
Show, (forall x.
 InsertSongCommentsCommandResponse
 -> Rep InsertSongCommentsCommandResponse x)
-> (forall x.
    Rep InsertSongCommentsCommandResponse x
    -> InsertSongCommentsCommandResponse)
-> Generic InsertSongCommentsCommandResponse
forall x.
Rep InsertSongCommentsCommandResponse x
-> InsertSongCommentsCommandResponse
forall x.
InsertSongCommentsCommandResponse
-> Rep InsertSongCommentsCommandResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
InsertSongCommentsCommandResponse
-> Rep InsertSongCommentsCommandResponse x
from :: forall x.
InsertSongCommentsCommandResponse
-> Rep InsertSongCommentsCommandResponse x
$cto :: forall x.
Rep InsertSongCommentsCommandResponse x
-> InsertSongCommentsCommandResponse
to :: forall x.
Rep InsertSongCommentsCommandResponse x
-> InsertSongCommentsCommandResponse
Generic, Maybe InsertSongCommentsCommandResponse
Value -> Parser [InsertSongCommentsCommandResponse]
Value -> Parser InsertSongCommentsCommandResponse
(Value -> Parser InsertSongCommentsCommandResponse)
-> (Value -> Parser [InsertSongCommentsCommandResponse])
-> Maybe InsertSongCommentsCommandResponse
-> FromJSON InsertSongCommentsCommandResponse
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser InsertSongCommentsCommandResponse
parseJSON :: Value -> Parser InsertSongCommentsCommandResponse
$cparseJSONList :: Value -> Parser [InsertSongCommentsCommandResponse]
parseJSONList :: Value -> Parser [InsertSongCommentsCommandResponse]
$comittedField :: Maybe InsertSongCommentsCommandResponse
omittedField :: Maybe InsertSongCommentsCommandResponse
FromJSON, [InsertSongCommentsCommandResponse] -> Value
[InsertSongCommentsCommandResponse] -> Encoding
InsertSongCommentsCommandResponse -> Bool
InsertSongCommentsCommandResponse -> Value
InsertSongCommentsCommandResponse -> Encoding
(InsertSongCommentsCommandResponse -> Value)
-> (InsertSongCommentsCommandResponse -> Encoding)
-> ([InsertSongCommentsCommandResponse] -> Value)
-> ([InsertSongCommentsCommandResponse] -> Encoding)
-> (InsertSongCommentsCommandResponse -> Bool)
-> ToJSON InsertSongCommentsCommandResponse
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: InsertSongCommentsCommandResponse -> Value
toJSON :: InsertSongCommentsCommandResponse -> Value
$ctoEncoding :: InsertSongCommentsCommandResponse -> Encoding
toEncoding :: InsertSongCommentsCommandResponse -> Encoding
$ctoJSONList :: [InsertSongCommentsCommandResponse] -> Value
toJSONList :: [InsertSongCommentsCommandResponse] -> Value
$ctoEncodingList :: [InsertSongCommentsCommandResponse] -> Encoding
toEncodingList :: [InsertSongCommentsCommandResponse] -> Encoding
$comitField :: InsertSongCommentsCommandResponse -> Bool
omitField :: InsertSongCommentsCommandResponse -> Bool
ToJSON, Typeable InsertSongCommentsCommandResponse
Typeable InsertSongCommentsCommandResponse =>
(Proxy InsertSongCommentsCommandResponse
 -> Declare (Definitions Schema) NamedSchema)
-> ToSchema InsertSongCommentsCommandResponse
Proxy InsertSongCommentsCommandResponse
-> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy InsertSongCommentsCommandResponse
-> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy InsertSongCommentsCommandResponse
-> Declare (Definitions Schema) NamedSchema
ToSchema)
makeFieldLabelsNoPrefix ''InsertSongCommentsCommandResponse
data  = 
  {  :: UUID,
     :: Maybe UUID,
     :: Text
  }
  deriving (InsertSongCommentsRequestItem
-> InsertSongCommentsRequestItem -> Bool
(InsertSongCommentsRequestItem
 -> InsertSongCommentsRequestItem -> Bool)
-> (InsertSongCommentsRequestItem
    -> InsertSongCommentsRequestItem -> Bool)
-> Eq InsertSongCommentsRequestItem
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InsertSongCommentsRequestItem
-> InsertSongCommentsRequestItem -> Bool
== :: InsertSongCommentsRequestItem
-> InsertSongCommentsRequestItem -> Bool
$c/= :: InsertSongCommentsRequestItem
-> InsertSongCommentsRequestItem -> Bool
/= :: InsertSongCommentsRequestItem
-> InsertSongCommentsRequestItem -> Bool
Eq, Int -> InsertSongCommentsRequestItem -> ShowS
[InsertSongCommentsRequestItem] -> ShowS
InsertSongCommentsRequestItem -> String
(Int -> InsertSongCommentsRequestItem -> ShowS)
-> (InsertSongCommentsRequestItem -> String)
-> ([InsertSongCommentsRequestItem] -> ShowS)
-> Show InsertSongCommentsRequestItem
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InsertSongCommentsRequestItem -> ShowS
showsPrec :: Int -> InsertSongCommentsRequestItem -> ShowS
$cshow :: InsertSongCommentsRequestItem -> String
show :: InsertSongCommentsRequestItem -> String
$cshowList :: [InsertSongCommentsRequestItem] -> ShowS
showList :: [InsertSongCommentsRequestItem] -> ShowS
Show, (forall x.
 InsertSongCommentsRequestItem
 -> Rep InsertSongCommentsRequestItem x)
-> (forall x.
    Rep InsertSongCommentsRequestItem x
    -> InsertSongCommentsRequestItem)
-> Generic InsertSongCommentsRequestItem
forall x.
Rep InsertSongCommentsRequestItem x
-> InsertSongCommentsRequestItem
forall x.
InsertSongCommentsRequestItem
-> Rep InsertSongCommentsRequestItem x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
InsertSongCommentsRequestItem
-> Rep InsertSongCommentsRequestItem x
from :: forall x.
InsertSongCommentsRequestItem
-> Rep InsertSongCommentsRequestItem x
$cto :: forall x.
Rep InsertSongCommentsRequestItem x
-> InsertSongCommentsRequestItem
to :: forall x.
Rep InsertSongCommentsRequestItem x
-> InsertSongCommentsRequestItem
Generic, Maybe InsertSongCommentsRequestItem
Value -> Parser [InsertSongCommentsRequestItem]
Value -> Parser InsertSongCommentsRequestItem
(Value -> Parser InsertSongCommentsRequestItem)
-> (Value -> Parser [InsertSongCommentsRequestItem])
-> Maybe InsertSongCommentsRequestItem
-> FromJSON InsertSongCommentsRequestItem
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser InsertSongCommentsRequestItem
parseJSON :: Value -> Parser InsertSongCommentsRequestItem
$cparseJSONList :: Value -> Parser [InsertSongCommentsRequestItem]
parseJSONList :: Value -> Parser [InsertSongCommentsRequestItem]
$comittedField :: Maybe InsertSongCommentsRequestItem
omittedField :: Maybe InsertSongCommentsRequestItem
FromJSON, [InsertSongCommentsRequestItem] -> Value
[InsertSongCommentsRequestItem] -> Encoding
InsertSongCommentsRequestItem -> Bool
InsertSongCommentsRequestItem -> Value
InsertSongCommentsRequestItem -> Encoding
(InsertSongCommentsRequestItem -> Value)
-> (InsertSongCommentsRequestItem -> Encoding)
-> ([InsertSongCommentsRequestItem] -> Value)
-> ([InsertSongCommentsRequestItem] -> Encoding)
-> (InsertSongCommentsRequestItem -> Bool)
-> ToJSON InsertSongCommentsRequestItem
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: InsertSongCommentsRequestItem -> Value
toJSON :: InsertSongCommentsRequestItem -> Value
$ctoEncoding :: InsertSongCommentsRequestItem -> Encoding
toEncoding :: InsertSongCommentsRequestItem -> Encoding
$ctoJSONList :: [InsertSongCommentsRequestItem] -> Value
toJSONList :: [InsertSongCommentsRequestItem] -> Value
$ctoEncodingList :: [InsertSongCommentsRequestItem] -> Encoding
toEncodingList :: [InsertSongCommentsRequestItem] -> Encoding
$comitField :: InsertSongCommentsRequestItem -> Bool
omitField :: InsertSongCommentsRequestItem -> Bool
ToJSON, Typeable InsertSongCommentsRequestItem
Typeable InsertSongCommentsRequestItem =>
(Proxy InsertSongCommentsRequestItem
 -> Declare (Definitions Schema) NamedSchema)
-> ToSchema InsertSongCommentsRequestItem
Proxy InsertSongCommentsRequestItem
-> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy InsertSongCommentsRequestItem
-> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy InsertSongCommentsRequestItem
-> Declare (Definitions Schema) NamedSchema
ToSchema)
newtype  = 
  {  :: [InsertSongCommentsRequestItem]
  }
  deriving (InsertSongCommentsRequest -> InsertSongCommentsRequest -> Bool
(InsertSongCommentsRequest -> InsertSongCommentsRequest -> Bool)
-> (InsertSongCommentsRequest -> InsertSongCommentsRequest -> Bool)
-> Eq InsertSongCommentsRequest
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InsertSongCommentsRequest -> InsertSongCommentsRequest -> Bool
== :: InsertSongCommentsRequest -> InsertSongCommentsRequest -> Bool
$c/= :: InsertSongCommentsRequest -> InsertSongCommentsRequest -> Bool
/= :: InsertSongCommentsRequest -> InsertSongCommentsRequest -> Bool
Eq, Int -> InsertSongCommentsRequest -> ShowS
[InsertSongCommentsRequest] -> ShowS
InsertSongCommentsRequest -> String
(Int -> InsertSongCommentsRequest -> ShowS)
-> (InsertSongCommentsRequest -> String)
-> ([InsertSongCommentsRequest] -> ShowS)
-> Show InsertSongCommentsRequest
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InsertSongCommentsRequest -> ShowS
showsPrec :: Int -> InsertSongCommentsRequest -> ShowS
$cshow :: InsertSongCommentsRequest -> String
show :: InsertSongCommentsRequest -> String
$cshowList :: [InsertSongCommentsRequest] -> ShowS
showList :: [InsertSongCommentsRequest] -> ShowS
Show, (forall x.
 InsertSongCommentsRequest -> Rep InsertSongCommentsRequest x)
-> (forall x.
    Rep InsertSongCommentsRequest x -> InsertSongCommentsRequest)
-> Generic InsertSongCommentsRequest
forall x.
Rep InsertSongCommentsRequest x -> InsertSongCommentsRequest
forall x.
InsertSongCommentsRequest -> Rep InsertSongCommentsRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
InsertSongCommentsRequest -> Rep InsertSongCommentsRequest x
from :: forall x.
InsertSongCommentsRequest -> Rep InsertSongCommentsRequest x
$cto :: forall x.
Rep InsertSongCommentsRequest x -> InsertSongCommentsRequest
to :: forall x.
Rep InsertSongCommentsRequest x -> InsertSongCommentsRequest
Generic)
  deriving anyclass (Maybe InsertSongCommentsRequest
Value -> Parser [InsertSongCommentsRequest]
Value -> Parser InsertSongCommentsRequest
(Value -> Parser InsertSongCommentsRequest)
-> (Value -> Parser [InsertSongCommentsRequest])
-> Maybe InsertSongCommentsRequest
-> FromJSON InsertSongCommentsRequest
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser InsertSongCommentsRequest
parseJSON :: Value -> Parser InsertSongCommentsRequest
$cparseJSONList :: Value -> Parser [InsertSongCommentsRequest]
parseJSONList :: Value -> Parser [InsertSongCommentsRequest]
$comittedField :: Maybe InsertSongCommentsRequest
omittedField :: Maybe InsertSongCommentsRequest
FromJSON, [InsertSongCommentsRequest] -> Value
[InsertSongCommentsRequest] -> Encoding
InsertSongCommentsRequest -> Bool
InsertSongCommentsRequest -> Value
InsertSongCommentsRequest -> Encoding
(InsertSongCommentsRequest -> Value)
-> (InsertSongCommentsRequest -> Encoding)
-> ([InsertSongCommentsRequest] -> Value)
-> ([InsertSongCommentsRequest] -> Encoding)
-> (InsertSongCommentsRequest -> Bool)
-> ToJSON InsertSongCommentsRequest
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: InsertSongCommentsRequest -> Value
toJSON :: InsertSongCommentsRequest -> Value
$ctoEncoding :: InsertSongCommentsRequest -> Encoding
toEncoding :: InsertSongCommentsRequest -> Encoding
$ctoJSONList :: [InsertSongCommentsRequest] -> Value
toJSONList :: [InsertSongCommentsRequest] -> Value
$ctoEncodingList :: [InsertSongCommentsRequest] -> Encoding
toEncodingList :: [InsertSongCommentsRequest] -> Encoding
$comitField :: InsertSongCommentsRequest -> Bool
omitField :: InsertSongCommentsRequest -> Bool
ToJSON, Typeable InsertSongCommentsRequest
Typeable InsertSongCommentsRequest =>
(Proxy InsertSongCommentsRequest
 -> Declare (Definitions Schema) NamedSchema)
-> ToSchema InsertSongCommentsRequest
Proxy InsertSongCommentsRequest
-> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy InsertSongCommentsRequest
-> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy InsertSongCommentsRequest
-> Declare (Definitions Schema) NamedSchema
ToSchema)
makeFieldLabelsNoPrefix ''InsertSongCommentsRequest
makeFieldLabelsNoPrefix ''InsertSongCommentsRequestItem
data UpsertSongOpinionsCommandResponse = UpsertSongOpinionsCommandResponse
  { UpsertSongOpinionsCommandResponse -> Map UUID SongOpinion
songOpinions :: Map UUID SongOpinion,
    UpsertSongOpinionsCommandResponse -> Map Text (Validation [Text])
validationResults :: Map Text ValidationResult
  }
  deriving (UpsertSongOpinionsCommandResponse
-> UpsertSongOpinionsCommandResponse -> Bool
(UpsertSongOpinionsCommandResponse
 -> UpsertSongOpinionsCommandResponse -> Bool)
-> (UpsertSongOpinionsCommandResponse
    -> UpsertSongOpinionsCommandResponse -> Bool)
-> Eq UpsertSongOpinionsCommandResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UpsertSongOpinionsCommandResponse
-> UpsertSongOpinionsCommandResponse -> Bool
== :: UpsertSongOpinionsCommandResponse
-> UpsertSongOpinionsCommandResponse -> Bool
$c/= :: UpsertSongOpinionsCommandResponse
-> UpsertSongOpinionsCommandResponse -> Bool
/= :: UpsertSongOpinionsCommandResponse
-> UpsertSongOpinionsCommandResponse -> Bool
Eq, Int -> UpsertSongOpinionsCommandResponse -> ShowS
[UpsertSongOpinionsCommandResponse] -> ShowS
UpsertSongOpinionsCommandResponse -> String
(Int -> UpsertSongOpinionsCommandResponse -> ShowS)
-> (UpsertSongOpinionsCommandResponse -> String)
-> ([UpsertSongOpinionsCommandResponse] -> ShowS)
-> Show UpsertSongOpinionsCommandResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UpsertSongOpinionsCommandResponse -> ShowS
showsPrec :: Int -> UpsertSongOpinionsCommandResponse -> ShowS
$cshow :: UpsertSongOpinionsCommandResponse -> String
show :: UpsertSongOpinionsCommandResponse -> String
$cshowList :: [UpsertSongOpinionsCommandResponse] -> ShowS
showList :: [UpsertSongOpinionsCommandResponse] -> ShowS
Show, (forall x.
 UpsertSongOpinionsCommandResponse
 -> Rep UpsertSongOpinionsCommandResponse x)
-> (forall x.
    Rep UpsertSongOpinionsCommandResponse x
    -> UpsertSongOpinionsCommandResponse)
-> Generic UpsertSongOpinionsCommandResponse
forall x.
Rep UpsertSongOpinionsCommandResponse x
-> UpsertSongOpinionsCommandResponse
forall x.
UpsertSongOpinionsCommandResponse
-> Rep UpsertSongOpinionsCommandResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
UpsertSongOpinionsCommandResponse
-> Rep UpsertSongOpinionsCommandResponse x
from :: forall x.
UpsertSongOpinionsCommandResponse
-> Rep UpsertSongOpinionsCommandResponse x
$cto :: forall x.
Rep UpsertSongOpinionsCommandResponse x
-> UpsertSongOpinionsCommandResponse
to :: forall x.
Rep UpsertSongOpinionsCommandResponse x
-> UpsertSongOpinionsCommandResponse
Generic, Maybe UpsertSongOpinionsCommandResponse
Value -> Parser [UpsertSongOpinionsCommandResponse]
Value -> Parser UpsertSongOpinionsCommandResponse
(Value -> Parser UpsertSongOpinionsCommandResponse)
-> (Value -> Parser [UpsertSongOpinionsCommandResponse])
-> Maybe UpsertSongOpinionsCommandResponse
-> FromJSON UpsertSongOpinionsCommandResponse
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser UpsertSongOpinionsCommandResponse
parseJSON :: Value -> Parser UpsertSongOpinionsCommandResponse
$cparseJSONList :: Value -> Parser [UpsertSongOpinionsCommandResponse]
parseJSONList :: Value -> Parser [UpsertSongOpinionsCommandResponse]
$comittedField :: Maybe UpsertSongOpinionsCommandResponse
omittedField :: Maybe UpsertSongOpinionsCommandResponse
FromJSON, [UpsertSongOpinionsCommandResponse] -> Value
[UpsertSongOpinionsCommandResponse] -> Encoding
UpsertSongOpinionsCommandResponse -> Bool
UpsertSongOpinionsCommandResponse -> Value
UpsertSongOpinionsCommandResponse -> Encoding
(UpsertSongOpinionsCommandResponse -> Value)
-> (UpsertSongOpinionsCommandResponse -> Encoding)
-> ([UpsertSongOpinionsCommandResponse] -> Value)
-> ([UpsertSongOpinionsCommandResponse] -> Encoding)
-> (UpsertSongOpinionsCommandResponse -> Bool)
-> ToJSON UpsertSongOpinionsCommandResponse
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: UpsertSongOpinionsCommandResponse -> Value
toJSON :: UpsertSongOpinionsCommandResponse -> Value
$ctoEncoding :: UpsertSongOpinionsCommandResponse -> Encoding
toEncoding :: UpsertSongOpinionsCommandResponse -> Encoding
$ctoJSONList :: [UpsertSongOpinionsCommandResponse] -> Value
toJSONList :: [UpsertSongOpinionsCommandResponse] -> Value
$ctoEncodingList :: [UpsertSongOpinionsCommandResponse] -> Encoding
toEncodingList :: [UpsertSongOpinionsCommandResponse] -> Encoding
$comitField :: UpsertSongOpinionsCommandResponse -> Bool
omitField :: UpsertSongOpinionsCommandResponse -> Bool
ToJSON, Typeable UpsertSongOpinionsCommandResponse
Typeable UpsertSongOpinionsCommandResponse =>
(Proxy UpsertSongOpinionsCommandResponse
 -> Declare (Definitions Schema) NamedSchema)
-> ToSchema UpsertSongOpinionsCommandResponse
Proxy UpsertSongOpinionsCommandResponse
-> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy UpsertSongOpinionsCommandResponse
-> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy UpsertSongOpinionsCommandResponse
-> Declare (Definitions Schema) NamedSchema
ToSchema)
makeFieldLabelsNoPrefix ''UpsertSongOpinionsCommandResponse
data UpsertSongOpinionsRequestItem = UpsertSongOpinionsRequestItem
  { UpsertSongOpinionsRequestItem -> UUID
songIdentifier :: UUID,
    UpsertSongOpinionsRequestItem -> Bool
isLike :: Bool
  }
  deriving (UpsertSongOpinionsRequestItem
-> UpsertSongOpinionsRequestItem -> Bool
(UpsertSongOpinionsRequestItem
 -> UpsertSongOpinionsRequestItem -> Bool)
-> (UpsertSongOpinionsRequestItem
    -> UpsertSongOpinionsRequestItem -> Bool)
-> Eq UpsertSongOpinionsRequestItem
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UpsertSongOpinionsRequestItem
-> UpsertSongOpinionsRequestItem -> Bool
== :: UpsertSongOpinionsRequestItem
-> UpsertSongOpinionsRequestItem -> Bool
$c/= :: UpsertSongOpinionsRequestItem
-> UpsertSongOpinionsRequestItem -> Bool
/= :: UpsertSongOpinionsRequestItem
-> UpsertSongOpinionsRequestItem -> Bool
Eq, Int -> UpsertSongOpinionsRequestItem -> ShowS
[UpsertSongOpinionsRequestItem] -> ShowS
UpsertSongOpinionsRequestItem -> String
(Int -> UpsertSongOpinionsRequestItem -> ShowS)
-> (UpsertSongOpinionsRequestItem -> String)
-> ([UpsertSongOpinionsRequestItem] -> ShowS)
-> Show UpsertSongOpinionsRequestItem
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UpsertSongOpinionsRequestItem -> ShowS
showsPrec :: Int -> UpsertSongOpinionsRequestItem -> ShowS
$cshow :: UpsertSongOpinionsRequestItem -> String
show :: UpsertSongOpinionsRequestItem -> String
$cshowList :: [UpsertSongOpinionsRequestItem] -> ShowS
showList :: [UpsertSongOpinionsRequestItem] -> ShowS
Show, (forall x.
 UpsertSongOpinionsRequestItem
 -> Rep UpsertSongOpinionsRequestItem x)
-> (forall x.
    Rep UpsertSongOpinionsRequestItem x
    -> UpsertSongOpinionsRequestItem)
-> Generic UpsertSongOpinionsRequestItem
forall x.
Rep UpsertSongOpinionsRequestItem x
-> UpsertSongOpinionsRequestItem
forall x.
UpsertSongOpinionsRequestItem
-> Rep UpsertSongOpinionsRequestItem x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
UpsertSongOpinionsRequestItem
-> Rep UpsertSongOpinionsRequestItem x
from :: forall x.
UpsertSongOpinionsRequestItem
-> Rep UpsertSongOpinionsRequestItem x
$cto :: forall x.
Rep UpsertSongOpinionsRequestItem x
-> UpsertSongOpinionsRequestItem
to :: forall x.
Rep UpsertSongOpinionsRequestItem x
-> UpsertSongOpinionsRequestItem
Generic, Maybe UpsertSongOpinionsRequestItem
Value -> Parser [UpsertSongOpinionsRequestItem]
Value -> Parser UpsertSongOpinionsRequestItem
(Value -> Parser UpsertSongOpinionsRequestItem)
-> (Value -> Parser [UpsertSongOpinionsRequestItem])
-> Maybe UpsertSongOpinionsRequestItem
-> FromJSON UpsertSongOpinionsRequestItem
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser UpsertSongOpinionsRequestItem
parseJSON :: Value -> Parser UpsertSongOpinionsRequestItem
$cparseJSONList :: Value -> Parser [UpsertSongOpinionsRequestItem]
parseJSONList :: Value -> Parser [UpsertSongOpinionsRequestItem]
$comittedField :: Maybe UpsertSongOpinionsRequestItem
omittedField :: Maybe UpsertSongOpinionsRequestItem
FromJSON, [UpsertSongOpinionsRequestItem] -> Value
[UpsertSongOpinionsRequestItem] -> Encoding
UpsertSongOpinionsRequestItem -> Bool
UpsertSongOpinionsRequestItem -> Value
UpsertSongOpinionsRequestItem -> Encoding
(UpsertSongOpinionsRequestItem -> Value)
-> (UpsertSongOpinionsRequestItem -> Encoding)
-> ([UpsertSongOpinionsRequestItem] -> Value)
-> ([UpsertSongOpinionsRequestItem] -> Encoding)
-> (UpsertSongOpinionsRequestItem -> Bool)
-> ToJSON UpsertSongOpinionsRequestItem
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: UpsertSongOpinionsRequestItem -> Value
toJSON :: UpsertSongOpinionsRequestItem -> Value
$ctoEncoding :: UpsertSongOpinionsRequestItem -> Encoding
toEncoding :: UpsertSongOpinionsRequestItem -> Encoding
$ctoJSONList :: [UpsertSongOpinionsRequestItem] -> Value
toJSONList :: [UpsertSongOpinionsRequestItem] -> Value
$ctoEncodingList :: [UpsertSongOpinionsRequestItem] -> Encoding
toEncodingList :: [UpsertSongOpinionsRequestItem] -> Encoding
$comitField :: UpsertSongOpinionsRequestItem -> Bool
omitField :: UpsertSongOpinionsRequestItem -> Bool
ToJSON, Typeable UpsertSongOpinionsRequestItem
Typeable UpsertSongOpinionsRequestItem =>
(Proxy UpsertSongOpinionsRequestItem
 -> Declare (Definitions Schema) NamedSchema)
-> ToSchema UpsertSongOpinionsRequestItem
Proxy UpsertSongOpinionsRequestItem
-> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy UpsertSongOpinionsRequestItem
-> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy UpsertSongOpinionsRequestItem
-> Declare (Definitions Schema) NamedSchema
ToSchema)
newtype UpsertSongOpinionsRequest = UpsertSongOpinionsRequest
  { UpsertSongOpinionsRequest -> [UpsertSongOpinionsRequestItem]
songOpinions :: [UpsertSongOpinionsRequestItem]
  }
  deriving (UpsertSongOpinionsRequest -> UpsertSongOpinionsRequest -> Bool
(UpsertSongOpinionsRequest -> UpsertSongOpinionsRequest -> Bool)
-> (UpsertSongOpinionsRequest -> UpsertSongOpinionsRequest -> Bool)
-> Eq UpsertSongOpinionsRequest
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UpsertSongOpinionsRequest -> UpsertSongOpinionsRequest -> Bool
== :: UpsertSongOpinionsRequest -> UpsertSongOpinionsRequest -> Bool
$c/= :: UpsertSongOpinionsRequest -> UpsertSongOpinionsRequest -> Bool
/= :: UpsertSongOpinionsRequest -> UpsertSongOpinionsRequest -> Bool
Eq, Int -> UpsertSongOpinionsRequest -> ShowS
[UpsertSongOpinionsRequest] -> ShowS
UpsertSongOpinionsRequest -> String
(Int -> UpsertSongOpinionsRequest -> ShowS)
-> (UpsertSongOpinionsRequest -> String)
-> ([UpsertSongOpinionsRequest] -> ShowS)
-> Show UpsertSongOpinionsRequest
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UpsertSongOpinionsRequest -> ShowS
showsPrec :: Int -> UpsertSongOpinionsRequest -> ShowS
$cshow :: UpsertSongOpinionsRequest -> String
show :: UpsertSongOpinionsRequest -> String
$cshowList :: [UpsertSongOpinionsRequest] -> ShowS
showList :: [UpsertSongOpinionsRequest] -> ShowS
Show, (forall x.
 UpsertSongOpinionsRequest -> Rep UpsertSongOpinionsRequest x)
-> (forall x.
    Rep UpsertSongOpinionsRequest x -> UpsertSongOpinionsRequest)
-> Generic UpsertSongOpinionsRequest
forall x.
Rep UpsertSongOpinionsRequest x -> UpsertSongOpinionsRequest
forall x.
UpsertSongOpinionsRequest -> Rep UpsertSongOpinionsRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
UpsertSongOpinionsRequest -> Rep UpsertSongOpinionsRequest x
from :: forall x.
UpsertSongOpinionsRequest -> Rep UpsertSongOpinionsRequest x
$cto :: forall x.
Rep UpsertSongOpinionsRequest x -> UpsertSongOpinionsRequest
to :: forall x.
Rep UpsertSongOpinionsRequest x -> UpsertSongOpinionsRequest
Generic)
  deriving anyclass (Maybe UpsertSongOpinionsRequest
Value -> Parser [UpsertSongOpinionsRequest]
Value -> Parser UpsertSongOpinionsRequest
(Value -> Parser UpsertSongOpinionsRequest)
-> (Value -> Parser [UpsertSongOpinionsRequest])
-> Maybe UpsertSongOpinionsRequest
-> FromJSON UpsertSongOpinionsRequest
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser UpsertSongOpinionsRequest
parseJSON :: Value -> Parser UpsertSongOpinionsRequest
$cparseJSONList :: Value -> Parser [UpsertSongOpinionsRequest]
parseJSONList :: Value -> Parser [UpsertSongOpinionsRequest]
$comittedField :: Maybe UpsertSongOpinionsRequest
omittedField :: Maybe UpsertSongOpinionsRequest
FromJSON, [UpsertSongOpinionsRequest] -> Value
[UpsertSongOpinionsRequest] -> Encoding
UpsertSongOpinionsRequest -> Bool
UpsertSongOpinionsRequest -> Value
UpsertSongOpinionsRequest -> Encoding
(UpsertSongOpinionsRequest -> Value)
-> (UpsertSongOpinionsRequest -> Encoding)
-> ([UpsertSongOpinionsRequest] -> Value)
-> ([UpsertSongOpinionsRequest] -> Encoding)
-> (UpsertSongOpinionsRequest -> Bool)
-> ToJSON UpsertSongOpinionsRequest
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: UpsertSongOpinionsRequest -> Value
toJSON :: UpsertSongOpinionsRequest -> Value
$ctoEncoding :: UpsertSongOpinionsRequest -> Encoding
toEncoding :: UpsertSongOpinionsRequest -> Encoding
$ctoJSONList :: [UpsertSongOpinionsRequest] -> Value
toJSONList :: [UpsertSongOpinionsRequest] -> Value
$ctoEncodingList :: [UpsertSongOpinionsRequest] -> Encoding
toEncodingList :: [UpsertSongOpinionsRequest] -> Encoding
$comitField :: UpsertSongOpinionsRequest -> Bool
omitField :: UpsertSongOpinionsRequest -> Bool
ToJSON, Typeable UpsertSongOpinionsRequest
Typeable UpsertSongOpinionsRequest =>
(Proxy UpsertSongOpinionsRequest
 -> Declare (Definitions Schema) NamedSchema)
-> ToSchema UpsertSongOpinionsRequest
Proxy UpsertSongOpinionsRequest
-> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy UpsertSongOpinionsRequest
-> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy UpsertSongOpinionsRequest
-> Declare (Definitions Schema) NamedSchema
ToSchema)
makeFieldLabelsNoPrefix ''UpsertSongOpinionsRequest
makeFieldLabelsNoPrefix ''UpsertSongOpinionsRequestItem
data InsertSongArtworksCommandResponse = InsertSongArtworksCommandResponse
  { InsertSongArtworksCommandResponse -> Map UUID SongArtwork
songArtworks :: Map UUID SongArtwork,
    InsertSongArtworksCommandResponse -> Map Text (Validation [Text])
validationResults :: Map Text ValidationResult
  }
  deriving (InsertSongArtworksCommandResponse
-> InsertSongArtworksCommandResponse -> Bool
(InsertSongArtworksCommandResponse
 -> InsertSongArtworksCommandResponse -> Bool)
-> (InsertSongArtworksCommandResponse
    -> InsertSongArtworksCommandResponse -> Bool)
-> Eq InsertSongArtworksCommandResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InsertSongArtworksCommandResponse
-> InsertSongArtworksCommandResponse -> Bool
== :: InsertSongArtworksCommandResponse
-> InsertSongArtworksCommandResponse -> Bool
$c/= :: InsertSongArtworksCommandResponse
-> InsertSongArtworksCommandResponse -> Bool
/= :: InsertSongArtworksCommandResponse
-> InsertSongArtworksCommandResponse -> Bool
Eq, Int -> InsertSongArtworksCommandResponse -> ShowS
[InsertSongArtworksCommandResponse] -> ShowS
InsertSongArtworksCommandResponse -> String
(Int -> InsertSongArtworksCommandResponse -> ShowS)
-> (InsertSongArtworksCommandResponse -> String)
-> ([InsertSongArtworksCommandResponse] -> ShowS)
-> Show InsertSongArtworksCommandResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InsertSongArtworksCommandResponse -> ShowS
showsPrec :: Int -> InsertSongArtworksCommandResponse -> ShowS
$cshow :: InsertSongArtworksCommandResponse -> String
show :: InsertSongArtworksCommandResponse -> String
$cshowList :: [InsertSongArtworksCommandResponse] -> ShowS
showList :: [InsertSongArtworksCommandResponse] -> ShowS
Show, (forall x.
 InsertSongArtworksCommandResponse
 -> Rep InsertSongArtworksCommandResponse x)
-> (forall x.
    Rep InsertSongArtworksCommandResponse x
    -> InsertSongArtworksCommandResponse)
-> Generic InsertSongArtworksCommandResponse
forall x.
Rep InsertSongArtworksCommandResponse x
-> InsertSongArtworksCommandResponse
forall x.
InsertSongArtworksCommandResponse
-> Rep InsertSongArtworksCommandResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
InsertSongArtworksCommandResponse
-> Rep InsertSongArtworksCommandResponse x
from :: forall x.
InsertSongArtworksCommandResponse
-> Rep InsertSongArtworksCommandResponse x
$cto :: forall x.
Rep InsertSongArtworksCommandResponse x
-> InsertSongArtworksCommandResponse
to :: forall x.
Rep InsertSongArtworksCommandResponse x
-> InsertSongArtworksCommandResponse
Generic, Maybe InsertSongArtworksCommandResponse
Value -> Parser [InsertSongArtworksCommandResponse]
Value -> Parser InsertSongArtworksCommandResponse
(Value -> Parser InsertSongArtworksCommandResponse)
-> (Value -> Parser [InsertSongArtworksCommandResponse])
-> Maybe InsertSongArtworksCommandResponse
-> FromJSON InsertSongArtworksCommandResponse
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser InsertSongArtworksCommandResponse
parseJSON :: Value -> Parser InsertSongArtworksCommandResponse
$cparseJSONList :: Value -> Parser [InsertSongArtworksCommandResponse]
parseJSONList :: Value -> Parser [InsertSongArtworksCommandResponse]
$comittedField :: Maybe InsertSongArtworksCommandResponse
omittedField :: Maybe InsertSongArtworksCommandResponse
FromJSON, [InsertSongArtworksCommandResponse] -> Value
[InsertSongArtworksCommandResponse] -> Encoding
InsertSongArtworksCommandResponse -> Bool
InsertSongArtworksCommandResponse -> Value
InsertSongArtworksCommandResponse -> Encoding
(InsertSongArtworksCommandResponse -> Value)
-> (InsertSongArtworksCommandResponse -> Encoding)
-> ([InsertSongArtworksCommandResponse] -> Value)
-> ([InsertSongArtworksCommandResponse] -> Encoding)
-> (InsertSongArtworksCommandResponse -> Bool)
-> ToJSON InsertSongArtworksCommandResponse
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: InsertSongArtworksCommandResponse -> Value
toJSON :: InsertSongArtworksCommandResponse -> Value
$ctoEncoding :: InsertSongArtworksCommandResponse -> Encoding
toEncoding :: InsertSongArtworksCommandResponse -> Encoding
$ctoJSONList :: [InsertSongArtworksCommandResponse] -> Value
toJSONList :: [InsertSongArtworksCommandResponse] -> Value
$ctoEncodingList :: [InsertSongArtworksCommandResponse] -> Encoding
toEncodingList :: [InsertSongArtworksCommandResponse] -> Encoding
$comitField :: InsertSongArtworksCommandResponse -> Bool
omitField :: InsertSongArtworksCommandResponse -> Bool
ToJSON, Typeable InsertSongArtworksCommandResponse
Typeable InsertSongArtworksCommandResponse =>
(Proxy InsertSongArtworksCommandResponse
 -> Declare (Definitions Schema) NamedSchema)
-> ToSchema InsertSongArtworksCommandResponse
Proxy InsertSongArtworksCommandResponse
-> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy InsertSongArtworksCommandResponse
-> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy InsertSongArtworksCommandResponse
-> Declare (Definitions Schema) NamedSchema
ToSchema)
makeFieldLabelsNoPrefix ''InsertSongArtworksCommandResponse
data InsertArtistsOfSongCommandResponse = InsertArtistsOfSongCommandResponse
  { InsertArtistsOfSongCommandResponse -> Map UUID ArtistOfSong
songArtists :: Map UUID ArtistOfSong,
    InsertArtistsOfSongCommandResponse -> Map Text (Validation [Text])
validationResults :: Map Text ValidationResult
  }
  deriving (InsertArtistsOfSongCommandResponse
-> InsertArtistsOfSongCommandResponse -> Bool
(InsertArtistsOfSongCommandResponse
 -> InsertArtistsOfSongCommandResponse -> Bool)
-> (InsertArtistsOfSongCommandResponse
    -> InsertArtistsOfSongCommandResponse -> Bool)
-> Eq InsertArtistsOfSongCommandResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InsertArtistsOfSongCommandResponse
-> InsertArtistsOfSongCommandResponse -> Bool
== :: InsertArtistsOfSongCommandResponse
-> InsertArtistsOfSongCommandResponse -> Bool
$c/= :: InsertArtistsOfSongCommandResponse
-> InsertArtistsOfSongCommandResponse -> Bool
/= :: InsertArtistsOfSongCommandResponse
-> InsertArtistsOfSongCommandResponse -> Bool
Eq, Int -> InsertArtistsOfSongCommandResponse -> ShowS
[InsertArtistsOfSongCommandResponse] -> ShowS
InsertArtistsOfSongCommandResponse -> String
(Int -> InsertArtistsOfSongCommandResponse -> ShowS)
-> (InsertArtistsOfSongCommandResponse -> String)
-> ([InsertArtistsOfSongCommandResponse] -> ShowS)
-> Show InsertArtistsOfSongCommandResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InsertArtistsOfSongCommandResponse -> ShowS
showsPrec :: Int -> InsertArtistsOfSongCommandResponse -> ShowS
$cshow :: InsertArtistsOfSongCommandResponse -> String
show :: InsertArtistsOfSongCommandResponse -> String
$cshowList :: [InsertArtistsOfSongCommandResponse] -> ShowS
showList :: [InsertArtistsOfSongCommandResponse] -> ShowS
Show, (forall x.
 InsertArtistsOfSongCommandResponse
 -> Rep InsertArtistsOfSongCommandResponse x)
-> (forall x.
    Rep InsertArtistsOfSongCommandResponse x
    -> InsertArtistsOfSongCommandResponse)
-> Generic InsertArtistsOfSongCommandResponse
forall x.
Rep InsertArtistsOfSongCommandResponse x
-> InsertArtistsOfSongCommandResponse
forall x.
InsertArtistsOfSongCommandResponse
-> Rep InsertArtistsOfSongCommandResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
InsertArtistsOfSongCommandResponse
-> Rep InsertArtistsOfSongCommandResponse x
from :: forall x.
InsertArtistsOfSongCommandResponse
-> Rep InsertArtistsOfSongCommandResponse x
$cto :: forall x.
Rep InsertArtistsOfSongCommandResponse x
-> InsertArtistsOfSongCommandResponse
to :: forall x.
Rep InsertArtistsOfSongCommandResponse x
-> InsertArtistsOfSongCommandResponse
Generic, Maybe InsertArtistsOfSongCommandResponse
Value -> Parser [InsertArtistsOfSongCommandResponse]
Value -> Parser InsertArtistsOfSongCommandResponse
(Value -> Parser InsertArtistsOfSongCommandResponse)
-> (Value -> Parser [InsertArtistsOfSongCommandResponse])
-> Maybe InsertArtistsOfSongCommandResponse
-> FromJSON InsertArtistsOfSongCommandResponse
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser InsertArtistsOfSongCommandResponse
parseJSON :: Value -> Parser InsertArtistsOfSongCommandResponse
$cparseJSONList :: Value -> Parser [InsertArtistsOfSongCommandResponse]
parseJSONList :: Value -> Parser [InsertArtistsOfSongCommandResponse]
$comittedField :: Maybe InsertArtistsOfSongCommandResponse
omittedField :: Maybe InsertArtistsOfSongCommandResponse
FromJSON, [InsertArtistsOfSongCommandResponse] -> Value
[InsertArtistsOfSongCommandResponse] -> Encoding
InsertArtistsOfSongCommandResponse -> Bool
InsertArtistsOfSongCommandResponse -> Value
InsertArtistsOfSongCommandResponse -> Encoding
(InsertArtistsOfSongCommandResponse -> Value)
-> (InsertArtistsOfSongCommandResponse -> Encoding)
-> ([InsertArtistsOfSongCommandResponse] -> Value)
-> ([InsertArtistsOfSongCommandResponse] -> Encoding)
-> (InsertArtistsOfSongCommandResponse -> Bool)
-> ToJSON InsertArtistsOfSongCommandResponse
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: InsertArtistsOfSongCommandResponse -> Value
toJSON :: InsertArtistsOfSongCommandResponse -> Value
$ctoEncoding :: InsertArtistsOfSongCommandResponse -> Encoding
toEncoding :: InsertArtistsOfSongCommandResponse -> Encoding
$ctoJSONList :: [InsertArtistsOfSongCommandResponse] -> Value
toJSONList :: [InsertArtistsOfSongCommandResponse] -> Value
$ctoEncodingList :: [InsertArtistsOfSongCommandResponse] -> Encoding
toEncodingList :: [InsertArtistsOfSongCommandResponse] -> Encoding
$comitField :: InsertArtistsOfSongCommandResponse -> Bool
omitField :: InsertArtistsOfSongCommandResponse -> Bool
ToJSON, Typeable InsertArtistsOfSongCommandResponse
Typeable InsertArtistsOfSongCommandResponse =>
(Proxy InsertArtistsOfSongCommandResponse
 -> Declare (Definitions Schema) NamedSchema)
-> ToSchema InsertArtistsOfSongCommandResponse
Proxy InsertArtistsOfSongCommandResponse
-> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy InsertArtistsOfSongCommandResponse
-> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy InsertArtistsOfSongCommandResponse
-> Declare (Definitions Schema) NamedSchema
ToSchema)
makeFieldLabelsNoPrefix ''InsertArtistsOfSongCommandResponse
data InsertSongArtworksRequestItem = InsertSongArtworksRequestItem
  { InsertSongArtworksRequestItem -> UUID
songIdentifier :: UUID,
    InsertSongArtworksRequestItem -> Text
contentUrl :: Text,
    InsertSongArtworksRequestItem -> Maybe Text
contentCaption :: Maybe Text,
    InsertSongArtworksRequestItem -> Int
orderValue :: Int
  }
  deriving (InsertSongArtworksRequestItem
-> InsertSongArtworksRequestItem -> Bool
(InsertSongArtworksRequestItem
 -> InsertSongArtworksRequestItem -> Bool)
-> (InsertSongArtworksRequestItem
    -> InsertSongArtworksRequestItem -> Bool)
-> Eq InsertSongArtworksRequestItem
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InsertSongArtworksRequestItem
-> InsertSongArtworksRequestItem -> Bool
== :: InsertSongArtworksRequestItem
-> InsertSongArtworksRequestItem -> Bool
$c/= :: InsertSongArtworksRequestItem
-> InsertSongArtworksRequestItem -> Bool
/= :: InsertSongArtworksRequestItem
-> InsertSongArtworksRequestItem -> Bool
Eq, Int -> InsertSongArtworksRequestItem -> ShowS
[InsertSongArtworksRequestItem] -> ShowS
InsertSongArtworksRequestItem -> String
(Int -> InsertSongArtworksRequestItem -> ShowS)
-> (InsertSongArtworksRequestItem -> String)
-> ([InsertSongArtworksRequestItem] -> ShowS)
-> Show InsertSongArtworksRequestItem
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InsertSongArtworksRequestItem -> ShowS
showsPrec :: Int -> InsertSongArtworksRequestItem -> ShowS
$cshow :: InsertSongArtworksRequestItem -> String
show :: InsertSongArtworksRequestItem -> String
$cshowList :: [InsertSongArtworksRequestItem] -> ShowS
showList :: [InsertSongArtworksRequestItem] -> ShowS
Show, (forall x.
 InsertSongArtworksRequestItem
 -> Rep InsertSongArtworksRequestItem x)
-> (forall x.
    Rep InsertSongArtworksRequestItem x
    -> InsertSongArtworksRequestItem)
-> Generic InsertSongArtworksRequestItem
forall x.
Rep InsertSongArtworksRequestItem x
-> InsertSongArtworksRequestItem
forall x.
InsertSongArtworksRequestItem
-> Rep InsertSongArtworksRequestItem x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
InsertSongArtworksRequestItem
-> Rep InsertSongArtworksRequestItem x
from :: forall x.
InsertSongArtworksRequestItem
-> Rep InsertSongArtworksRequestItem x
$cto :: forall x.
Rep InsertSongArtworksRequestItem x
-> InsertSongArtworksRequestItem
to :: forall x.
Rep InsertSongArtworksRequestItem x
-> InsertSongArtworksRequestItem
Generic, Maybe InsertSongArtworksRequestItem
Value -> Parser [InsertSongArtworksRequestItem]
Value -> Parser InsertSongArtworksRequestItem
(Value -> Parser InsertSongArtworksRequestItem)
-> (Value -> Parser [InsertSongArtworksRequestItem])
-> Maybe InsertSongArtworksRequestItem
-> FromJSON InsertSongArtworksRequestItem
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser InsertSongArtworksRequestItem
parseJSON :: Value -> Parser InsertSongArtworksRequestItem
$cparseJSONList :: Value -> Parser [InsertSongArtworksRequestItem]
parseJSONList :: Value -> Parser [InsertSongArtworksRequestItem]
$comittedField :: Maybe InsertSongArtworksRequestItem
omittedField :: Maybe InsertSongArtworksRequestItem
FromJSON, [InsertSongArtworksRequestItem] -> Value
[InsertSongArtworksRequestItem] -> Encoding
InsertSongArtworksRequestItem -> Bool
InsertSongArtworksRequestItem -> Value
InsertSongArtworksRequestItem -> Encoding
(InsertSongArtworksRequestItem -> Value)
-> (InsertSongArtworksRequestItem -> Encoding)
-> ([InsertSongArtworksRequestItem] -> Value)
-> ([InsertSongArtworksRequestItem] -> Encoding)
-> (InsertSongArtworksRequestItem -> Bool)
-> ToJSON InsertSongArtworksRequestItem
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: InsertSongArtworksRequestItem -> Value
toJSON :: InsertSongArtworksRequestItem -> Value
$ctoEncoding :: InsertSongArtworksRequestItem -> Encoding
toEncoding :: InsertSongArtworksRequestItem -> Encoding
$ctoJSONList :: [InsertSongArtworksRequestItem] -> Value
toJSONList :: [InsertSongArtworksRequestItem] -> Value
$ctoEncodingList :: [InsertSongArtworksRequestItem] -> Encoding
toEncodingList :: [InsertSongArtworksRequestItem] -> Encoding
$comitField :: InsertSongArtworksRequestItem -> Bool
omitField :: InsertSongArtworksRequestItem -> Bool
ToJSON, Typeable InsertSongArtworksRequestItem
Typeable InsertSongArtworksRequestItem =>
(Proxy InsertSongArtworksRequestItem
 -> Declare (Definitions Schema) NamedSchema)
-> ToSchema InsertSongArtworksRequestItem
Proxy InsertSongArtworksRequestItem
-> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy InsertSongArtworksRequestItem
-> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy InsertSongArtworksRequestItem
-> Declare (Definitions Schema) NamedSchema
ToSchema)
newtype InsertSongArtworksRequest = InsertSongArtworksRequest
  { InsertSongArtworksRequest -> [InsertSongArtworksRequestItem]
songArtworks :: [InsertSongArtworksRequestItem]
  }
  deriving (InsertSongArtworksRequest -> InsertSongArtworksRequest -> Bool
(InsertSongArtworksRequest -> InsertSongArtworksRequest -> Bool)
-> (InsertSongArtworksRequest -> InsertSongArtworksRequest -> Bool)
-> Eq InsertSongArtworksRequest
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InsertSongArtworksRequest -> InsertSongArtworksRequest -> Bool
== :: InsertSongArtworksRequest -> InsertSongArtworksRequest -> Bool
$c/= :: InsertSongArtworksRequest -> InsertSongArtworksRequest -> Bool
/= :: InsertSongArtworksRequest -> InsertSongArtworksRequest -> Bool
Eq, Int -> InsertSongArtworksRequest -> ShowS
[InsertSongArtworksRequest] -> ShowS
InsertSongArtworksRequest -> String
(Int -> InsertSongArtworksRequest -> ShowS)
-> (InsertSongArtworksRequest -> String)
-> ([InsertSongArtworksRequest] -> ShowS)
-> Show InsertSongArtworksRequest
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InsertSongArtworksRequest -> ShowS
showsPrec :: Int -> InsertSongArtworksRequest -> ShowS
$cshow :: InsertSongArtworksRequest -> String
show :: InsertSongArtworksRequest -> String
$cshowList :: [InsertSongArtworksRequest] -> ShowS
showList :: [InsertSongArtworksRequest] -> ShowS
Show, (forall x.
 InsertSongArtworksRequest -> Rep InsertSongArtworksRequest x)
-> (forall x.
    Rep InsertSongArtworksRequest x -> InsertSongArtworksRequest)
-> Generic InsertSongArtworksRequest
forall x.
Rep InsertSongArtworksRequest x -> InsertSongArtworksRequest
forall x.
InsertSongArtworksRequest -> Rep InsertSongArtworksRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
InsertSongArtworksRequest -> Rep InsertSongArtworksRequest x
from :: forall x.
InsertSongArtworksRequest -> Rep InsertSongArtworksRequest x
$cto :: forall x.
Rep InsertSongArtworksRequest x -> InsertSongArtworksRequest
to :: forall x.
Rep InsertSongArtworksRequest x -> InsertSongArtworksRequest
Generic)
  deriving anyclass (Maybe InsertSongArtworksRequest
Value -> Parser [InsertSongArtworksRequest]
Value -> Parser InsertSongArtworksRequest
(Value -> Parser InsertSongArtworksRequest)
-> (Value -> Parser [InsertSongArtworksRequest])
-> Maybe InsertSongArtworksRequest
-> FromJSON InsertSongArtworksRequest
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser InsertSongArtworksRequest
parseJSON :: Value -> Parser InsertSongArtworksRequest
$cparseJSONList :: Value -> Parser [InsertSongArtworksRequest]
parseJSONList :: Value -> Parser [InsertSongArtworksRequest]
$comittedField :: Maybe InsertSongArtworksRequest
omittedField :: Maybe InsertSongArtworksRequest
FromJSON, [InsertSongArtworksRequest] -> Value
[InsertSongArtworksRequest] -> Encoding
InsertSongArtworksRequest -> Bool
InsertSongArtworksRequest -> Value
InsertSongArtworksRequest -> Encoding
(InsertSongArtworksRequest -> Value)
-> (InsertSongArtworksRequest -> Encoding)
-> ([InsertSongArtworksRequest] -> Value)
-> ([InsertSongArtworksRequest] -> Encoding)
-> (InsertSongArtworksRequest -> Bool)
-> ToJSON InsertSongArtworksRequest
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: InsertSongArtworksRequest -> Value
toJSON :: InsertSongArtworksRequest -> Value
$ctoEncoding :: InsertSongArtworksRequest -> Encoding
toEncoding :: InsertSongArtworksRequest -> Encoding
$ctoJSONList :: [InsertSongArtworksRequest] -> Value
toJSONList :: [InsertSongArtworksRequest] -> Value
$ctoEncodingList :: [InsertSongArtworksRequest] -> Encoding
toEncodingList :: [InsertSongArtworksRequest] -> Encoding
$comitField :: InsertSongArtworksRequest -> Bool
omitField :: InsertSongArtworksRequest -> Bool
ToJSON, Typeable InsertSongArtworksRequest
Typeable InsertSongArtworksRequest =>
(Proxy InsertSongArtworksRequest
 -> Declare (Definitions Schema) NamedSchema)
-> ToSchema InsertSongArtworksRequest
Proxy InsertSongArtworksRequest
-> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy InsertSongArtworksRequest
-> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy InsertSongArtworksRequest
-> Declare (Definitions Schema) NamedSchema
ToSchema)
makeFieldLabelsNoPrefix ''InsertSongArtworksRequest
makeFieldLabelsNoPrefix ''InsertSongArtworksRequestItem
data InsertArtistsOfSongsRequestItem = InsertArtistsOfSongsRequestItem
  { InsertArtistsOfSongsRequestItem -> UUID
songIdentifier :: UUID,
    InsertArtistsOfSongsRequestItem -> UUID
artistIdentifier :: UUID
  }
  deriving (InsertArtistsOfSongsRequestItem
-> InsertArtistsOfSongsRequestItem -> Bool
(InsertArtistsOfSongsRequestItem
 -> InsertArtistsOfSongsRequestItem -> Bool)
-> (InsertArtistsOfSongsRequestItem
    -> InsertArtistsOfSongsRequestItem -> Bool)
-> Eq InsertArtistsOfSongsRequestItem
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InsertArtistsOfSongsRequestItem
-> InsertArtistsOfSongsRequestItem -> Bool
== :: InsertArtistsOfSongsRequestItem
-> InsertArtistsOfSongsRequestItem -> Bool
$c/= :: InsertArtistsOfSongsRequestItem
-> InsertArtistsOfSongsRequestItem -> Bool
/= :: InsertArtistsOfSongsRequestItem
-> InsertArtistsOfSongsRequestItem -> Bool
Eq, Int -> InsertArtistsOfSongsRequestItem -> ShowS
[InsertArtistsOfSongsRequestItem] -> ShowS
InsertArtistsOfSongsRequestItem -> String
(Int -> InsertArtistsOfSongsRequestItem -> ShowS)
-> (InsertArtistsOfSongsRequestItem -> String)
-> ([InsertArtistsOfSongsRequestItem] -> ShowS)
-> Show InsertArtistsOfSongsRequestItem
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InsertArtistsOfSongsRequestItem -> ShowS
showsPrec :: Int -> InsertArtistsOfSongsRequestItem -> ShowS
$cshow :: InsertArtistsOfSongsRequestItem -> String
show :: InsertArtistsOfSongsRequestItem -> String
$cshowList :: [InsertArtistsOfSongsRequestItem] -> ShowS
showList :: [InsertArtistsOfSongsRequestItem] -> ShowS
Show, (forall x.
 InsertArtistsOfSongsRequestItem
 -> Rep InsertArtistsOfSongsRequestItem x)
-> (forall x.
    Rep InsertArtistsOfSongsRequestItem x
    -> InsertArtistsOfSongsRequestItem)
-> Generic InsertArtistsOfSongsRequestItem
forall x.
Rep InsertArtistsOfSongsRequestItem x
-> InsertArtistsOfSongsRequestItem
forall x.
InsertArtistsOfSongsRequestItem
-> Rep InsertArtistsOfSongsRequestItem x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
InsertArtistsOfSongsRequestItem
-> Rep InsertArtistsOfSongsRequestItem x
from :: forall x.
InsertArtistsOfSongsRequestItem
-> Rep InsertArtistsOfSongsRequestItem x
$cto :: forall x.
Rep InsertArtistsOfSongsRequestItem x
-> InsertArtistsOfSongsRequestItem
to :: forall x.
Rep InsertArtistsOfSongsRequestItem x
-> InsertArtistsOfSongsRequestItem
Generic, Maybe InsertArtistsOfSongsRequestItem
Value -> Parser [InsertArtistsOfSongsRequestItem]
Value -> Parser InsertArtistsOfSongsRequestItem
(Value -> Parser InsertArtistsOfSongsRequestItem)
-> (Value -> Parser [InsertArtistsOfSongsRequestItem])
-> Maybe InsertArtistsOfSongsRequestItem
-> FromJSON InsertArtistsOfSongsRequestItem
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser InsertArtistsOfSongsRequestItem
parseJSON :: Value -> Parser InsertArtistsOfSongsRequestItem
$cparseJSONList :: Value -> Parser [InsertArtistsOfSongsRequestItem]
parseJSONList :: Value -> Parser [InsertArtistsOfSongsRequestItem]
$comittedField :: Maybe InsertArtistsOfSongsRequestItem
omittedField :: Maybe InsertArtistsOfSongsRequestItem
FromJSON, [InsertArtistsOfSongsRequestItem] -> Value
[InsertArtistsOfSongsRequestItem] -> Encoding
InsertArtistsOfSongsRequestItem -> Bool
InsertArtistsOfSongsRequestItem -> Value
InsertArtistsOfSongsRequestItem -> Encoding
(InsertArtistsOfSongsRequestItem -> Value)
-> (InsertArtistsOfSongsRequestItem -> Encoding)
-> ([InsertArtistsOfSongsRequestItem] -> Value)
-> ([InsertArtistsOfSongsRequestItem] -> Encoding)
-> (InsertArtistsOfSongsRequestItem -> Bool)
-> ToJSON InsertArtistsOfSongsRequestItem
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: InsertArtistsOfSongsRequestItem -> Value
toJSON :: InsertArtistsOfSongsRequestItem -> Value
$ctoEncoding :: InsertArtistsOfSongsRequestItem -> Encoding
toEncoding :: InsertArtistsOfSongsRequestItem -> Encoding
$ctoJSONList :: [InsertArtistsOfSongsRequestItem] -> Value
toJSONList :: [InsertArtistsOfSongsRequestItem] -> Value
$ctoEncodingList :: [InsertArtistsOfSongsRequestItem] -> Encoding
toEncodingList :: [InsertArtistsOfSongsRequestItem] -> Encoding
$comitField :: InsertArtistsOfSongsRequestItem -> Bool
omitField :: InsertArtistsOfSongsRequestItem -> Bool
ToJSON, Typeable InsertArtistsOfSongsRequestItem
Typeable InsertArtistsOfSongsRequestItem =>
(Proxy InsertArtistsOfSongsRequestItem
 -> Declare (Definitions Schema) NamedSchema)
-> ToSchema InsertArtistsOfSongsRequestItem
Proxy InsertArtistsOfSongsRequestItem
-> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy InsertArtistsOfSongsRequestItem
-> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy InsertArtistsOfSongsRequestItem
-> Declare (Definitions Schema) NamedSchema
ToSchema)
newtype InsertArtistsOfSongsRequest = InsertArtistsOfSongsRequest
  { InsertArtistsOfSongsRequest -> [InsertArtistsOfSongsRequestItem]
songArtists :: [InsertArtistsOfSongsRequestItem]
  }
  deriving (InsertArtistsOfSongsRequest -> InsertArtistsOfSongsRequest -> Bool
(InsertArtistsOfSongsRequest
 -> InsertArtistsOfSongsRequest -> Bool)
-> (InsertArtistsOfSongsRequest
    -> InsertArtistsOfSongsRequest -> Bool)
-> Eq InsertArtistsOfSongsRequest
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InsertArtistsOfSongsRequest -> InsertArtistsOfSongsRequest -> Bool
== :: InsertArtistsOfSongsRequest -> InsertArtistsOfSongsRequest -> Bool
$c/= :: InsertArtistsOfSongsRequest -> InsertArtistsOfSongsRequest -> Bool
/= :: InsertArtistsOfSongsRequest -> InsertArtistsOfSongsRequest -> Bool
Eq, Int -> InsertArtistsOfSongsRequest -> ShowS
[InsertArtistsOfSongsRequest] -> ShowS
InsertArtistsOfSongsRequest -> String
(Int -> InsertArtistsOfSongsRequest -> ShowS)
-> (InsertArtistsOfSongsRequest -> String)
-> ([InsertArtistsOfSongsRequest] -> ShowS)
-> Show InsertArtistsOfSongsRequest
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InsertArtistsOfSongsRequest -> ShowS
showsPrec :: Int -> InsertArtistsOfSongsRequest -> ShowS
$cshow :: InsertArtistsOfSongsRequest -> String
show :: InsertArtistsOfSongsRequest -> String
$cshowList :: [InsertArtistsOfSongsRequest] -> ShowS
showList :: [InsertArtistsOfSongsRequest] -> ShowS
Show, (forall x.
 InsertArtistsOfSongsRequest -> Rep InsertArtistsOfSongsRequest x)
-> (forall x.
    Rep InsertArtistsOfSongsRequest x -> InsertArtistsOfSongsRequest)
-> Generic InsertArtistsOfSongsRequest
forall x.
Rep InsertArtistsOfSongsRequest x -> InsertArtistsOfSongsRequest
forall x.
InsertArtistsOfSongsRequest -> Rep InsertArtistsOfSongsRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
InsertArtistsOfSongsRequest -> Rep InsertArtistsOfSongsRequest x
from :: forall x.
InsertArtistsOfSongsRequest -> Rep InsertArtistsOfSongsRequest x
$cto :: forall x.
Rep InsertArtistsOfSongsRequest x -> InsertArtistsOfSongsRequest
to :: forall x.
Rep InsertArtistsOfSongsRequest x -> InsertArtistsOfSongsRequest
Generic)
  deriving anyclass (Maybe InsertArtistsOfSongsRequest
Value -> Parser [InsertArtistsOfSongsRequest]
Value -> Parser InsertArtistsOfSongsRequest
(Value -> Parser InsertArtistsOfSongsRequest)
-> (Value -> Parser [InsertArtistsOfSongsRequest])
-> Maybe InsertArtistsOfSongsRequest
-> FromJSON InsertArtistsOfSongsRequest
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser InsertArtistsOfSongsRequest
parseJSON :: Value -> Parser InsertArtistsOfSongsRequest
$cparseJSONList :: Value -> Parser [InsertArtistsOfSongsRequest]
parseJSONList :: Value -> Parser [InsertArtistsOfSongsRequest]
$comittedField :: Maybe InsertArtistsOfSongsRequest
omittedField :: Maybe InsertArtistsOfSongsRequest
FromJSON, [InsertArtistsOfSongsRequest] -> Value
[InsertArtistsOfSongsRequest] -> Encoding
InsertArtistsOfSongsRequest -> Bool
InsertArtistsOfSongsRequest -> Value
InsertArtistsOfSongsRequest -> Encoding
(InsertArtistsOfSongsRequest -> Value)
-> (InsertArtistsOfSongsRequest -> Encoding)
-> ([InsertArtistsOfSongsRequest] -> Value)
-> ([InsertArtistsOfSongsRequest] -> Encoding)
-> (InsertArtistsOfSongsRequest -> Bool)
-> ToJSON InsertArtistsOfSongsRequest
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: InsertArtistsOfSongsRequest -> Value
toJSON :: InsertArtistsOfSongsRequest -> Value
$ctoEncoding :: InsertArtistsOfSongsRequest -> Encoding
toEncoding :: InsertArtistsOfSongsRequest -> Encoding
$ctoJSONList :: [InsertArtistsOfSongsRequest] -> Value
toJSONList :: [InsertArtistsOfSongsRequest] -> Value
$ctoEncodingList :: [InsertArtistsOfSongsRequest] -> Encoding
toEncodingList :: [InsertArtistsOfSongsRequest] -> Encoding
$comitField :: InsertArtistsOfSongsRequest -> Bool
omitField :: InsertArtistsOfSongsRequest -> Bool
ToJSON, Typeable InsertArtistsOfSongsRequest
Typeable InsertArtistsOfSongsRequest =>
(Proxy InsertArtistsOfSongsRequest
 -> Declare (Definitions Schema) NamedSchema)
-> ToSchema InsertArtistsOfSongsRequest
Proxy InsertArtistsOfSongsRequest
-> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy InsertArtistsOfSongsRequest
-> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy InsertArtistsOfSongsRequest
-> Declare (Definitions Schema) NamedSchema
ToSchema)
makeFieldLabelsNoPrefix ''InsertArtistsOfSongsRequest
makeFieldLabelsNoPrefix ''InsertArtistsOfSongsRequestItem
newtype SongArtworkOrderUpdateRequest = SongArtworkOrderUpdateRequest
  { SongArtworkOrderUpdateRequest -> [SongArtworkOrderUpdate]
songArtworkOrders :: [SongArtworkOrderUpdate]
  }
  deriving (SongArtworkOrderUpdateRequest
-> SongArtworkOrderUpdateRequest -> Bool
(SongArtworkOrderUpdateRequest
 -> SongArtworkOrderUpdateRequest -> Bool)
-> (SongArtworkOrderUpdateRequest
    -> SongArtworkOrderUpdateRequest -> Bool)
-> Eq SongArtworkOrderUpdateRequest
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SongArtworkOrderUpdateRequest
-> SongArtworkOrderUpdateRequest -> Bool
== :: SongArtworkOrderUpdateRequest
-> SongArtworkOrderUpdateRequest -> Bool
$c/= :: SongArtworkOrderUpdateRequest
-> SongArtworkOrderUpdateRequest -> Bool
/= :: SongArtworkOrderUpdateRequest
-> SongArtworkOrderUpdateRequest -> Bool
Eq, Int -> SongArtworkOrderUpdateRequest -> ShowS
[SongArtworkOrderUpdateRequest] -> ShowS
SongArtworkOrderUpdateRequest -> String
(Int -> SongArtworkOrderUpdateRequest -> ShowS)
-> (SongArtworkOrderUpdateRequest -> String)
-> ([SongArtworkOrderUpdateRequest] -> ShowS)
-> Show SongArtworkOrderUpdateRequest
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SongArtworkOrderUpdateRequest -> ShowS
showsPrec :: Int -> SongArtworkOrderUpdateRequest -> ShowS
$cshow :: SongArtworkOrderUpdateRequest -> String
show :: SongArtworkOrderUpdateRequest -> String
$cshowList :: [SongArtworkOrderUpdateRequest] -> ShowS
showList :: [SongArtworkOrderUpdateRequest] -> ShowS
Show, (forall x.
 SongArtworkOrderUpdateRequest
 -> Rep SongArtworkOrderUpdateRequest x)
-> (forall x.
    Rep SongArtworkOrderUpdateRequest x
    -> SongArtworkOrderUpdateRequest)
-> Generic SongArtworkOrderUpdateRequest
forall x.
Rep SongArtworkOrderUpdateRequest x
-> SongArtworkOrderUpdateRequest
forall x.
SongArtworkOrderUpdateRequest
-> Rep SongArtworkOrderUpdateRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
SongArtworkOrderUpdateRequest
-> Rep SongArtworkOrderUpdateRequest x
from :: forall x.
SongArtworkOrderUpdateRequest
-> Rep SongArtworkOrderUpdateRequest x
$cto :: forall x.
Rep SongArtworkOrderUpdateRequest x
-> SongArtworkOrderUpdateRequest
to :: forall x.
Rep SongArtworkOrderUpdateRequest x
-> SongArtworkOrderUpdateRequest
Generic)
  deriving anyclass (Maybe SongArtworkOrderUpdateRequest
Value -> Parser [SongArtworkOrderUpdateRequest]
Value -> Parser SongArtworkOrderUpdateRequest
(Value -> Parser SongArtworkOrderUpdateRequest)
-> (Value -> Parser [SongArtworkOrderUpdateRequest])
-> Maybe SongArtworkOrderUpdateRequest
-> FromJSON SongArtworkOrderUpdateRequest
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser SongArtworkOrderUpdateRequest
parseJSON :: Value -> Parser SongArtworkOrderUpdateRequest
$cparseJSONList :: Value -> Parser [SongArtworkOrderUpdateRequest]
parseJSONList :: Value -> Parser [SongArtworkOrderUpdateRequest]
$comittedField :: Maybe SongArtworkOrderUpdateRequest
omittedField :: Maybe SongArtworkOrderUpdateRequest
FromJSON, [SongArtworkOrderUpdateRequest] -> Value
[SongArtworkOrderUpdateRequest] -> Encoding
SongArtworkOrderUpdateRequest -> Bool
SongArtworkOrderUpdateRequest -> Value
SongArtworkOrderUpdateRequest -> Encoding
(SongArtworkOrderUpdateRequest -> Value)
-> (SongArtworkOrderUpdateRequest -> Encoding)
-> ([SongArtworkOrderUpdateRequest] -> Value)
-> ([SongArtworkOrderUpdateRequest] -> Encoding)
-> (SongArtworkOrderUpdateRequest -> Bool)
-> ToJSON SongArtworkOrderUpdateRequest
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: SongArtworkOrderUpdateRequest -> Value
toJSON :: SongArtworkOrderUpdateRequest -> Value
$ctoEncoding :: SongArtworkOrderUpdateRequest -> Encoding
toEncoding :: SongArtworkOrderUpdateRequest -> Encoding
$ctoJSONList :: [SongArtworkOrderUpdateRequest] -> Value
toJSONList :: [SongArtworkOrderUpdateRequest] -> Value
$ctoEncodingList :: [SongArtworkOrderUpdateRequest] -> Encoding
toEncodingList :: [SongArtworkOrderUpdateRequest] -> Encoding
$comitField :: SongArtworkOrderUpdateRequest -> Bool
omitField :: SongArtworkOrderUpdateRequest -> Bool
ToJSON, Typeable SongArtworkOrderUpdateRequest
Typeable SongArtworkOrderUpdateRequest =>
(Proxy SongArtworkOrderUpdateRequest
 -> Declare (Definitions Schema) NamedSchema)
-> ToSchema SongArtworkOrderUpdateRequest
Proxy SongArtworkOrderUpdateRequest
-> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy SongArtworkOrderUpdateRequest
-> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy SongArtworkOrderUpdateRequest
-> Declare (Definitions Schema) NamedSchema
ToSchema)
makeFieldLabelsNoPrefix ''SongArtworkOrderUpdateRequest
newtype SongDeltaRequest = SongDeltaRequest
  { SongDeltaRequest -> [SongDelta]
songDeltas :: [SongDelta]
  }
  deriving (SongDeltaRequest -> SongDeltaRequest -> Bool
(SongDeltaRequest -> SongDeltaRequest -> Bool)
-> (SongDeltaRequest -> SongDeltaRequest -> Bool)
-> Eq SongDeltaRequest
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SongDeltaRequest -> SongDeltaRequest -> Bool
== :: SongDeltaRequest -> SongDeltaRequest -> Bool
$c/= :: SongDeltaRequest -> SongDeltaRequest -> Bool
/= :: SongDeltaRequest -> SongDeltaRequest -> Bool
Eq, Int -> SongDeltaRequest -> ShowS
[SongDeltaRequest] -> ShowS
SongDeltaRequest -> String
(Int -> SongDeltaRequest -> ShowS)
-> (SongDeltaRequest -> String)
-> ([SongDeltaRequest] -> ShowS)
-> Show SongDeltaRequest
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SongDeltaRequest -> ShowS
showsPrec :: Int -> SongDeltaRequest -> ShowS
$cshow :: SongDeltaRequest -> String
show :: SongDeltaRequest -> String
$cshowList :: [SongDeltaRequest] -> ShowS
showList :: [SongDeltaRequest] -> ShowS
Show, (forall x. SongDeltaRequest -> Rep SongDeltaRequest x)
-> (forall x. Rep SongDeltaRequest x -> SongDeltaRequest)
-> Generic SongDeltaRequest
forall x. Rep SongDeltaRequest x -> SongDeltaRequest
forall x. SongDeltaRequest -> Rep SongDeltaRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SongDeltaRequest -> Rep SongDeltaRequest x
from :: forall x. SongDeltaRequest -> Rep SongDeltaRequest x
$cto :: forall x. Rep SongDeltaRequest x -> SongDeltaRequest
to :: forall x. Rep SongDeltaRequest x -> SongDeltaRequest
Generic)
  deriving anyclass (Maybe SongDeltaRequest
Value -> Parser [SongDeltaRequest]
Value -> Parser SongDeltaRequest
(Value -> Parser SongDeltaRequest)
-> (Value -> Parser [SongDeltaRequest])
-> Maybe SongDeltaRequest
-> FromJSON SongDeltaRequest
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser SongDeltaRequest
parseJSON :: Value -> Parser SongDeltaRequest
$cparseJSONList :: Value -> Parser [SongDeltaRequest]
parseJSONList :: Value -> Parser [SongDeltaRequest]
$comittedField :: Maybe SongDeltaRequest
omittedField :: Maybe SongDeltaRequest
FromJSON, [SongDeltaRequest] -> Value
[SongDeltaRequest] -> Encoding
SongDeltaRequest -> Bool
SongDeltaRequest -> Value
SongDeltaRequest -> Encoding
(SongDeltaRequest -> Value)
-> (SongDeltaRequest -> Encoding)
-> ([SongDeltaRequest] -> Value)
-> ([SongDeltaRequest] -> Encoding)
-> (SongDeltaRequest -> Bool)
-> ToJSON SongDeltaRequest
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: SongDeltaRequest -> Value
toJSON :: SongDeltaRequest -> Value
$ctoEncoding :: SongDeltaRequest -> Encoding
toEncoding :: SongDeltaRequest -> Encoding
$ctoJSONList :: [SongDeltaRequest] -> Value
toJSONList :: [SongDeltaRequest] -> Value
$ctoEncodingList :: [SongDeltaRequest] -> Encoding
toEncodingList :: [SongDeltaRequest] -> Encoding
$comitField :: SongDeltaRequest -> Bool
omitField :: SongDeltaRequest -> Bool
ToJSON, Typeable SongDeltaRequest
Typeable SongDeltaRequest =>
(Proxy SongDeltaRequest
 -> Declare (Definitions Schema) NamedSchema)
-> ToSchema SongDeltaRequest
Proxy SongDeltaRequest -> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy SongDeltaRequest -> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy SongDeltaRequest -> Declare (Definitions Schema) NamedSchema
ToSchema)
makeFieldLabelsNoPrefix ''SongDeltaRequest
newtype SongContentDeltaRequest = SongContentDeltaRequest
  { SongContentDeltaRequest -> [SongContentDelta]
songContentDeltas :: [SongContentDelta]
  }
  deriving (SongContentDeltaRequest -> SongContentDeltaRequest -> Bool
(SongContentDeltaRequest -> SongContentDeltaRequest -> Bool)
-> (SongContentDeltaRequest -> SongContentDeltaRequest -> Bool)
-> Eq SongContentDeltaRequest
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SongContentDeltaRequest -> SongContentDeltaRequest -> Bool
== :: SongContentDeltaRequest -> SongContentDeltaRequest -> Bool
$c/= :: SongContentDeltaRequest -> SongContentDeltaRequest -> Bool
/= :: SongContentDeltaRequest -> SongContentDeltaRequest -> Bool
Eq, Int -> SongContentDeltaRequest -> ShowS
[SongContentDeltaRequest] -> ShowS
SongContentDeltaRequest -> String
(Int -> SongContentDeltaRequest -> ShowS)
-> (SongContentDeltaRequest -> String)
-> ([SongContentDeltaRequest] -> ShowS)
-> Show SongContentDeltaRequest
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SongContentDeltaRequest -> ShowS
showsPrec :: Int -> SongContentDeltaRequest -> ShowS
$cshow :: SongContentDeltaRequest -> String
show :: SongContentDeltaRequest -> String
$cshowList :: [SongContentDeltaRequest] -> ShowS
showList :: [SongContentDeltaRequest] -> ShowS
Show, (forall x.
 SongContentDeltaRequest -> Rep SongContentDeltaRequest x)
-> (forall x.
    Rep SongContentDeltaRequest x -> SongContentDeltaRequest)
-> Generic SongContentDeltaRequest
forall x. Rep SongContentDeltaRequest x -> SongContentDeltaRequest
forall x. SongContentDeltaRequest -> Rep SongContentDeltaRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SongContentDeltaRequest -> Rep SongContentDeltaRequest x
from :: forall x. SongContentDeltaRequest -> Rep SongContentDeltaRequest x
$cto :: forall x. Rep SongContentDeltaRequest x -> SongContentDeltaRequest
to :: forall x. Rep SongContentDeltaRequest x -> SongContentDeltaRequest
Generic)
  deriving anyclass (Maybe SongContentDeltaRequest
Value -> Parser [SongContentDeltaRequest]
Value -> Parser SongContentDeltaRequest
(Value -> Parser SongContentDeltaRequest)
-> (Value -> Parser [SongContentDeltaRequest])
-> Maybe SongContentDeltaRequest
-> FromJSON SongContentDeltaRequest
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser SongContentDeltaRequest
parseJSON :: Value -> Parser SongContentDeltaRequest
$cparseJSONList :: Value -> Parser [SongContentDeltaRequest]
parseJSONList :: Value -> Parser [SongContentDeltaRequest]
$comittedField :: Maybe SongContentDeltaRequest
omittedField :: Maybe SongContentDeltaRequest
FromJSON, [SongContentDeltaRequest] -> Value
[SongContentDeltaRequest] -> Encoding
SongContentDeltaRequest -> Bool
SongContentDeltaRequest -> Value
SongContentDeltaRequest -> Encoding
(SongContentDeltaRequest -> Value)
-> (SongContentDeltaRequest -> Encoding)
-> ([SongContentDeltaRequest] -> Value)
-> ([SongContentDeltaRequest] -> Encoding)
-> (SongContentDeltaRequest -> Bool)
-> ToJSON SongContentDeltaRequest
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: SongContentDeltaRequest -> Value
toJSON :: SongContentDeltaRequest -> Value
$ctoEncoding :: SongContentDeltaRequest -> Encoding
toEncoding :: SongContentDeltaRequest -> Encoding
$ctoJSONList :: [SongContentDeltaRequest] -> Value
toJSONList :: [SongContentDeltaRequest] -> Value
$ctoEncodingList :: [SongContentDeltaRequest] -> Encoding
toEncodingList :: [SongContentDeltaRequest] -> Encoding
$comitField :: SongContentDeltaRequest -> Bool
omitField :: SongContentDeltaRequest -> Bool
ToJSON, Typeable SongContentDeltaRequest
Typeable SongContentDeltaRequest =>
(Proxy SongContentDeltaRequest
 -> Declare (Definitions Schema) NamedSchema)
-> ToSchema SongContentDeltaRequest
Proxy SongContentDeltaRequest
-> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy SongContentDeltaRequest
-> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy SongContentDeltaRequest
-> Declare (Definitions Schema) NamedSchema
ToSchema)
makeFieldLabelsNoPrefix ''SongContentDeltaRequest
data InsertSongContentsRequestItem = InsertSongContentsRequestItem
  { InsertSongContentsRequestItem -> UUID
songIdentifier :: UUID,
    InsertSongContentsRequestItem -> Text
versionName :: Text,
    InsertSongContentsRequestItem -> Text
instrumentType :: Text,
    InsertSongContentsRequestItem -> Maybe Text
asciiLegend :: Maybe Text,
    InsertSongContentsRequestItem -> Maybe Text
asciiContents :: Maybe Text,
    InsertSongContentsRequestItem -> Maybe Text
pdfContents :: Maybe Text,
    InsertSongContentsRequestItem -> Maybe Text
guitarProContents :: Maybe Text
  }
  deriving (InsertSongContentsRequestItem
-> InsertSongContentsRequestItem -> Bool
(InsertSongContentsRequestItem
 -> InsertSongContentsRequestItem -> Bool)
-> (InsertSongContentsRequestItem
    -> InsertSongContentsRequestItem -> Bool)
-> Eq InsertSongContentsRequestItem
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InsertSongContentsRequestItem
-> InsertSongContentsRequestItem -> Bool
== :: InsertSongContentsRequestItem
-> InsertSongContentsRequestItem -> Bool
$c/= :: InsertSongContentsRequestItem
-> InsertSongContentsRequestItem -> Bool
/= :: InsertSongContentsRequestItem
-> InsertSongContentsRequestItem -> Bool
Eq, Int -> InsertSongContentsRequestItem -> ShowS
[InsertSongContentsRequestItem] -> ShowS
InsertSongContentsRequestItem -> String
(Int -> InsertSongContentsRequestItem -> ShowS)
-> (InsertSongContentsRequestItem -> String)
-> ([InsertSongContentsRequestItem] -> ShowS)
-> Show InsertSongContentsRequestItem
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InsertSongContentsRequestItem -> ShowS
showsPrec :: Int -> InsertSongContentsRequestItem -> ShowS
$cshow :: InsertSongContentsRequestItem -> String
show :: InsertSongContentsRequestItem -> String
$cshowList :: [InsertSongContentsRequestItem] -> ShowS
showList :: [InsertSongContentsRequestItem] -> ShowS
Show, (forall x.
 InsertSongContentsRequestItem
 -> Rep InsertSongContentsRequestItem x)
-> (forall x.
    Rep InsertSongContentsRequestItem x
    -> InsertSongContentsRequestItem)
-> Generic InsertSongContentsRequestItem
forall x.
Rep InsertSongContentsRequestItem x
-> InsertSongContentsRequestItem
forall x.
InsertSongContentsRequestItem
-> Rep InsertSongContentsRequestItem x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
InsertSongContentsRequestItem
-> Rep InsertSongContentsRequestItem x
from :: forall x.
InsertSongContentsRequestItem
-> Rep InsertSongContentsRequestItem x
$cto :: forall x.
Rep InsertSongContentsRequestItem x
-> InsertSongContentsRequestItem
to :: forall x.
Rep InsertSongContentsRequestItem x
-> InsertSongContentsRequestItem
Generic, Maybe InsertSongContentsRequestItem
Value -> Parser [InsertSongContentsRequestItem]
Value -> Parser InsertSongContentsRequestItem
(Value -> Parser InsertSongContentsRequestItem)
-> (Value -> Parser [InsertSongContentsRequestItem])
-> Maybe InsertSongContentsRequestItem
-> FromJSON InsertSongContentsRequestItem
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser InsertSongContentsRequestItem
parseJSON :: Value -> Parser InsertSongContentsRequestItem
$cparseJSONList :: Value -> Parser [InsertSongContentsRequestItem]
parseJSONList :: Value -> Parser [InsertSongContentsRequestItem]
$comittedField :: Maybe InsertSongContentsRequestItem
omittedField :: Maybe InsertSongContentsRequestItem
FromJSON, [InsertSongContentsRequestItem] -> Value
[InsertSongContentsRequestItem] -> Encoding
InsertSongContentsRequestItem -> Bool
InsertSongContentsRequestItem -> Value
InsertSongContentsRequestItem -> Encoding
(InsertSongContentsRequestItem -> Value)
-> (InsertSongContentsRequestItem -> Encoding)
-> ([InsertSongContentsRequestItem] -> Value)
-> ([InsertSongContentsRequestItem] -> Encoding)
-> (InsertSongContentsRequestItem -> Bool)
-> ToJSON InsertSongContentsRequestItem
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: InsertSongContentsRequestItem -> Value
toJSON :: InsertSongContentsRequestItem -> Value
$ctoEncoding :: InsertSongContentsRequestItem -> Encoding
toEncoding :: InsertSongContentsRequestItem -> Encoding
$ctoJSONList :: [InsertSongContentsRequestItem] -> Value
toJSONList :: [InsertSongContentsRequestItem] -> Value
$ctoEncodingList :: [InsertSongContentsRequestItem] -> Encoding
toEncodingList :: [InsertSongContentsRequestItem] -> Encoding
$comitField :: InsertSongContentsRequestItem -> Bool
omitField :: InsertSongContentsRequestItem -> Bool
ToJSON, Typeable InsertSongContentsRequestItem
Typeable InsertSongContentsRequestItem =>
(Proxy InsertSongContentsRequestItem
 -> Declare (Definitions Schema) NamedSchema)
-> ToSchema InsertSongContentsRequestItem
Proxy InsertSongContentsRequestItem
-> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy InsertSongContentsRequestItem
-> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy InsertSongContentsRequestItem
-> Declare (Definitions Schema) NamedSchema
ToSchema)
makeFieldLabelsNoPrefix ''InsertSongContentsRequestItem
newtype InsertSongContentsRequest = InsertSongContentsRequest
  { InsertSongContentsRequest -> [InsertSongContentsRequestItem]
songContents :: [InsertSongContentsRequestItem]
  }
  deriving (InsertSongContentsRequest -> InsertSongContentsRequest -> Bool
(InsertSongContentsRequest -> InsertSongContentsRequest -> Bool)
-> (InsertSongContentsRequest -> InsertSongContentsRequest -> Bool)
-> Eq InsertSongContentsRequest
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InsertSongContentsRequest -> InsertSongContentsRequest -> Bool
== :: InsertSongContentsRequest -> InsertSongContentsRequest -> Bool
$c/= :: InsertSongContentsRequest -> InsertSongContentsRequest -> Bool
/= :: InsertSongContentsRequest -> InsertSongContentsRequest -> Bool
Eq, Int -> InsertSongContentsRequest -> ShowS
[InsertSongContentsRequest] -> ShowS
InsertSongContentsRequest -> String
(Int -> InsertSongContentsRequest -> ShowS)
-> (InsertSongContentsRequest -> String)
-> ([InsertSongContentsRequest] -> ShowS)
-> Show InsertSongContentsRequest
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InsertSongContentsRequest -> ShowS
showsPrec :: Int -> InsertSongContentsRequest -> ShowS
$cshow :: InsertSongContentsRequest -> String
show :: InsertSongContentsRequest -> String
$cshowList :: [InsertSongContentsRequest] -> ShowS
showList :: [InsertSongContentsRequest] -> ShowS
Show, (forall x.
 InsertSongContentsRequest -> Rep InsertSongContentsRequest x)
-> (forall x.
    Rep InsertSongContentsRequest x -> InsertSongContentsRequest)
-> Generic InsertSongContentsRequest
forall x.
Rep InsertSongContentsRequest x -> InsertSongContentsRequest
forall x.
InsertSongContentsRequest -> Rep InsertSongContentsRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
InsertSongContentsRequest -> Rep InsertSongContentsRequest x
from :: forall x.
InsertSongContentsRequest -> Rep InsertSongContentsRequest x
$cto :: forall x.
Rep InsertSongContentsRequest x -> InsertSongContentsRequest
to :: forall x.
Rep InsertSongContentsRequest x -> InsertSongContentsRequest
Generic)
  deriving anyclass (Maybe InsertSongContentsRequest
Value -> Parser [InsertSongContentsRequest]
Value -> Parser InsertSongContentsRequest
(Value -> Parser InsertSongContentsRequest)
-> (Value -> Parser [InsertSongContentsRequest])
-> Maybe InsertSongContentsRequest
-> FromJSON InsertSongContentsRequest
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser InsertSongContentsRequest
parseJSON :: Value -> Parser InsertSongContentsRequest
$cparseJSONList :: Value -> Parser [InsertSongContentsRequest]
parseJSONList :: Value -> Parser [InsertSongContentsRequest]
$comittedField :: Maybe InsertSongContentsRequest
omittedField :: Maybe InsertSongContentsRequest
FromJSON, [InsertSongContentsRequest] -> Value
[InsertSongContentsRequest] -> Encoding
InsertSongContentsRequest -> Bool
InsertSongContentsRequest -> Value
InsertSongContentsRequest -> Encoding
(InsertSongContentsRequest -> Value)
-> (InsertSongContentsRequest -> Encoding)
-> ([InsertSongContentsRequest] -> Value)
-> ([InsertSongContentsRequest] -> Encoding)
-> (InsertSongContentsRequest -> Bool)
-> ToJSON InsertSongContentsRequest
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: InsertSongContentsRequest -> Value
toJSON :: InsertSongContentsRequest -> Value
$ctoEncoding :: InsertSongContentsRequest -> Encoding
toEncoding :: InsertSongContentsRequest -> Encoding
$ctoJSONList :: [InsertSongContentsRequest] -> Value
toJSONList :: [InsertSongContentsRequest] -> Value
$ctoEncodingList :: [InsertSongContentsRequest] -> Encoding
toEncodingList :: [InsertSongContentsRequest] -> Encoding
$comitField :: InsertSongContentsRequest -> Bool
omitField :: InsertSongContentsRequest -> Bool
ToJSON, Typeable InsertSongContentsRequest
Typeable InsertSongContentsRequest =>
(Proxy InsertSongContentsRequest
 -> Declare (Definitions Schema) NamedSchema)
-> ToSchema InsertSongContentsRequest
Proxy InsertSongContentsRequest
-> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy InsertSongContentsRequest
-> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy InsertSongContentsRequest
-> Declare (Definitions Schema) NamedSchema
ToSchema)
makeFieldLabelsNoPrefix ''InsertSongContentsRequest
data InsertSongContentsCommandResponse = InsertSongContentsCommandResponse
  { InsertSongContentsCommandResponse -> Map UUID SongContent
songContents :: Map UUID SongContent,
    InsertSongContentsCommandResponse -> Map Text (Validation [Text])
validationResults :: Map Text ValidationResult
  }
  deriving (InsertSongContentsCommandResponse
-> InsertSongContentsCommandResponse -> Bool
(InsertSongContentsCommandResponse
 -> InsertSongContentsCommandResponse -> Bool)
-> (InsertSongContentsCommandResponse
    -> InsertSongContentsCommandResponse -> Bool)
-> Eq InsertSongContentsCommandResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InsertSongContentsCommandResponse
-> InsertSongContentsCommandResponse -> Bool
== :: InsertSongContentsCommandResponse
-> InsertSongContentsCommandResponse -> Bool
$c/= :: InsertSongContentsCommandResponse
-> InsertSongContentsCommandResponse -> Bool
/= :: InsertSongContentsCommandResponse
-> InsertSongContentsCommandResponse -> Bool
Eq, Int -> InsertSongContentsCommandResponse -> ShowS
[InsertSongContentsCommandResponse] -> ShowS
InsertSongContentsCommandResponse -> String
(Int -> InsertSongContentsCommandResponse -> ShowS)
-> (InsertSongContentsCommandResponse -> String)
-> ([InsertSongContentsCommandResponse] -> ShowS)
-> Show InsertSongContentsCommandResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InsertSongContentsCommandResponse -> ShowS
showsPrec :: Int -> InsertSongContentsCommandResponse -> ShowS
$cshow :: InsertSongContentsCommandResponse -> String
show :: InsertSongContentsCommandResponse -> String
$cshowList :: [InsertSongContentsCommandResponse] -> ShowS
showList :: [InsertSongContentsCommandResponse] -> ShowS
Show, (forall x.
 InsertSongContentsCommandResponse
 -> Rep InsertSongContentsCommandResponse x)
-> (forall x.
    Rep InsertSongContentsCommandResponse x
    -> InsertSongContentsCommandResponse)
-> Generic InsertSongContentsCommandResponse
forall x.
Rep InsertSongContentsCommandResponse x
-> InsertSongContentsCommandResponse
forall x.
InsertSongContentsCommandResponse
-> Rep InsertSongContentsCommandResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
InsertSongContentsCommandResponse
-> Rep InsertSongContentsCommandResponse x
from :: forall x.
InsertSongContentsCommandResponse
-> Rep InsertSongContentsCommandResponse x
$cto :: forall x.
Rep InsertSongContentsCommandResponse x
-> InsertSongContentsCommandResponse
to :: forall x.
Rep InsertSongContentsCommandResponse x
-> InsertSongContentsCommandResponse
Generic, Maybe InsertSongContentsCommandResponse
Value -> Parser [InsertSongContentsCommandResponse]
Value -> Parser InsertSongContentsCommandResponse
(Value -> Parser InsertSongContentsCommandResponse)
-> (Value -> Parser [InsertSongContentsCommandResponse])
-> Maybe InsertSongContentsCommandResponse
-> FromJSON InsertSongContentsCommandResponse
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser InsertSongContentsCommandResponse
parseJSON :: Value -> Parser InsertSongContentsCommandResponse
$cparseJSONList :: Value -> Parser [InsertSongContentsCommandResponse]
parseJSONList :: Value -> Parser [InsertSongContentsCommandResponse]
$comittedField :: Maybe InsertSongContentsCommandResponse
omittedField :: Maybe InsertSongContentsCommandResponse
FromJSON, [InsertSongContentsCommandResponse] -> Value
[InsertSongContentsCommandResponse] -> Encoding
InsertSongContentsCommandResponse -> Bool
InsertSongContentsCommandResponse -> Value
InsertSongContentsCommandResponse -> Encoding
(InsertSongContentsCommandResponse -> Value)
-> (InsertSongContentsCommandResponse -> Encoding)
-> ([InsertSongContentsCommandResponse] -> Value)
-> ([InsertSongContentsCommandResponse] -> Encoding)
-> (InsertSongContentsCommandResponse -> Bool)
-> ToJSON InsertSongContentsCommandResponse
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: InsertSongContentsCommandResponse -> Value
toJSON :: InsertSongContentsCommandResponse -> Value
$ctoEncoding :: InsertSongContentsCommandResponse -> Encoding
toEncoding :: InsertSongContentsCommandResponse -> Encoding
$ctoJSONList :: [InsertSongContentsCommandResponse] -> Value
toJSONList :: [InsertSongContentsCommandResponse] -> Value
$ctoEncodingList :: [InsertSongContentsCommandResponse] -> Encoding
toEncodingList :: [InsertSongContentsCommandResponse] -> Encoding
$comitField :: InsertSongContentsCommandResponse -> Bool
omitField :: InsertSongContentsCommandResponse -> Bool
ToJSON, Typeable InsertSongContentsCommandResponse
Typeable InsertSongContentsCommandResponse =>
(Proxy InsertSongContentsCommandResponse
 -> Declare (Definitions Schema) NamedSchema)
-> ToSchema InsertSongContentsCommandResponse
Proxy InsertSongContentsCommandResponse
-> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy InsertSongContentsCommandResponse
-> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy InsertSongContentsCommandResponse
-> Declare (Definitions Schema) NamedSchema
ToSchema)
makeFieldLabelsNoPrefix ''InsertSongContentsCommandResponse
data SongError
  = ValidationFailedError (Map Text ValidationResult)
  | AccessUnauthorizedError
  | SomeError Text
  deriving (Int -> SongError -> ShowS
[SongError] -> ShowS
SongError -> String
(Int -> SongError -> ShowS)
-> (SongError -> String)
-> ([SongError] -> ShowS)
-> Show SongError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SongError -> ShowS
showsPrec :: Int -> SongError -> ShowS
$cshow :: SongError -> String
show :: SongError -> String
$cshowList :: [SongError] -> ShowS
showList :: [SongError] -> ShowS
Show, SongError -> SongError -> Bool
(SongError -> SongError -> Bool)
-> (SongError -> SongError -> Bool) -> Eq SongError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SongError -> SongError -> Bool
== :: SongError -> SongError -> Bool
$c/= :: SongError -> SongError -> Bool
/= :: SongError -> SongError -> Bool
Eq, (forall x. SongError -> Rep SongError x)
-> (forall x. Rep SongError x -> SongError) -> Generic SongError
forall x. Rep SongError x -> SongError
forall x. SongError -> Rep SongError x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SongError -> Rep SongError x
from :: forall x. SongError -> Rep SongError x
$cto :: forall x. Rep SongError x -> SongError
to :: forall x. Rep SongError x -> SongError
Generic)
ifAllValid ::
  (Applicative f) =>
  Map Text (Validation [Text]) ->
  f (Either SongError b) ->
  f (Either SongError b)
ifAllValid :: forall (f :: * -> *) b.
Applicative f =>
Map Text (Validation [Text])
-> f (Either SongError b) -> f (Either SongError b)
ifAllValid Map Text (Validation [Text])
validationResults f (Either SongError b)
eff = do
  if Map Text (Validation [Text]) -> Bool
forall a. Map Text a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (Map Text (Validation [Text]) -> Bool)
-> Map Text (Validation [Text]) -> Bool
forall a b. (a -> b) -> a -> b
$ Map Text (Validation [Text]) -> Map Text (Validation [Text])
forall err. Map Text (Validation err) -> Map Text (Validation err)
filterFailedValidations Map Text (Validation [Text])
validationResults
    then do f (Either SongError b)
eff
    else Either SongError b -> f (Either SongError b)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either SongError b -> f (Either SongError b))
-> (SongError -> Either SongError b)
-> SongError
-> f (Either SongError b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SongError -> Either SongError b
forall a b. a -> Either a b
Left (SongError -> f (Either SongError b))
-> SongError -> f (Either SongError b)
forall a b. (a -> b) -> a -> b
$ Map Text (Validation [Text]) -> SongError
ValidationFailedError Map Text (Validation [Text])
validationResults