| Safe Haskell | Safe-Inferred |
|---|---|
| Language | GHC2021 |
Spotify.Types.Misc
Documentation
Constructors
| Copyright | |
Fields
| |
Instances
| FromJSON Copyright Source # | |
| Generic Copyright Source # | |
| Show Copyright Source # | |
| Eq Copyright Source # | |
| Ord Copyright Source # | |
| type Rep Copyright Source # | |
Defined in Spotify.Types.Misc type Rep Copyright = D1 ('MetaData "Copyright" "Spotify.Types.Misc" "spotify-0.1.0.1-DSXk6mPWfQGGnICPbDr6pO-spotify-types" 'False) (C1 ('MetaCons "Copyright" 'PrefixI 'True) (S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "type_") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CopyrightType))) | |
data CopyrightType Source #
Instances
Instances
| FromJSON Error Source # | |
| Generic Error Source # | |
| Show Error Source # | |
| Eq Error Source # | |
| Ord Error Source # | |
| type Rep Error Source # | |
Defined in Spotify.Types.Misc type Rep Error = D1 ('MetaData "Error" "Spotify.Types.Misc" "spotify-0.1.0.1-DSXk6mPWfQGGnICPbDr6pO-spotify-types" 'False) (C1 ('MetaCons "Error" 'PrefixI 'True) (S1 ('MetaSel ('Just "status") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HTTPError) :*: S1 ('MetaSel ('Just "message") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) | |
Instances
| FromJSON Followers Source # | |
| Generic Followers Source # | |
| Show Followers Source # | |
| Eq Followers Source # | |
| Ord Followers Source # | |
| type Rep Followers Source # | |
Defined in Spotify.Types.Misc type Rep Followers = D1 ('MetaData "Followers" "Spotify.Types.Misc" "spotify-0.1.0.1-DSXk6mPWfQGGnICPbDr6pO-spotify-types" 'False) (C1 ('MetaCons "Followers" 'PrefixI 'True) (S1 ('MetaSel ('Just "href") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "total") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) | |
Instances
| FromJSON Image Source # | |
| Generic Image Source # | |
| Show Image Source # | |
| Eq Image Source # | |
| Ord Image Source # | |
| type Rep Image Source # | |
Defined in Spotify.Types.Misc type Rep Image = D1 ('MetaData "Image" "Spotify.Types.Misc" "spotify-0.1.0.1-DSXk6mPWfQGGnICPbDr6pO-spotify-types" 'False) (C1 ('MetaCons "Image" 'PrefixI 'True) (S1 ('MetaSel ('Just "height") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: (S1 ('MetaSel ('Just "url") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "width") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))))) | |
Constructors
| Paging | |
Instances
Instances
| FromJSON Tracks Source # | |
| Generic Tracks Source # | |
| Show Tracks Source # | |
| Eq Tracks Source # | |
| Ord Tracks Source # | |
| type Rep Tracks Source # | |
Defined in Spotify.Types.Misc type Rep Tracks = D1 ('MetaData "Tracks" "Spotify.Types.Misc" "spotify-0.1.0.1-DSXk6mPWfQGGnICPbDr6pO-spotify-types" 'False) (C1 ('MetaCons "Tracks" 'PrefixI 'True) (S1 ('MetaSel ('Just "href") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "total") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) | |
data DatePrecision Source #
Constructors
| DatePrecisionYear | |
| DatePrecisionMonth | |
| DatePrecisionDay |
Instances
Instances
Constructors
| TrackLink | |
Fields
| |
Instances
| FromJSON TrackLink Source # | |
| Generic TrackLink Source # | |
| Show TrackLink Source # | |
| Eq TrackLink Source # | |
| Ord TrackLink Source # | |
| type Rep TrackLink Source # | |
Defined in Spotify.Types.Misc type Rep TrackLink = D1 ('MetaData "TrackLink" "Spotify.Types.Misc" "spotify-0.1.0.1-DSXk6mPWfQGGnICPbDr6pO-spotify-types" 'False) (C1 ('MetaCons "TrackLink" 'PrefixI 'True) ((S1 ('MetaSel ('Just "externalUrls") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ExternalURLs) :*: S1 ('MetaSel ('Just "href") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Href)) :*: (S1 ('MetaSel ('Just "id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TrackID) :*: S1 ('MetaSel ('Just "url") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))))) | |
data AlbumGroup Source #
Constructors
| GroupAlbum | |
| GroupSingle | |
| GroupCompilation | |
| AppearsOn |
Instances
Constructors
| AlbumTypeAlbum | |
| AlbumTypeSingle | |
| AlbumTypeCompilation |
Instances
| FromJSON AlbumType Source # | |
| Generic AlbumType Source # | |
| Show AlbumType Source # | |
| Eq AlbumType Source # | |
| Ord AlbumType Source # | |
| type Rep AlbumType Source # | |
Defined in Spotify.Types.Misc type Rep AlbumType = D1 ('MetaData "AlbumType" "Spotify.Types.Misc" "spotify-0.1.0.1-DSXk6mPWfQGGnICPbDr6pO-spotify-types" 'False) (C1 ('MetaCons "AlbumTypeAlbum" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AlbumTypeSingle" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AlbumTypeCompilation" 'PrefixI 'False) (U1 :: Type -> Type))) | |
data ExplicitContent Source #
Constructors
| ExplicitContent | |
Fields
| |
Instances
Instances
| ToJSON Offset Source # | |
Defined in Spotify.Types.Misc | |
| Generic Offset Source # | |
| Show Offset Source # | |
| Eq Offset Source # | |
| Ord Offset Source # | |
| type Rep Offset Source # | |
Defined in Spotify.Types.Misc type Rep Offset = D1 ('MetaData "Offset" "Spotify.Types.Misc" "spotify-0.1.0.1-DSXk6mPWfQGGnICPbDr6pO-spotify-types" 'False) (C1 ('MetaCons "Offset" 'PrefixI 'True) (S1 ('MetaSel ('Just "position") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "uri") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe URI)))) | |
Instances
| IsString Market Source # | |
Defined in Spotify.Types.Misc Methods fromString :: String -> Market # | |
| Show Market Source # | |
| Eq Market Source # | |
| Ord Market Source # | |
| ToHttpApiData Market Source # | |
Defined in Spotify.Types.Misc Methods toUrlPiece :: Market -> Text # toEncodedUrlPiece :: Market -> Builder # toHeader :: Market -> ByteString # toQueryParam :: Market -> Text # toEncodedQueryParam :: Market -> Builder # | |
Instances
Instances
| FromJSON DeviceID Source # | |
| ToJSON DeviceID Source # | |
Defined in Spotify.Types.Misc | |
| IsString DeviceID Source # | |
Defined in Spotify.Types.Misc Methods fromString :: String -> DeviceID # | |
| Show DeviceID Source # | |
| Eq DeviceID Source # | |
| Ord DeviceID Source # | |
Defined in Spotify.Types.Misc | |
| ToHttpApiData DeviceID Source # | |
Defined in Spotify.Types.Misc Methods toUrlPiece :: DeviceID -> Text # toEncodedUrlPiece :: DeviceID -> Builder # toHeader :: DeviceID -> ByteString # toQueryParam :: DeviceID -> Text # toEncodedQueryParam :: DeviceID -> Builder # | |
Instances
| FromJSON AlbumID Source # | |
| ToJSON AlbumID Source # | |
Defined in Spotify.Types.Misc | |
| IsString AlbumID Source # | |
Defined in Spotify.Types.Misc Methods fromString :: String -> AlbumID # | |
| Show AlbumID Source # | |
| Eq AlbumID Source # | |
| Ord AlbumID Source # | |
| ToHttpApiData AlbumID Source # | |
Defined in Spotify.Types.Misc Methods toUrlPiece :: AlbumID -> Text # toEncodedUrlPiece :: AlbumID -> Builder # toHeader :: AlbumID -> ByteString # toQueryParam :: AlbumID -> Text # toEncodedQueryParam :: AlbumID -> Builder # | |
| ToURI AlbumID Source # | |
Instances
| FromJSON ArtistID Source # | |
| ToJSON ArtistID Source # | |
Defined in Spotify.Types.Misc | |
| IsString ArtistID Source # | |
Defined in Spotify.Types.Misc Methods fromString :: String -> ArtistID # | |
| Show ArtistID Source # | |
| Eq ArtistID Source # | |
| Ord ArtistID Source # | |
Defined in Spotify.Types.Misc | |
| ToHttpApiData ArtistID Source # | |
Defined in Spotify.Types.Misc Methods toUrlPiece :: ArtistID -> Text # toEncodedUrlPiece :: ArtistID -> Builder # toHeader :: ArtistID -> ByteString # toQueryParam :: ArtistID -> Text # toEncodedQueryParam :: ArtistID -> Builder # | |
| ToURI ArtistID Source # | |
Instances
| FromJSON EpisodeID Source # | |
| ToJSON EpisodeID Source # | |
Defined in Spotify.Types.Misc | |
| IsString EpisodeID Source # | |
Defined in Spotify.Types.Misc Methods fromString :: String -> EpisodeID # | |
| Show EpisodeID Source # | |
| Eq EpisodeID Source # | |
| Ord EpisodeID Source # | |
| ToHttpApiData EpisodeID Source # | |
Defined in Spotify.Types.Misc Methods toUrlPiece :: EpisodeID -> Text # toEncodedUrlPiece :: EpisodeID -> Builder # toHeader :: EpisodeID -> ByteString # toQueryParam :: EpisodeID -> Text # toEncodedQueryParam :: EpisodeID -> Builder # | |
| ToURI EpisodeID Source # | |
Instances
| FromJSON TrackID Source # | |
| ToJSON TrackID Source # | |
Defined in Spotify.Types.Misc | |
| IsString TrackID Source # | |
Defined in Spotify.Types.Misc Methods fromString :: String -> TrackID # | |
| Show TrackID Source # | |
| Eq TrackID Source # | |
| Ord TrackID Source # | |
| ToHttpApiData TrackID Source # | |
Defined in Spotify.Types.Misc Methods toUrlPiece :: TrackID -> Text # toEncodedUrlPiece :: TrackID -> Builder # toHeader :: TrackID -> ByteString # toQueryParam :: TrackID -> Text # toEncodedQueryParam :: TrackID -> Builder # | |
| ToURI TrackID Source # | |
Instances
| FromJSON UserID Source # | |
| ToJSON UserID Source # | |
Defined in Spotify.Types.Misc | |
| IsString UserID Source # | |
Defined in Spotify.Types.Misc Methods fromString :: String -> UserID # | |
| Show UserID Source # | |
| Eq UserID Source # | |
| Ord UserID Source # | |
| ToHttpApiData UserID Source # | |
Defined in Spotify.Types.Misc Methods toUrlPiece :: UserID -> Text # toEncodedUrlPiece :: UserID -> Builder # toHeader :: UserID -> ByteString # toQueryParam :: UserID -> Text # toEncodedQueryParam :: UserID -> Builder # | |
| ToURI UserID Source # | |
newtype PlaylistID Source #
Constructors
| PlaylistID | |
Instances
newtype CategoryID Source #
Constructors
| CategoryID | |
Instances
newtype SnapshotID Source #
Constructors
| SnapshotID | |
Instances
Instances
| FromJSON URL Source # | |
| IsString URL Source # | |
Defined in Spotify.Types.Misc Methods fromString :: String -> URL # | |
| Show URL Source # | |
| Eq URL Source # | |
| Ord URL Source # | |
| ToHttpApiData URL Source # | |
Defined in Spotify.Types.Misc Methods toUrlPiece :: URL -> Text # toEncodedUrlPiece :: URL -> Builder # toHeader :: URL -> ByteString # toQueryParam :: URL -> Text # toEncodedQueryParam :: URL -> Builder # | |
Instances
| FromJSON Country Source # | |
| ToJSON Country Source # | |
Defined in Spotify.Types.Misc | |
| IsString Country Source # | |
Defined in Spotify.Types.Misc Methods fromString :: String -> Country # | |
| Show Country Source # | |
| Eq Country Source # | |
| Ord Country Source # | |
| ToHttpApiData Country Source # | |
Defined in Spotify.Types.Misc Methods toUrlPiece :: Country -> Text # toEncodedUrlPiece :: Country -> Builder # toHeader :: Country -> ByteString # toQueryParam :: Country -> Text # toEncodedQueryParam :: Country -> Builder # | |
Instances
| FromJSON Locale Source # | |
| ToJSON Locale Source # | |
Defined in Spotify.Types.Misc | |
| IsString Locale Source # | |
Defined in Spotify.Types.Misc Methods fromString :: String -> Locale # | |
| Show Locale Source # | |
| Eq Locale Source # | |
| Ord Locale Source # | |
| ToHttpApiData Locale Source # | |
Defined in Spotify.Types.Misc Methods toUrlPiece :: Locale -> Text # toEncodedUrlPiece :: Locale -> Builder # toHeader :: Locale -> ByteString # toQueryParam :: Locale -> Text # toEncodedQueryParam :: Locale -> Builder # | |
Instances
| FromJSON HTTPError Source # | |
| Show HTTPError Source # | |
| Eq HTTPError Source # | |
| Ord HTTPError Source # | |
newtype Restrictions Source #
Constructors
| Restrictions | |
Instances
| FromJSON Restrictions Source # | |
Defined in Spotify.Types.Misc | |
| Show Restrictions Source # | |
Defined in Spotify.Types.Misc Methods showsPrec :: Int -> Restrictions -> ShowS # show :: Restrictions -> String # showList :: [Restrictions] -> ShowS # | |
| Eq Restrictions Source # | |
Defined in Spotify.Types.Misc | |
| Ord Restrictions Source # | |
Defined in Spotify.Types.Misc Methods compare :: Restrictions -> Restrictions -> Ordering # (<) :: Restrictions -> Restrictions -> Bool # (<=) :: Restrictions -> Restrictions -> Bool # (>) :: Restrictions -> Restrictions -> Bool # (>=) :: Restrictions -> Restrictions -> Bool # max :: Restrictions -> Restrictions -> Restrictions # min :: Restrictions -> Restrictions -> Restrictions # | |
newtype ExternalIDs Source #
Constructors
| ExternalIDs | |
Instances
| FromJSON ExternalIDs Source # | |
Defined in Spotify.Types.Misc | |
| Show ExternalIDs Source # | |
Defined in Spotify.Types.Misc Methods showsPrec :: Int -> ExternalIDs -> ShowS # show :: ExternalIDs -> String # showList :: [ExternalIDs] -> ShowS # | |
| Eq ExternalIDs Source # | |
Defined in Spotify.Types.Misc | |
| Ord ExternalIDs Source # | |
Defined in Spotify.Types.Misc Methods compare :: ExternalIDs -> ExternalIDs -> Ordering # (<) :: ExternalIDs -> ExternalIDs -> Bool # (<=) :: ExternalIDs -> ExternalIDs -> Bool # (>) :: ExternalIDs -> ExternalIDs -> Bool # (>=) :: ExternalIDs -> ExternalIDs -> Bool # max :: ExternalIDs -> ExternalIDs -> ExternalIDs # min :: ExternalIDs -> ExternalIDs -> ExternalIDs # | |
newtype ExternalURLs Source #
Constructors
| ExternalURLs | |
Instances
| FromJSON ExternalURLs Source # | |
Defined in Spotify.Types.Misc | |
| Show ExternalURLs Source # | |
Defined in Spotify.Types.Misc Methods showsPrec :: Int -> ExternalURLs -> ShowS # show :: ExternalURLs -> String # showList :: [ExternalURLs] -> ShowS # | |
| Eq ExternalURLs Source # | |
Defined in Spotify.Types.Misc | |
| Ord ExternalURLs Source # | |
Defined in Spotify.Types.Misc Methods compare :: ExternalURLs -> ExternalURLs -> Ordering # (<) :: ExternalURLs -> ExternalURLs -> Bool # (<=) :: ExternalURLs -> ExternalURLs -> Bool # (>) :: ExternalURLs -> ExternalURLs -> Bool # (>=) :: ExternalURLs -> ExternalURLs -> Bool # max :: ExternalURLs -> ExternalURLs -> ExternalURLs # min :: ExternalURLs -> ExternalURLs -> ExternalURLs # | |
Constructors