module Spotify.Types.Simple where

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

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

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

data TrackSimple = TrackSimple
    { TrackSimple -> [ArtistSimple]
artists :: [ArtistSimple]
    , TrackSimple -> Maybe [Text]
availableMarkets :: Maybe [Text]
    , TrackSimple -> Int
discNumber :: Int
    , TrackSimple -> Int
durationMs :: Int
    , TrackSimple -> Bool
explicit :: Bool
    , TrackSimple -> ExternalURLs
externalUrls :: ExternalURLs
    , TrackSimple -> Href
href :: Href
    , TrackSimple -> TrackID
id :: TrackID
    , TrackSimple -> Maybe Bool
isPlayable :: Maybe Bool
    , TrackSimple -> Maybe TrackLink
linkedFrom :: Maybe TrackLink
    , TrackSimple -> Text
name :: Text
    , TrackSimple -> Maybe Text
previewUrl :: Maybe Text
    , TrackSimple -> Int
trackNumber :: Int
    , TrackSimple -> URI
uri :: URI
    }
    deriving (TrackSimple -> TrackSimple -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TrackSimple -> TrackSimple -> Bool
$c/= :: TrackSimple -> TrackSimple -> Bool
== :: TrackSimple -> TrackSimple -> Bool
$c== :: TrackSimple -> TrackSimple -> Bool
Eq, Eq TrackSimple
TrackSimple -> TrackSimple -> Bool
TrackSimple -> TrackSimple -> Ordering
TrackSimple -> TrackSimple -> TrackSimple
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 :: TrackSimple -> TrackSimple -> TrackSimple
$cmin :: TrackSimple -> TrackSimple -> TrackSimple
max :: TrackSimple -> TrackSimple -> TrackSimple
$cmax :: TrackSimple -> TrackSimple -> TrackSimple
>= :: TrackSimple -> TrackSimple -> Bool
$c>= :: TrackSimple -> TrackSimple -> Bool
> :: TrackSimple -> TrackSimple -> Bool
$c> :: TrackSimple -> TrackSimple -> Bool
<= :: TrackSimple -> TrackSimple -> Bool
$c<= :: TrackSimple -> TrackSimple -> Bool
< :: TrackSimple -> TrackSimple -> Bool
$c< :: TrackSimple -> TrackSimple -> Bool
compare :: TrackSimple -> TrackSimple -> Ordering
$ccompare :: TrackSimple -> TrackSimple -> Ordering
Ord, Int -> TrackSimple -> ShowS
[TrackSimple] -> ShowS
TrackSimple -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TrackSimple] -> ShowS
$cshowList :: [TrackSimple] -> ShowS
show :: TrackSimple -> String
$cshow :: TrackSimple -> String
showsPrec :: Int -> TrackSimple -> ShowS
$cshowsPrec :: Int -> TrackSimple -> ShowS
Show, forall x. Rep TrackSimple x -> TrackSimple
forall x. TrackSimple -> Rep TrackSimple x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TrackSimple x -> TrackSimple
$cfrom :: forall x. TrackSimple -> Rep TrackSimple x
Generic)
    deriving (Value -> Parser [TrackSimple]
Value -> Parser TrackSimple
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [TrackSimple]
$cparseJSONList :: Value -> Parser [TrackSimple]
parseJSON :: Value -> Parser TrackSimple
$cparseJSON :: Value -> Parser TrackSimple
FromJSON) via CustomJSON TrackSimple

data AlbumSimple = AlbumSimple
    { AlbumSimple -> AlbumType
albumType :: AlbumType
    , AlbumSimple -> [ArtistSimple]
artists :: [ArtistSimple]
    , AlbumSimple -> Maybe [Text]
availableMarkets :: Maybe [Text]
    , AlbumSimple -> ExternalURLs
externalUrls :: ExternalURLs
    , AlbumSimple -> Maybe AlbumGroup
albumGroup :: Maybe AlbumGroup
    , AlbumSimple -> Href
href :: Href
    , AlbumSimple -> AlbumID
id :: AlbumID
    , AlbumSimple -> [Image]
images :: [Image]
    , AlbumSimple -> Text
name :: Text
    , AlbumSimple -> Text
releaseDate :: Text
    , AlbumSimple -> DatePrecision
releaseDatePrecision :: DatePrecision
    , AlbumSimple -> Maybe Restrictions
restrictions :: Maybe Restrictions
    , AlbumSimple -> URI
uri :: URI
    }
    deriving (AlbumSimple -> AlbumSimple -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AlbumSimple -> AlbumSimple -> Bool
$c/= :: AlbumSimple -> AlbumSimple -> Bool
== :: AlbumSimple -> AlbumSimple -> Bool
$c== :: AlbumSimple -> AlbumSimple -> Bool
Eq, Eq AlbumSimple
AlbumSimple -> AlbumSimple -> Bool
AlbumSimple -> AlbumSimple -> Ordering
AlbumSimple -> AlbumSimple -> AlbumSimple
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 :: AlbumSimple -> AlbumSimple -> AlbumSimple
$cmin :: AlbumSimple -> AlbumSimple -> AlbumSimple
max :: AlbumSimple -> AlbumSimple -> AlbumSimple
$cmax :: AlbumSimple -> AlbumSimple -> AlbumSimple
>= :: AlbumSimple -> AlbumSimple -> Bool
$c>= :: AlbumSimple -> AlbumSimple -> Bool
> :: AlbumSimple -> AlbumSimple -> Bool
$c> :: AlbumSimple -> AlbumSimple -> Bool
<= :: AlbumSimple -> AlbumSimple -> Bool
$c<= :: AlbumSimple -> AlbumSimple -> Bool
< :: AlbumSimple -> AlbumSimple -> Bool
$c< :: AlbumSimple -> AlbumSimple -> Bool
compare :: AlbumSimple -> AlbumSimple -> Ordering
$ccompare :: AlbumSimple -> AlbumSimple -> Ordering
Ord, Int -> AlbumSimple -> ShowS
[AlbumSimple] -> ShowS
AlbumSimple -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AlbumSimple] -> ShowS
$cshowList :: [AlbumSimple] -> ShowS
show :: AlbumSimple -> String
$cshow :: AlbumSimple -> String
showsPrec :: Int -> AlbumSimple -> ShowS
$cshowsPrec :: Int -> AlbumSimple -> ShowS
Show, forall x. Rep AlbumSimple x -> AlbumSimple
forall x. AlbumSimple -> Rep AlbumSimple x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AlbumSimple x -> AlbumSimple
$cfrom :: forall x. AlbumSimple -> Rep AlbumSimple x
Generic)
    deriving (Value -> Parser [AlbumSimple]
Value -> Parser AlbumSimple
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [AlbumSimple]
$cparseJSONList :: Value -> Parser [AlbumSimple]
parseJSON :: Value -> Parser AlbumSimple
$cparseJSON :: Value -> Parser AlbumSimple
FromJSON) via CustomJSON AlbumSimple

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

