module Spotify.Types.Artists where

import Spotify.Types.Internal.CustomJSON
import Spotify.Types.Misc

import Data.Aeson (FromJSON)
import Data.Text (Text)
import GHC.Generics (Generic)

data Artist = Artist
    { Artist -> ExternalURLs
externalUrls :: ExternalURLs
    , Artist -> Followers
followers :: Followers
    , Artist -> [Genre]
genres :: [Genre]
    , Artist -> Href
href :: Href
    , Artist -> ArtistID
id :: ArtistID
    , Artist -> [Image]
images :: [Image]
    , Artist -> Text
name :: Text
    , Artist -> Int
popularity :: Int
    , Artist -> URI
uri :: URI
    }
    deriving (Artist -> Artist -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Artist -> Artist -> Bool
$c/= :: Artist -> Artist -> Bool
== :: Artist -> Artist -> Bool
$c== :: Artist -> Artist -> Bool
Eq, Eq Artist
Artist -> Artist -> Bool
Artist -> Artist -> Ordering
Artist -> Artist -> Artist
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Artist -> Artist -> Artist
$cmin :: Artist -> Artist -> Artist
max :: Artist -> Artist -> Artist
$cmax :: Artist -> Artist -> Artist
>= :: Artist -> Artist -> Bool
$c>= :: Artist -> Artist -> Bool
> :: Artist -> Artist -> Bool
$c> :: Artist -> Artist -> Bool
<= :: Artist -> Artist -> Bool
$c<= :: Artist -> Artist -> Bool
< :: Artist -> Artist -> Bool
$c< :: Artist -> Artist -> Bool
compare :: Artist -> Artist -> Ordering
$ccompare :: Artist -> Artist -> Ordering
Ord, Int -> Artist -> ShowS
[Artist] -> ShowS
Artist -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Artist] -> ShowS
$cshowList :: [Artist] -> ShowS
show :: Artist -> String
$cshow :: Artist -> String
showsPrec :: Int -> Artist -> ShowS
$cshowsPrec :: Int -> Artist -> ShowS
Show, forall x. Rep Artist x -> Artist
forall x. Artist -> Rep Artist x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Artist x -> Artist
$cfrom :: forall x. Artist -> Rep Artist x
Generic)
    deriving (Value -> Parser [Artist]
Value -> Parser Artist
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Artist]
$cparseJSONList :: Value -> Parser [Artist]
parseJSON :: Value -> Parser Artist
$cparseJSON :: Value -> Parser Artist
FromJSON) via CustomJSON Artist