{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE NoFieldSelectors #-}
module WikiMusic.Model.Genre
( Genre (..),
GenreArtwork (..),
GenreComment (..),
GenreOpinion (..),
validateGenre,
validateGenreArtwork,
validateGenreComment,
validateGenreOpinion,
GenreSortOrder (..),
GenreExternalSources (..),
validateGenreExternalSources,
GenreArtworkOrderUpdate (..),
validateGenreArtworkOrderUpdate,
validateGenreDelta,
GenreDelta (..),
Prelude.show,
Prelude.read,
GenreIncludes (..),
EnrichGenreParams (..),
fullEnrichment,
noEnrichment,
parseInclude,
)
where
import Data.Aeson hiding (Success)
import Data.Map qualified as Map
import Data.OpenApi
import Data.Text qualified as T
import Data.Time
import Data.UUID
import Keuringsdienst
import Keuringsdienst.Helpers
import Optics
import Relude
import Text.Read
import WikiMusic.Model.Artwork
import WikiMusic.Model.Comment
import WikiMusic.Model.Opinion
import WikiMusic.Model.Thread
import Prelude qualified
data GenreIncludes = | IncludeOpinions | IncludeArtworks deriving (GenreIncludes -> GenreIncludes -> Bool
(GenreIncludes -> GenreIncludes -> Bool)
-> (GenreIncludes -> GenreIncludes -> Bool) -> Eq GenreIncludes
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GenreIncludes -> GenreIncludes -> Bool
== :: GenreIncludes -> GenreIncludes -> Bool
$c/= :: GenreIncludes -> GenreIncludes -> Bool
/= :: GenreIncludes -> GenreIncludes -> Bool
Eq, (forall x. GenreIncludes -> Rep GenreIncludes x)
-> (forall x. Rep GenreIncludes x -> GenreIncludes)
-> Generic GenreIncludes
forall x. Rep GenreIncludes x -> GenreIncludes
forall x. GenreIncludes -> Rep GenreIncludes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GenreIncludes -> Rep GenreIncludes x
from :: forall x. GenreIncludes -> Rep GenreIncludes x
$cto :: forall x. Rep GenreIncludes x -> GenreIncludes
to :: forall x. Rep GenreIncludes x -> GenreIncludes
Generic, Maybe GenreIncludes
Value -> Parser [GenreIncludes]
Value -> Parser GenreIncludes
(Value -> Parser GenreIncludes)
-> (Value -> Parser [GenreIncludes])
-> Maybe GenreIncludes
-> FromJSON GenreIncludes
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser GenreIncludes
parseJSON :: Value -> Parser GenreIncludes
$cparseJSONList :: Value -> Parser [GenreIncludes]
parseJSONList :: Value -> Parser [GenreIncludes]
$comittedField :: Maybe GenreIncludes
omittedField :: Maybe GenreIncludes
FromJSON, [GenreIncludes] -> Value
[GenreIncludes] -> Encoding
GenreIncludes -> Bool
GenreIncludes -> Value
GenreIncludes -> Encoding
(GenreIncludes -> Value)
-> (GenreIncludes -> Encoding)
-> ([GenreIncludes] -> Value)
-> ([GenreIncludes] -> Encoding)
-> (GenreIncludes -> Bool)
-> ToJSON GenreIncludes
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: GenreIncludes -> Value
toJSON :: GenreIncludes -> Value
$ctoEncoding :: GenreIncludes -> Encoding
toEncoding :: GenreIncludes -> Encoding
$ctoJSONList :: [GenreIncludes] -> Value
toJSONList :: [GenreIncludes] -> Value
$ctoEncodingList :: [GenreIncludes] -> Encoding
toEncodingList :: [GenreIncludes] -> Encoding
$comitField :: GenreIncludes -> Bool
omitField :: GenreIncludes -> Bool
ToJSON, Typeable GenreIncludes
Typeable GenreIncludes =>
(Proxy GenreIncludes -> Declare (Definitions Schema) NamedSchema)
-> ToSchema GenreIncludes
Proxy GenreIncludes -> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy GenreIncludes -> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy GenreIncludes -> Declare (Definitions Schema) NamedSchema
ToSchema)
instance Show GenreIncludes where
show :: GenreIncludes -> String
show GenreIncludes
IncludeComments = String
"comments"
show GenreIncludes
IncludeOpinions = String
"opinions"
show GenreIncludes
IncludeArtworks = String
"artworks"
instance Read GenreIncludes where
readsPrec :: Int -> ReadS GenreIncludes
readsPrec Int
_ String
"comments" = [(GenreIncludes
IncludeComments, String
"")]
readsPrec Int
_ String
"opinions" = [(GenreIncludes
IncludeOpinions, String
"")]
readsPrec Int
_ String
"artworks" = [(GenreIncludes
IncludeArtworks, String
"")]
readsPrec Int
_ String
_ = []
data GenreSortOrder
= DescCreatedAt
| AscCreatedAt
| DescLastEditedAt
| AscLastEditedAt
| DescDisplayName
| AscDisplayName
instance Show GenreSortOrder where
show :: GenreSortOrder -> String
show GenreSortOrder
DescCreatedAt = String
"genres.created_at DESC"
show GenreSortOrder
AscCreatedAt = String
"genres.created_at ASC"
show GenreSortOrder
DescLastEditedAt = String
"genres.last_edited_at DESC"
show GenreSortOrder
AscLastEditedAt = String
"genres.last_edited_at ASC"
show GenreSortOrder
DescDisplayName = String
"genres.display_name DESC"
show GenreSortOrder
AscDisplayName = String
"genres.display_name ASC"
instance Read GenreSortOrder where
readsPrec :: Int -> ReadS GenreSortOrder
readsPrec Int
_ String
"created-at-desc" = [(GenreSortOrder
DescCreatedAt, String
"")]
readsPrec Int
_ String
"created-at-asc" = [(GenreSortOrder
AscCreatedAt, String
"")]
readsPrec Int
_ String
"last-edited-at-desc" = [(GenreSortOrder
DescLastEditedAt, String
"")]
readsPrec Int
_ String
"last-edited-at-asc" = [(GenreSortOrder
AscLastEditedAt, String
"")]
readsPrec Int
_ String
"display-name-desc" = [(GenreSortOrder
DescDisplayName, String
"")]
readsPrec Int
_ String
"display-name-asc" = [(GenreSortOrder
AscDisplayName, String
"")]
readsPrec Int
_ String
_ = []
validateGenreOpinion :: GenreOpinion -> ValidationResult
validateGenreOpinion :: GenreOpinion -> ValidationResult
validateGenreOpinion GenreOpinion
x =
(GenreOpinion
x GenreOpinion -> Optic' A_Lens NoIx GenreOpinion Bool -> Bool
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic A_Lens NoIx GenreOpinion GenreOpinion Opinion Opinion
#opinion Optic A_Lens NoIx GenreOpinion GenreOpinion Opinion Opinion
-> Optic A_Lens NoIx Opinion Opinion Bool Bool
-> Optic' A_Lens NoIx GenreOpinion Bool
forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% Optic A_Lens NoIx Opinion Opinion Bool Bool
#isLike)
Bool -> ValidationRule Bool -> ValidationResult
forall a. a -> ValidationRule a -> ValidationResult
|?| Bool -> ValidationRule Bool
forall a. (Show a, Eq a) => a -> ValidationRule a
isNotEqualTo (GenreOpinion
x GenreOpinion -> Optic' A_Lens NoIx GenreOpinion Bool -> Bool
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic A_Lens NoIx GenreOpinion GenreOpinion Opinion Opinion
#opinion Optic A_Lens NoIx GenreOpinion GenreOpinion Opinion Opinion
-> Optic A_Lens NoIx Opinion Opinion Bool Bool
-> Optic' A_Lens NoIx GenreOpinion Bool
forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% Optic A_Lens NoIx Opinion Opinion Bool Bool
#isDislike)
ValidationResult -> ValidationResult -> ValidationResult
forall a. Semigroup a => a -> a -> a
<> (GenreOpinion
x GenreOpinion -> Optic' A_Lens NoIx GenreOpinion Bool -> Bool
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic A_Lens NoIx GenreOpinion GenreOpinion Opinion Opinion
#opinion Optic A_Lens NoIx GenreOpinion GenreOpinion Opinion Opinion
-> Optic A_Lens NoIx Opinion Opinion Bool Bool
-> Optic' A_Lens NoIx GenreOpinion Bool
forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% Optic A_Lens NoIx Opinion Opinion Bool Bool
#isDislike)
Bool -> ValidationRule Bool -> ValidationResult
forall a. a -> ValidationRule a -> ValidationResult
|?| Bool -> ValidationRule Bool
forall a. (Show a, Eq a) => a -> ValidationRule a
isNotEqualTo (GenreOpinion
x GenreOpinion -> Optic' A_Lens NoIx GenreOpinion Bool -> Bool
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic A_Lens NoIx GenreOpinion GenreOpinion Opinion Opinion
#opinion Optic A_Lens NoIx GenreOpinion GenreOpinion Opinion Opinion
-> Optic A_Lens NoIx Opinion Opinion Bool Bool
-> Optic' A_Lens NoIx GenreOpinion Bool
forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% Optic A_Lens NoIx Opinion Opinion Bool Bool
#isLike)
data GenreOpinion = GenreOpinion
{ GenreOpinion -> UUID
genreIdentifier :: UUID,
GenreOpinion -> Opinion
opinion :: Opinion
}
deriving (GenreOpinion -> GenreOpinion -> Bool
(GenreOpinion -> GenreOpinion -> Bool)
-> (GenreOpinion -> GenreOpinion -> Bool) -> Eq GenreOpinion
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GenreOpinion -> GenreOpinion -> Bool
== :: GenreOpinion -> GenreOpinion -> Bool
$c/= :: GenreOpinion -> GenreOpinion -> Bool
/= :: GenreOpinion -> GenreOpinion -> Bool
Eq, Int -> GenreOpinion -> ShowS
[GenreOpinion] -> ShowS
GenreOpinion -> String
(Int -> GenreOpinion -> ShowS)
-> (GenreOpinion -> String)
-> ([GenreOpinion] -> ShowS)
-> Show GenreOpinion
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GenreOpinion -> ShowS
showsPrec :: Int -> GenreOpinion -> ShowS
$cshow :: GenreOpinion -> String
show :: GenreOpinion -> String
$cshowList :: [GenreOpinion] -> ShowS
showList :: [GenreOpinion] -> ShowS
Show, (forall x. GenreOpinion -> Rep GenreOpinion x)
-> (forall x. Rep GenreOpinion x -> GenreOpinion)
-> Generic GenreOpinion
forall x. Rep GenreOpinion x -> GenreOpinion
forall x. GenreOpinion -> Rep GenreOpinion x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GenreOpinion -> Rep GenreOpinion x
from :: forall x. GenreOpinion -> Rep GenreOpinion x
$cto :: forall x. Rep GenreOpinion x -> GenreOpinion
to :: forall x. Rep GenreOpinion x -> GenreOpinion
Generic, Maybe GenreOpinion
Value -> Parser [GenreOpinion]
Value -> Parser GenreOpinion
(Value -> Parser GenreOpinion)
-> (Value -> Parser [GenreOpinion])
-> Maybe GenreOpinion
-> FromJSON GenreOpinion
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser GenreOpinion
parseJSON :: Value -> Parser GenreOpinion
$cparseJSONList :: Value -> Parser [GenreOpinion]
parseJSONList :: Value -> Parser [GenreOpinion]
$comittedField :: Maybe GenreOpinion
omittedField :: Maybe GenreOpinion
FromJSON, [GenreOpinion] -> Value
[GenreOpinion] -> Encoding
GenreOpinion -> Bool
GenreOpinion -> Value
GenreOpinion -> Encoding
(GenreOpinion -> Value)
-> (GenreOpinion -> Encoding)
-> ([GenreOpinion] -> Value)
-> ([GenreOpinion] -> Encoding)
-> (GenreOpinion -> Bool)
-> ToJSON GenreOpinion
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: GenreOpinion -> Value
toJSON :: GenreOpinion -> Value
$ctoEncoding :: GenreOpinion -> Encoding
toEncoding :: GenreOpinion -> Encoding
$ctoJSONList :: [GenreOpinion] -> Value
toJSONList :: [GenreOpinion] -> Value
$ctoEncodingList :: [GenreOpinion] -> Encoding
toEncodingList :: [GenreOpinion] -> Encoding
$comitField :: GenreOpinion -> Bool
omitField :: GenreOpinion -> Bool
ToJSON, Typeable GenreOpinion
Typeable GenreOpinion =>
(Proxy GenreOpinion -> Declare (Definitions Schema) NamedSchema)
-> ToSchema GenreOpinion
Proxy GenreOpinion -> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy GenreOpinion -> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy GenreOpinion -> Declare (Definitions Schema) NamedSchema
ToSchema)
validateGenreArtwork :: GenreArtwork -> ValidationResult
validateGenreArtwork :: GenreArtwork -> ValidationResult
validateGenreArtwork GenreArtwork
x =
(GenreArtwork
x GenreArtwork -> Optic' A_Lens NoIx GenreArtwork Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic A_Lens NoIx GenreArtwork GenreArtwork Artwork Artwork
#artwork Optic A_Lens NoIx GenreArtwork GenreArtwork Artwork Artwork
-> Optic A_Lens NoIx Artwork Artwork Text Text
-> Optic' A_Lens NoIx GenreArtwork Text
forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% Optic A_Lens NoIx Artwork Artwork Text Text
#contentUrl)
Text -> ValidationRule Text -> ValidationResult
forall a. a -> ValidationRule a -> ValidationResult
|?| ValidationRule Text
isNonEmptyText
ValidationResult -> ValidationResult -> ValidationResult
forall a. Semigroup a => a -> a -> a
<> (GenreArtwork
x GenreArtwork
-> Optic' A_Lens NoIx GenreArtwork (Maybe Text) -> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic A_Lens NoIx GenreArtwork GenreArtwork Artwork Artwork
#artwork Optic A_Lens NoIx GenreArtwork GenreArtwork Artwork Artwork
-> Optic A_Lens NoIx Artwork Artwork (Maybe Text) (Maybe Text)
-> Optic' A_Lens NoIx GenreArtwork (Maybe Text)
forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% Optic A_Lens NoIx Artwork Artwork (Maybe Text) (Maybe Text)
#contentCaption)
Maybe Text -> ValidationRule Text -> ValidationResult
forall a. Maybe a -> ValidationRule a -> ValidationResult
|??| ValidationRule Text
isNonEmptyText
ValidationResult -> ValidationResult -> ValidationResult
forall a. Semigroup a => a -> a -> a
<> (GenreArtwork
x GenreArtwork -> Optic' A_Lens NoIx GenreArtwork Int -> Int
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic A_Lens NoIx GenreArtwork GenreArtwork Artwork Artwork
#artwork Optic A_Lens NoIx GenreArtwork GenreArtwork Artwork Artwork
-> Optic A_Lens NoIx Artwork Artwork Int Int
-> Optic' A_Lens NoIx GenreArtwork Int
forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% Optic A_Lens NoIx Artwork Artwork Int Int
#visibilityStatus)
Int -> ValidationRule Int -> ValidationResult
forall a. a -> ValidationRule a -> ValidationResult
|?| ValidationRule Int
isPositiveOrZero
ValidationResult -> ValidationResult -> ValidationResult
forall a. Semigroup a => a -> a -> a
<> (GenreArtwork
x GenreArtwork -> Optic' A_Lens NoIx GenreArtwork Int -> Int
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic A_Lens NoIx GenreArtwork GenreArtwork Artwork Artwork
#artwork Optic A_Lens NoIx GenreArtwork GenreArtwork Artwork Artwork
-> Optic A_Lens NoIx Artwork Artwork Int Int
-> Optic' A_Lens NoIx GenreArtwork Int
forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% Optic A_Lens NoIx Artwork Artwork Int Int
#orderValue)
Int -> ValidationRule Int -> ValidationResult
forall a. a -> ValidationRule a -> ValidationResult
|?| ValidationRule Int
isPositiveOrZero
data GenreArtwork = GenreArtwork
{ GenreArtwork -> UUID
genreIdentifier :: UUID,
GenreArtwork -> Artwork
artwork :: Artwork
}
deriving (GenreArtwork -> GenreArtwork -> Bool
(GenreArtwork -> GenreArtwork -> Bool)
-> (GenreArtwork -> GenreArtwork -> Bool) -> Eq GenreArtwork
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GenreArtwork -> GenreArtwork -> Bool
== :: GenreArtwork -> GenreArtwork -> Bool
$c/= :: GenreArtwork -> GenreArtwork -> Bool
/= :: GenreArtwork -> GenreArtwork -> Bool
Eq, Int -> GenreArtwork -> ShowS
[GenreArtwork] -> ShowS
GenreArtwork -> String
(Int -> GenreArtwork -> ShowS)
-> (GenreArtwork -> String)
-> ([GenreArtwork] -> ShowS)
-> Show GenreArtwork
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GenreArtwork -> ShowS
showsPrec :: Int -> GenreArtwork -> ShowS
$cshow :: GenreArtwork -> String
show :: GenreArtwork -> String
$cshowList :: [GenreArtwork] -> ShowS
showList :: [GenreArtwork] -> ShowS
Show, (forall x. GenreArtwork -> Rep GenreArtwork x)
-> (forall x. Rep GenreArtwork x -> GenreArtwork)
-> Generic GenreArtwork
forall x. Rep GenreArtwork x -> GenreArtwork
forall x. GenreArtwork -> Rep GenreArtwork x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GenreArtwork -> Rep GenreArtwork x
from :: forall x. GenreArtwork -> Rep GenreArtwork x
$cto :: forall x. Rep GenreArtwork x -> GenreArtwork
to :: forall x. Rep GenreArtwork x -> GenreArtwork
Generic, Maybe GenreArtwork
Value -> Parser [GenreArtwork]
Value -> Parser GenreArtwork
(Value -> Parser GenreArtwork)
-> (Value -> Parser [GenreArtwork])
-> Maybe GenreArtwork
-> FromJSON GenreArtwork
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser GenreArtwork
parseJSON :: Value -> Parser GenreArtwork
$cparseJSONList :: Value -> Parser [GenreArtwork]
parseJSONList :: Value -> Parser [GenreArtwork]
$comittedField :: Maybe GenreArtwork
omittedField :: Maybe GenreArtwork
FromJSON, [GenreArtwork] -> Value
[GenreArtwork] -> Encoding
GenreArtwork -> Bool
GenreArtwork -> Value
GenreArtwork -> Encoding
(GenreArtwork -> Value)
-> (GenreArtwork -> Encoding)
-> ([GenreArtwork] -> Value)
-> ([GenreArtwork] -> Encoding)
-> (GenreArtwork -> Bool)
-> ToJSON GenreArtwork
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: GenreArtwork -> Value
toJSON :: GenreArtwork -> Value
$ctoEncoding :: GenreArtwork -> Encoding
toEncoding :: GenreArtwork -> Encoding
$ctoJSONList :: [GenreArtwork] -> Value
toJSONList :: [GenreArtwork] -> Value
$ctoEncodingList :: [GenreArtwork] -> Encoding
toEncodingList :: [GenreArtwork] -> Encoding
$comitField :: GenreArtwork -> Bool
omitField :: GenreArtwork -> Bool
ToJSON, Typeable GenreArtwork
Typeable GenreArtwork =>
(Proxy GenreArtwork -> Declare (Definitions Schema) NamedSchema)
-> ToSchema GenreArtwork
Proxy GenreArtwork -> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy GenreArtwork -> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy GenreArtwork -> Declare (Definitions Schema) NamedSchema
ToSchema)
validateGenreComment :: GenreComment -> ValidationResult
GenreComment
x =
(GenreComment
x GenreComment -> Optic' A_Lens NoIx GenreComment Int -> Int
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic A_Lens NoIx GenreComment GenreComment Comment Comment
#comment Optic A_Lens NoIx GenreComment GenreComment Comment Comment
-> Optic A_Lens NoIx Comment Comment Int Int
-> Optic' A_Lens NoIx GenreComment Int
forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% Optic A_Lens NoIx Comment Comment Int Int
#visibilityStatus)
Int -> ValidationRule Int -> ValidationResult
forall a. a -> ValidationRule a -> ValidationResult
|?| ValidationRule Int
isPositiveOrZero
ValidationResult -> ValidationResult -> ValidationResult
forall a. Semigroup a => a -> a -> a
<> (GenreComment
x GenreComment -> Optic' A_Lens NoIx GenreComment Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic A_Lens NoIx GenreComment GenreComment Comment Comment
#comment Optic A_Lens NoIx GenreComment GenreComment Comment Comment
-> Optic A_Lens NoIx Comment Comment Text Text
-> Optic' A_Lens NoIx GenreComment Text
forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% Optic A_Lens NoIx Comment Comment Text Text
#contents)
Text -> ValidationRule Text -> ValidationResult
forall a. a -> ValidationRule a -> ValidationResult
|?| (ValidationRule Text
isNonEmptyText ValidationRule Text -> ValidationRule Text -> ValidationRule Text
forall a. Semigroup a => a -> a -> a
<> Int -> ValidationRule Text
isTextSmallerThanOrEqual Int
8200)
data =
{ :: UUID,
:: Comment
}
deriving (GenreComment -> GenreComment -> Bool
(GenreComment -> GenreComment -> Bool)
-> (GenreComment -> GenreComment -> Bool) -> Eq GenreComment
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GenreComment -> GenreComment -> Bool
== :: GenreComment -> GenreComment -> Bool
$c/= :: GenreComment -> GenreComment -> Bool
/= :: GenreComment -> GenreComment -> Bool
Eq, Int -> GenreComment -> ShowS
[GenreComment] -> ShowS
GenreComment -> String
(Int -> GenreComment -> ShowS)
-> (GenreComment -> String)
-> ([GenreComment] -> ShowS)
-> Show GenreComment
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GenreComment -> ShowS
showsPrec :: Int -> GenreComment -> ShowS
$cshow :: GenreComment -> String
show :: GenreComment -> String
$cshowList :: [GenreComment] -> ShowS
showList :: [GenreComment] -> ShowS
Show, (forall x. GenreComment -> Rep GenreComment x)
-> (forall x. Rep GenreComment x -> GenreComment)
-> Generic GenreComment
forall x. Rep GenreComment x -> GenreComment
forall x. GenreComment -> Rep GenreComment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GenreComment -> Rep GenreComment x
from :: forall x. GenreComment -> Rep GenreComment x
$cto :: forall x. Rep GenreComment x -> GenreComment
to :: forall x. Rep GenreComment x -> GenreComment
Generic, Maybe GenreComment
Value -> Parser [GenreComment]
Value -> Parser GenreComment
(Value -> Parser GenreComment)
-> (Value -> Parser [GenreComment])
-> Maybe GenreComment
-> FromJSON GenreComment
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser GenreComment
parseJSON :: Value -> Parser GenreComment
$cparseJSONList :: Value -> Parser [GenreComment]
parseJSONList :: Value -> Parser [GenreComment]
$comittedField :: Maybe GenreComment
omittedField :: Maybe GenreComment
FromJSON, [GenreComment] -> Value
[GenreComment] -> Encoding
GenreComment -> Bool
GenreComment -> Value
GenreComment -> Encoding
(GenreComment -> Value)
-> (GenreComment -> Encoding)
-> ([GenreComment] -> Value)
-> ([GenreComment] -> Encoding)
-> (GenreComment -> Bool)
-> ToJSON GenreComment
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: GenreComment -> Value
toJSON :: GenreComment -> Value
$ctoEncoding :: GenreComment -> Encoding
toEncoding :: GenreComment -> Encoding
$ctoJSONList :: [GenreComment] -> Value
toJSONList :: [GenreComment] -> Value
$ctoEncodingList :: [GenreComment] -> Encoding
toEncodingList :: [GenreComment] -> Encoding
$comitField :: GenreComment -> Bool
omitField :: GenreComment -> Bool
ToJSON, Typeable GenreComment
Typeable GenreComment =>
(Proxy GenreComment -> Declare (Definitions Schema) NamedSchema)
-> ToSchema GenreComment
Proxy GenreComment -> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy GenreComment -> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy GenreComment -> Declare (Definitions Schema) NamedSchema
ToSchema)
validateGenre :: Genre -> ValidationResult
validateGenre :: Genre -> ValidationResult
validateGenre Genre
x =
(Genre
x Genre -> Optic' A_Lens NoIx Genre Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Genre Text
#displayName)
Text -> ValidationRule Text -> ValidationResult
forall a. a -> ValidationRule a -> ValidationResult
|?| (ValidationRule Text
isNonEmptyText ValidationRule Text -> ValidationRule Text -> ValidationRule Text
forall a. Semigroup a => a -> a -> a
<> Int -> ValidationRule Text
isTextSmallerThanOrEqual Int
340)
ValidationResult -> ValidationResult -> ValidationResult
forall a. Semigroup a => a -> a -> a
<> (Genre
x Genre -> Optic' A_Lens NoIx Genre Int -> Int
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Genre Int
#visibilityStatus)
Int -> ValidationRule Int -> ValidationResult
forall a. a -> ValidationRule a -> ValidationResult
|?| ValidationRule Int
isPositiveOrZero
ValidationResult -> ValidationResult -> ValidationResult
forall a. Semigroup a => a -> a -> a
<> (Genre
x Genre -> Optic' A_Lens NoIx Genre (Maybe Text) -> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Genre (Maybe Text)
#spotifyUrl)
Maybe Text -> ValidationRule Text -> ValidationResult
forall a. Maybe a -> ValidationRule a -> ValidationResult
|??| ValidationRule Text
isNonEmptyText
ValidationResult -> ValidationResult -> ValidationResult
forall a. Semigroup a => a -> a -> a
<> (Genre
x Genre -> Optic' A_Lens NoIx Genre (Maybe Text) -> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Genre (Maybe Text)
#youtubeUrl)
Maybe Text -> ValidationRule Text -> ValidationResult
forall a. Maybe a -> ValidationRule a -> ValidationResult
|??| ValidationRule Text
isNonEmptyText
ValidationResult -> ValidationResult -> ValidationResult
forall a. Semigroup a => a -> a -> a
<> (Genre
x Genre -> Optic' A_Lens NoIx Genre (Maybe Text) -> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Genre (Maybe Text)
#soundcloudUrl)
Maybe Text -> ValidationRule Text -> ValidationResult
forall a. Maybe a -> ValidationRule a -> ValidationResult
|??| ValidationRule Text
isNonEmptyText
ValidationResult -> ValidationResult -> ValidationResult
forall a. Semigroup a => a -> a -> a
<> (Genre
x Genre -> Optic' A_Lens NoIx Genre (Maybe Text) -> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Genre (Maybe Text)
#wikipediaUrl)
Maybe Text -> ValidationRule Text -> ValidationResult
forall a. Maybe a -> ValidationRule a -> ValidationResult
|??| ValidationRule Text
isNonEmptyText
data Genre = Genre
{ Genre -> UUID
identifier :: UUID,
Genre -> Maybe UUID
parentIdentifier :: Maybe UUID,
Genre -> Text
displayName :: Text,
Genre -> UUID
createdBy :: UUID,
Genre -> Int
visibilityStatus :: Int,
Genre -> Maybe UUID
approvedBy :: Maybe UUID,
Genre -> UTCTime
createdAt :: UTCTime,
Genre -> Maybe UTCTime
lastEditedAt :: Maybe UTCTime,
Genre -> Map UUID GenreArtwork
artworks :: Map UUID GenreArtwork,
:: [ThreadRender GenreComment],
Genre -> Map UUID GenreOpinion
opinions :: Map UUID GenreOpinion,
Genre -> Maybe Text
spotifyUrl :: Maybe Text,
Genre -> Maybe Text
youtubeUrl :: Maybe Text,
Genre -> Maybe Text
soundcloudUrl :: Maybe Text,
Genre -> Maybe Text
wikipediaUrl :: Maybe Text,
Genre -> Int
viewCount :: Int,
Genre -> Maybe Text
description :: Maybe Text
}
deriving (Genre -> Genre -> Bool
(Genre -> Genre -> Bool) -> (Genre -> Genre -> Bool) -> Eq Genre
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Genre -> Genre -> Bool
== :: Genre -> Genre -> Bool
$c/= :: Genre -> Genre -> Bool
/= :: Genre -> Genre -> Bool
Eq, Int -> Genre -> ShowS
[Genre] -> ShowS
Genre -> String
(Int -> Genre -> ShowS)
-> (Genre -> String) -> ([Genre] -> ShowS) -> Show Genre
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Genre -> ShowS
showsPrec :: Int -> Genre -> ShowS
$cshow :: Genre -> String
show :: Genre -> String
$cshowList :: [Genre] -> ShowS
showList :: [Genre] -> ShowS
Show, (forall x. Genre -> Rep Genre x)
-> (forall x. Rep Genre x -> Genre) -> Generic Genre
forall x. Rep Genre x -> Genre
forall x. Genre -> Rep Genre x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Genre -> Rep Genre x
from :: forall x. Genre -> Rep Genre x
$cto :: forall x. Rep Genre x -> Genre
to :: forall x. Rep Genre x -> Genre
Generic, Maybe Genre
Value -> Parser [Genre]
Value -> Parser Genre
(Value -> Parser Genre)
-> (Value -> Parser [Genre]) -> Maybe Genre -> FromJSON Genre
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Genre
parseJSON :: Value -> Parser Genre
$cparseJSONList :: Value -> Parser [Genre]
parseJSONList :: Value -> Parser [Genre]
$comittedField :: Maybe Genre
omittedField :: Maybe Genre
FromJSON, [Genre] -> Value
[Genre] -> Encoding
Genre -> Bool
Genre -> Value
Genre -> Encoding
(Genre -> Value)
-> (Genre -> Encoding)
-> ([Genre] -> Value)
-> ([Genre] -> Encoding)
-> (Genre -> Bool)
-> ToJSON Genre
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Genre -> Value
toJSON :: Genre -> Value
$ctoEncoding :: Genre -> Encoding
toEncoding :: Genre -> Encoding
$ctoJSONList :: [Genre] -> Value
toJSONList :: [Genre] -> Value
$ctoEncodingList :: [Genre] -> Encoding
toEncodingList :: [Genre] -> Encoding
$comitField :: Genre -> Bool
omitField :: Genre -> Bool
ToJSON, Typeable Genre
Typeable Genre =>
(Proxy Genre -> Declare (Definitions Schema) NamedSchema)
-> ToSchema Genre
Proxy Genre -> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy Genre -> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy Genre -> Declare (Definitions Schema) NamedSchema
ToSchema)
makeFieldLabelsNoPrefix ''Genre
makeFieldLabelsNoPrefix ''GenreComment
makeFieldLabelsNoPrefix ''GenreArtwork
makeFieldLabelsNoPrefix ''GenreOpinion
validateGenreExternalSources :: GenreExternalSources -> ValidationResult
validateGenreExternalSources :: GenreExternalSources -> ValidationResult
validateGenreExternalSources GenreExternalSources
x =
(GenreExternalSources
x GenreExternalSources
-> Optic' A_Lens NoIx GenreExternalSources (Maybe Text)
-> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx GenreExternalSources (Maybe Text)
#spotifyUrl)
Maybe Text -> ValidationRule Text -> ValidationResult
forall a. Maybe a -> ValidationRule a -> ValidationResult
|??| ValidationRule Text
isNonEmptyText
ValidationResult -> ValidationResult -> ValidationResult
forall a. Semigroup a => a -> a -> a
<> (GenreExternalSources
x GenreExternalSources
-> Optic' A_Lens NoIx GenreExternalSources (Maybe Text)
-> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx GenreExternalSources (Maybe Text)
#youtubeUrl)
Maybe Text -> ValidationRule Text -> ValidationResult
forall a. Maybe a -> ValidationRule a -> ValidationResult
|??| ValidationRule Text
isNonEmptyText
ValidationResult -> ValidationResult -> ValidationResult
forall a. Semigroup a => a -> a -> a
<> (GenreExternalSources
x GenreExternalSources
-> Optic' A_Lens NoIx GenreExternalSources (Maybe Text)
-> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx GenreExternalSources (Maybe Text)
#soundcloudUrl)
Maybe Text -> ValidationRule Text -> ValidationResult
forall a. Maybe a -> ValidationRule a -> ValidationResult
|??| ValidationRule Text
isNonEmptyText
ValidationResult -> ValidationResult -> ValidationResult
forall a. Semigroup a => a -> a -> a
<> (GenreExternalSources
x GenreExternalSources
-> Optic' A_Lens NoIx GenreExternalSources (Maybe Text)
-> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx GenreExternalSources (Maybe Text)
#wikipediaUrl)
Maybe Text -> ValidationRule Text -> ValidationResult
forall a. Maybe a -> ValidationRule a -> ValidationResult
|??| ValidationRule Text
isNonEmptyText
data GenreExternalSources = GenreExternalSources
{ GenreExternalSources -> UUID
identifier :: UUID,
GenreExternalSources -> UUID
genreIdentifier :: UUID,
GenreExternalSources -> UUID
createdBy :: UUID,
GenreExternalSources -> Maybe Text
spotifyUrl :: Maybe Text,
GenreExternalSources -> Maybe Text
youtubeUrl :: Maybe Text,
GenreExternalSources -> Maybe Text
soundcloudUrl :: Maybe Text,
GenreExternalSources -> Maybe Text
wikipediaUrl :: Maybe Text,
GenreExternalSources -> UTCTime
createdAt :: UTCTime,
GenreExternalSources -> Maybe UTCTime
lastEditedAt :: Maybe UTCTime
}
deriving (GenreExternalSources -> GenreExternalSources -> Bool
(GenreExternalSources -> GenreExternalSources -> Bool)
-> (GenreExternalSources -> GenreExternalSources -> Bool)
-> Eq GenreExternalSources
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GenreExternalSources -> GenreExternalSources -> Bool
== :: GenreExternalSources -> GenreExternalSources -> Bool
$c/= :: GenreExternalSources -> GenreExternalSources -> Bool
/= :: GenreExternalSources -> GenreExternalSources -> Bool
Eq, Int -> GenreExternalSources -> ShowS
[GenreExternalSources] -> ShowS
GenreExternalSources -> String
(Int -> GenreExternalSources -> ShowS)
-> (GenreExternalSources -> String)
-> ([GenreExternalSources] -> ShowS)
-> Show GenreExternalSources
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GenreExternalSources -> ShowS
showsPrec :: Int -> GenreExternalSources -> ShowS
$cshow :: GenreExternalSources -> String
show :: GenreExternalSources -> String
$cshowList :: [GenreExternalSources] -> ShowS
showList :: [GenreExternalSources] -> ShowS
Show, (forall x. GenreExternalSources -> Rep GenreExternalSources x)
-> (forall x. Rep GenreExternalSources x -> GenreExternalSources)
-> Generic GenreExternalSources
forall x. Rep GenreExternalSources x -> GenreExternalSources
forall x. GenreExternalSources -> Rep GenreExternalSources x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GenreExternalSources -> Rep GenreExternalSources x
from :: forall x. GenreExternalSources -> Rep GenreExternalSources x
$cto :: forall x. Rep GenreExternalSources x -> GenreExternalSources
to :: forall x. Rep GenreExternalSources x -> GenreExternalSources
Generic, Maybe GenreExternalSources
Value -> Parser [GenreExternalSources]
Value -> Parser GenreExternalSources
(Value -> Parser GenreExternalSources)
-> (Value -> Parser [GenreExternalSources])
-> Maybe GenreExternalSources
-> FromJSON GenreExternalSources
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser GenreExternalSources
parseJSON :: Value -> Parser GenreExternalSources
$cparseJSONList :: Value -> Parser [GenreExternalSources]
parseJSONList :: Value -> Parser [GenreExternalSources]
$comittedField :: Maybe GenreExternalSources
omittedField :: Maybe GenreExternalSources
FromJSON, [GenreExternalSources] -> Value
[GenreExternalSources] -> Encoding
GenreExternalSources -> Bool
GenreExternalSources -> Value
GenreExternalSources -> Encoding
(GenreExternalSources -> Value)
-> (GenreExternalSources -> Encoding)
-> ([GenreExternalSources] -> Value)
-> ([GenreExternalSources] -> Encoding)
-> (GenreExternalSources -> Bool)
-> ToJSON GenreExternalSources
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: GenreExternalSources -> Value
toJSON :: GenreExternalSources -> Value
$ctoEncoding :: GenreExternalSources -> Encoding
toEncoding :: GenreExternalSources -> Encoding
$ctoJSONList :: [GenreExternalSources] -> Value
toJSONList :: [GenreExternalSources] -> Value
$ctoEncodingList :: [GenreExternalSources] -> Encoding
toEncodingList :: [GenreExternalSources] -> Encoding
$comitField :: GenreExternalSources -> Bool
omitField :: GenreExternalSources -> Bool
ToJSON, Typeable GenreExternalSources
Typeable GenreExternalSources =>
(Proxy GenreExternalSources
-> Declare (Definitions Schema) NamedSchema)
-> ToSchema GenreExternalSources
Proxy GenreExternalSources
-> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy GenreExternalSources
-> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy GenreExternalSources
-> Declare (Definitions Schema) NamedSchema
ToSchema)
makeFieldLabelsNoPrefix ''GenreExternalSources
validateGenreArtworkOrderUpdate :: GenreArtworkOrderUpdate -> ValidationResult
validateGenreArtworkOrderUpdate :: GenreArtworkOrderUpdate -> ValidationResult
validateGenreArtworkOrderUpdate GenreArtworkOrderUpdate
x =
(GenreArtworkOrderUpdate
x GenreArtworkOrderUpdate
-> Optic' A_Lens NoIx GenreArtworkOrderUpdate Int -> Int
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx GenreArtworkOrderUpdate Int
#orderValue) Int -> ValidationRule Int -> ValidationResult
forall a. a -> ValidationRule a -> ValidationResult
|?| ValidationRule Int
isPositiveOrZero
data GenreArtworkOrderUpdate = GenreArtworkOrderUpdate
{ GenreArtworkOrderUpdate -> UUID
identifier :: UUID,
GenreArtworkOrderUpdate -> Int
orderValue :: Int
}
deriving (GenreArtworkOrderUpdate -> GenreArtworkOrderUpdate -> Bool
(GenreArtworkOrderUpdate -> GenreArtworkOrderUpdate -> Bool)
-> (GenreArtworkOrderUpdate -> GenreArtworkOrderUpdate -> Bool)
-> Eq GenreArtworkOrderUpdate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GenreArtworkOrderUpdate -> GenreArtworkOrderUpdate -> Bool
== :: GenreArtworkOrderUpdate -> GenreArtworkOrderUpdate -> Bool
$c/= :: GenreArtworkOrderUpdate -> GenreArtworkOrderUpdate -> Bool
/= :: GenreArtworkOrderUpdate -> GenreArtworkOrderUpdate -> Bool
Eq, Int -> GenreArtworkOrderUpdate -> ShowS
[GenreArtworkOrderUpdate] -> ShowS
GenreArtworkOrderUpdate -> String
(Int -> GenreArtworkOrderUpdate -> ShowS)
-> (GenreArtworkOrderUpdate -> String)
-> ([GenreArtworkOrderUpdate] -> ShowS)
-> Show GenreArtworkOrderUpdate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GenreArtworkOrderUpdate -> ShowS
showsPrec :: Int -> GenreArtworkOrderUpdate -> ShowS
$cshow :: GenreArtworkOrderUpdate -> String
show :: GenreArtworkOrderUpdate -> String
$cshowList :: [GenreArtworkOrderUpdate] -> ShowS
showList :: [GenreArtworkOrderUpdate] -> ShowS
Show, (forall x.
GenreArtworkOrderUpdate -> Rep GenreArtworkOrderUpdate x)
-> (forall x.
Rep GenreArtworkOrderUpdate x -> GenreArtworkOrderUpdate)
-> Generic GenreArtworkOrderUpdate
forall x. Rep GenreArtworkOrderUpdate x -> GenreArtworkOrderUpdate
forall x. GenreArtworkOrderUpdate -> Rep GenreArtworkOrderUpdate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GenreArtworkOrderUpdate -> Rep GenreArtworkOrderUpdate x
from :: forall x. GenreArtworkOrderUpdate -> Rep GenreArtworkOrderUpdate x
$cto :: forall x. Rep GenreArtworkOrderUpdate x -> GenreArtworkOrderUpdate
to :: forall x. Rep GenreArtworkOrderUpdate x -> GenreArtworkOrderUpdate
Generic, Maybe GenreArtworkOrderUpdate
Value -> Parser [GenreArtworkOrderUpdate]
Value -> Parser GenreArtworkOrderUpdate
(Value -> Parser GenreArtworkOrderUpdate)
-> (Value -> Parser [GenreArtworkOrderUpdate])
-> Maybe GenreArtworkOrderUpdate
-> FromJSON GenreArtworkOrderUpdate
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser GenreArtworkOrderUpdate
parseJSON :: Value -> Parser GenreArtworkOrderUpdate
$cparseJSONList :: Value -> Parser [GenreArtworkOrderUpdate]
parseJSONList :: Value -> Parser [GenreArtworkOrderUpdate]
$comittedField :: Maybe GenreArtworkOrderUpdate
omittedField :: Maybe GenreArtworkOrderUpdate
FromJSON, [GenreArtworkOrderUpdate] -> Value
[GenreArtworkOrderUpdate] -> Encoding
GenreArtworkOrderUpdate -> Bool
GenreArtworkOrderUpdate -> Value
GenreArtworkOrderUpdate -> Encoding
(GenreArtworkOrderUpdate -> Value)
-> (GenreArtworkOrderUpdate -> Encoding)
-> ([GenreArtworkOrderUpdate] -> Value)
-> ([GenreArtworkOrderUpdate] -> Encoding)
-> (GenreArtworkOrderUpdate -> Bool)
-> ToJSON GenreArtworkOrderUpdate
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: GenreArtworkOrderUpdate -> Value
toJSON :: GenreArtworkOrderUpdate -> Value
$ctoEncoding :: GenreArtworkOrderUpdate -> Encoding
toEncoding :: GenreArtworkOrderUpdate -> Encoding
$ctoJSONList :: [GenreArtworkOrderUpdate] -> Value
toJSONList :: [GenreArtworkOrderUpdate] -> Value
$ctoEncodingList :: [GenreArtworkOrderUpdate] -> Encoding
toEncodingList :: [GenreArtworkOrderUpdate] -> Encoding
$comitField :: GenreArtworkOrderUpdate -> Bool
omitField :: GenreArtworkOrderUpdate -> Bool
ToJSON, Typeable GenreArtworkOrderUpdate
Typeable GenreArtworkOrderUpdate =>
(Proxy GenreArtworkOrderUpdate
-> Declare (Definitions Schema) NamedSchema)
-> ToSchema GenreArtworkOrderUpdate
Proxy GenreArtworkOrderUpdate
-> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy GenreArtworkOrderUpdate
-> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy GenreArtworkOrderUpdate
-> Declare (Definitions Schema) NamedSchema
ToSchema)
data GenreDelta = GenreDelta
{ GenreDelta -> UUID
identifier :: UUID,
GenreDelta -> Maybe Text
displayName :: Maybe Text,
GenreDelta -> Maybe Text
spotifyUrl :: Maybe Text,
GenreDelta -> Maybe Text
youtubeUrl :: Maybe Text,
GenreDelta -> Maybe Text
soundcloudUrl :: Maybe Text,
GenreDelta -> Maybe Text
wikipediaUrl :: Maybe Text,
GenreDelta -> Maybe Text
description :: Maybe Text
}
deriving (GenreDelta -> GenreDelta -> Bool
(GenreDelta -> GenreDelta -> Bool)
-> (GenreDelta -> GenreDelta -> Bool) -> Eq GenreDelta
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GenreDelta -> GenreDelta -> Bool
== :: GenreDelta -> GenreDelta -> Bool
$c/= :: GenreDelta -> GenreDelta -> Bool
/= :: GenreDelta -> GenreDelta -> Bool
Eq, Int -> GenreDelta -> ShowS
[GenreDelta] -> ShowS
GenreDelta -> String
(Int -> GenreDelta -> ShowS)
-> (GenreDelta -> String)
-> ([GenreDelta] -> ShowS)
-> Show GenreDelta
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GenreDelta -> ShowS
showsPrec :: Int -> GenreDelta -> ShowS
$cshow :: GenreDelta -> String
show :: GenreDelta -> String
$cshowList :: [GenreDelta] -> ShowS
showList :: [GenreDelta] -> ShowS
Show, (forall x. GenreDelta -> Rep GenreDelta x)
-> (forall x. Rep GenreDelta x -> GenreDelta) -> Generic GenreDelta
forall x. Rep GenreDelta x -> GenreDelta
forall x. GenreDelta -> Rep GenreDelta x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GenreDelta -> Rep GenreDelta x
from :: forall x. GenreDelta -> Rep GenreDelta x
$cto :: forall x. Rep GenreDelta x -> GenreDelta
to :: forall x. Rep GenreDelta x -> GenreDelta
Generic, Maybe GenreDelta
Value -> Parser [GenreDelta]
Value -> Parser GenreDelta
(Value -> Parser GenreDelta)
-> (Value -> Parser [GenreDelta])
-> Maybe GenreDelta
-> FromJSON GenreDelta
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser GenreDelta
parseJSON :: Value -> Parser GenreDelta
$cparseJSONList :: Value -> Parser [GenreDelta]
parseJSONList :: Value -> Parser [GenreDelta]
$comittedField :: Maybe GenreDelta
omittedField :: Maybe GenreDelta
FromJSON, [GenreDelta] -> Value
[GenreDelta] -> Encoding
GenreDelta -> Bool
GenreDelta -> Value
GenreDelta -> Encoding
(GenreDelta -> Value)
-> (GenreDelta -> Encoding)
-> ([GenreDelta] -> Value)
-> ([GenreDelta] -> Encoding)
-> (GenreDelta -> Bool)
-> ToJSON GenreDelta
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: GenreDelta -> Value
toJSON :: GenreDelta -> Value
$ctoEncoding :: GenreDelta -> Encoding
toEncoding :: GenreDelta -> Encoding
$ctoJSONList :: [GenreDelta] -> Value
toJSONList :: [GenreDelta] -> Value
$ctoEncodingList :: [GenreDelta] -> Encoding
toEncodingList :: [GenreDelta] -> Encoding
$comitField :: GenreDelta -> Bool
omitField :: GenreDelta -> Bool
ToJSON, Typeable GenreDelta
Typeable GenreDelta =>
(Proxy GenreDelta -> Declare (Definitions Schema) NamedSchema)
-> ToSchema GenreDelta
Proxy GenreDelta -> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy GenreDelta -> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy GenreDelta -> Declare (Definitions Schema) NamedSchema
ToSchema)
makeFieldLabelsNoPrefix ''GenreDelta
validateGenreDelta :: GenreDelta -> ValidationResult
validateGenreDelta :: GenreDelta -> ValidationResult
validateGenreDelta GenreDelta
x =
(GenreDelta
x GenreDelta
-> Optic' A_Lens NoIx GenreDelta (Maybe Text) -> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx GenreDelta (Maybe Text)
#displayName)
Maybe Text -> ValidationRule Text -> ValidationResult
forall a. Maybe a -> ValidationRule a -> ValidationResult
|??| (ValidationRule Text
isNonEmptyText ValidationRule Text -> ValidationRule Text -> ValidationRule Text
forall a. Semigroup a => a -> a -> a
<> Int -> ValidationRule Text
isTextSmallerThanOrEqual Int
340)
ValidationResult -> ValidationResult -> ValidationResult
forall a. Semigroup a => a -> a -> a
<> (GenreDelta
x GenreDelta
-> Optic' A_Lens NoIx GenreDelta (Maybe Text) -> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx GenreDelta (Maybe Text)
#spotifyUrl)
Maybe Text -> ValidationRule Text -> ValidationResult
forall a. Maybe a -> ValidationRule a -> ValidationResult
|??| ValidationRule Text
isNonEmptyText
ValidationResult -> ValidationResult -> ValidationResult
forall a. Semigroup a => a -> a -> a
<> (GenreDelta
x GenreDelta
-> Optic' A_Lens NoIx GenreDelta (Maybe Text) -> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx GenreDelta (Maybe Text)
#youtubeUrl)
Maybe Text -> ValidationRule Text -> ValidationResult
forall a. Maybe a -> ValidationRule a -> ValidationResult
|??| ValidationRule Text
isNonEmptyText
ValidationResult -> ValidationResult -> ValidationResult
forall a. Semigroup a => a -> a -> a
<> (GenreDelta
x GenreDelta
-> Optic' A_Lens NoIx GenreDelta (Maybe Text) -> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx GenreDelta (Maybe Text)
#soundcloudUrl)
Maybe Text -> ValidationRule Text -> ValidationResult
forall a. Maybe a -> ValidationRule a -> ValidationResult
|??| ValidationRule Text
isNonEmptyText
ValidationResult -> ValidationResult -> ValidationResult
forall a. Semigroup a => a -> a -> a
<> (GenreDelta
x GenreDelta
-> Optic' A_Lens NoIx GenreDelta (Maybe Text) -> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx GenreDelta (Maybe Text)
#wikipediaUrl)
Maybe Text -> ValidationRule Text -> ValidationResult
forall a. Maybe a -> ValidationRule a -> ValidationResult
|??| ValidationRule Text
isNonEmptyText
data EnrichGenreParams = EnrichGenreParams
{ :: Bool,
EnrichGenreParams -> Bool
includeOpinions :: Bool,
EnrichGenreParams -> Bool
includeArtworks :: Bool
}
deriving (EnrichGenreParams -> EnrichGenreParams -> Bool
(EnrichGenreParams -> EnrichGenreParams -> Bool)
-> (EnrichGenreParams -> EnrichGenreParams -> Bool)
-> Eq EnrichGenreParams
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EnrichGenreParams -> EnrichGenreParams -> Bool
== :: EnrichGenreParams -> EnrichGenreParams -> Bool
$c/= :: EnrichGenreParams -> EnrichGenreParams -> Bool
/= :: EnrichGenreParams -> EnrichGenreParams -> Bool
Eq, Int -> EnrichGenreParams -> ShowS
[EnrichGenreParams] -> ShowS
EnrichGenreParams -> String
(Int -> EnrichGenreParams -> ShowS)
-> (EnrichGenreParams -> String)
-> ([EnrichGenreParams] -> ShowS)
-> Show EnrichGenreParams
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EnrichGenreParams -> ShowS
showsPrec :: Int -> EnrichGenreParams -> ShowS
$cshow :: EnrichGenreParams -> String
show :: EnrichGenreParams -> String
$cshowList :: [EnrichGenreParams] -> ShowS
showList :: [EnrichGenreParams] -> ShowS
Show, (forall x. EnrichGenreParams -> Rep EnrichGenreParams x)
-> (forall x. Rep EnrichGenreParams x -> EnrichGenreParams)
-> Generic EnrichGenreParams
forall x. Rep EnrichGenreParams x -> EnrichGenreParams
forall x. EnrichGenreParams -> Rep EnrichGenreParams x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. EnrichGenreParams -> Rep EnrichGenreParams x
from :: forall x. EnrichGenreParams -> Rep EnrichGenreParams x
$cto :: forall x. Rep EnrichGenreParams x -> EnrichGenreParams
to :: forall x. Rep EnrichGenreParams x -> EnrichGenreParams
Generic, Maybe EnrichGenreParams
Value -> Parser [EnrichGenreParams]
Value -> Parser EnrichGenreParams
(Value -> Parser EnrichGenreParams)
-> (Value -> Parser [EnrichGenreParams])
-> Maybe EnrichGenreParams
-> FromJSON EnrichGenreParams
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser EnrichGenreParams
parseJSON :: Value -> Parser EnrichGenreParams
$cparseJSONList :: Value -> Parser [EnrichGenreParams]
parseJSONList :: Value -> Parser [EnrichGenreParams]
$comittedField :: Maybe EnrichGenreParams
omittedField :: Maybe EnrichGenreParams
FromJSON, [EnrichGenreParams] -> Value
[EnrichGenreParams] -> Encoding
EnrichGenreParams -> Bool
EnrichGenreParams -> Value
EnrichGenreParams -> Encoding
(EnrichGenreParams -> Value)
-> (EnrichGenreParams -> Encoding)
-> ([EnrichGenreParams] -> Value)
-> ([EnrichGenreParams] -> Encoding)
-> (EnrichGenreParams -> Bool)
-> ToJSON EnrichGenreParams
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: EnrichGenreParams -> Value
toJSON :: EnrichGenreParams -> Value
$ctoEncoding :: EnrichGenreParams -> Encoding
toEncoding :: EnrichGenreParams -> Encoding
$ctoJSONList :: [EnrichGenreParams] -> Value
toJSONList :: [EnrichGenreParams] -> Value
$ctoEncodingList :: [EnrichGenreParams] -> Encoding
toEncodingList :: [EnrichGenreParams] -> Encoding
$comitField :: EnrichGenreParams -> Bool
omitField :: EnrichGenreParams -> Bool
ToJSON, Typeable EnrichGenreParams
Typeable EnrichGenreParams =>
(Proxy EnrichGenreParams
-> Declare (Definitions Schema) NamedSchema)
-> ToSchema EnrichGenreParams
Proxy EnrichGenreParams -> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy EnrichGenreParams -> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy EnrichGenreParams -> Declare (Definitions Schema) NamedSchema
ToSchema)
makeFieldLabelsNoPrefix ''EnrichGenreParams
fullEnrichment :: EnrichGenreParams
fullEnrichment :: EnrichGenreParams
fullEnrichment =
EnrichGenreParams
{ $sel:includeComments:EnrichGenreParams :: Bool
includeComments = Bool
True,
$sel:includeArtworks:EnrichGenreParams :: Bool
includeArtworks = Bool
True,
$sel:includeOpinions:EnrichGenreParams :: Bool
includeOpinions = Bool
True
}
noEnrichment :: EnrichGenreParams
noEnrichment :: EnrichGenreParams
noEnrichment =
EnrichGenreParams
{ $sel:includeComments:EnrichGenreParams :: Bool
includeComments = Bool
False,
$sel:includeArtworks:EnrichGenreParams :: Bool
includeArtworks = Bool
False,
$sel:includeOpinions:EnrichGenreParams :: Bool
includeOpinions = Bool
False
}
parseInclude :: Text -> EnrichGenreParams
parseInclude :: Text -> EnrichGenreParams
parseInclude Text
includeString = do
EnrichGenreParams
{ $sel:includeComments:EnrichGenreParams :: Bool
includeComments = GenreIncludes -> Bool
fromIncludeMap GenreIncludes
IncludeComments,
$sel:includeOpinions:EnrichGenreParams :: Bool
includeOpinions = GenreIncludes -> Bool
fromIncludeMap GenreIncludes
IncludeOpinions,
$sel:includeArtworks:EnrichGenreParams :: Bool
includeArtworks = GenreIncludes -> Bool
fromIncludeMap GenreIncludes
IncludeArtworks
}
where
includes :: Map Text Bool
includes = [(Text, Bool)] -> Map Text Bool
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(Text, Bool)] -> Map Text Bool)
-> [(Text, Bool)] -> Map Text Bool
forall a b. (a -> b) -> a -> b
$ (Text -> (Text, Bool)) -> [Text] -> [(Text, Bool)]
forall a b. (a -> b) -> [a] -> [b]
map (,Bool
True) ((Char -> Bool) -> Text -> [Text]
T.split (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
',') Text
includeString)
fromIncludeMap :: GenreIncludes -> Bool
fromIncludeMap GenreIncludes
k = Bool -> Maybe Bool -> Bool
forall a. a -> Maybe a -> a
fromMaybe Bool
False (Map Text Bool
includes Map Text Bool -> Text -> Maybe Bool
forall k a. Ord k => Map k a -> k -> Maybe a
Map.!? (String -> Text
T.pack (String -> Text)
-> (GenreIncludes -> String) -> GenreIncludes -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenreIncludes -> String
forall b a. (Show a, IsString b) => a -> b
show (GenreIncludes -> Text) -> GenreIncludes -> Text
forall a b. (a -> b) -> a -> b
$ GenreIncludes
k))