data PlaylistSimple = PlaylistSimple
    { PlaylistSimple -> Bool
collaborative :: Bool
    , PlaylistSimple -> ExternalURLs
externalUrls :: ExternalURLs
    , PlaylistSimple -> Href
href :: Href
    , PlaylistSimple -> PlaylistID
id :: PlaylistID
    , PlaylistSimple -> [Image]
images :: [Image]
    , PlaylistSimple -> Text
name :: Text
    , PlaylistSimple -> UserSimple
owner :: UserSimple
    , PlaylistSimple -> Maybe Bool
public :: Maybe Bool
    , PlaylistSimple -> SnapshotID
snapshotId :: SnapshotID
    , PlaylistSimple -> Tracks
tracks :: Tracks
    , PlaylistSimple -> URI
uri :: URI
    }
    deriving (PlaylistSimple -> PlaylistSimple -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PlaylistSimple -> PlaylistSimple -> Bool
$c/= :: PlaylistSimple -> PlaylistSimple -> Bool
== :: PlaylistSimple -> PlaylistSimple -> Bool
$c== :: PlaylistSimple -> PlaylistSimple -> Bool
Eq, Eq PlaylistSimple
PlaylistSimple -> PlaylistSimple -> Bool
PlaylistSimple -> PlaylistSimple -> Ordering
PlaylistSimple -> PlaylistSimple -> PlaylistSimple
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 :: PlaylistSimple -> PlaylistSimple -> PlaylistSimple
$cmin :: PlaylistSimple -> PlaylistSimple -> PlaylistSimple
max :: PlaylistSimple -> PlaylistSimple -> PlaylistSimple
$cmax :: PlaylistSimple -> PlaylistSimple -> PlaylistSimple
>= :: PlaylistSimple -> PlaylistSimple -> Bool
$c>= :: PlaylistSimple -> PlaylistSimple -> Bool
> :: PlaylistSimple -> PlaylistSimple -> Bool
$c> :: PlaylistSimple -> PlaylistSimple -> Bool
<= :: PlaylistSimple -> PlaylistSimple -> Bool
$c<= :: PlaylistSimple -> PlaylistSimple -> Bool
< :: PlaylistSimple -> PlaylistSimple -> Bool
$c< :: PlaylistSimple -> PlaylistSimple -> Bool
compare :: PlaylistSimple -> PlaylistSimple -> Ordering
$ccompare :: PlaylistSimple -> PlaylistSimple -> Ordering
Ord, Int -> PlaylistSimple -> ShowS
[PlaylistSimple] -> ShowS
PlaylistSimple -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PlaylistSimple] -> ShowS
$cshowList :: [PlaylistSimple] -> ShowS
show :: PlaylistSimple -> String
$cshow :: PlaylistSimple -> String
showsPrec :: Int -> PlaylistSimple -> ShowS
$cshowsPrec :: Int -> PlaylistSimple -> ShowS
Show, forall x. Rep PlaylistSimple x -> PlaylistSimple
forall x. PlaylistSimple -> Rep PlaylistSimple x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PlaylistSimple x -> PlaylistSimple
$cfrom :: forall x. PlaylistSimple -> Rep PlaylistSimple x
Generic)
    deriving (Value -> Parser [PlaylistSimple]
Value -> Parser PlaylistSimple
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [PlaylistSimple]
$cparseJSONList :: Value -> Parser [PlaylistSimple]
parseJSON :: Value -> Parser PlaylistSimple
$cparseJSON :: Value -> Parser PlaylistSimple
FromJSON) via CustomJSON PlaylistSimple