spotify-0.1.0.1: Spotify Web API
Safe HaskellSafe-Inferred
LanguageGHC2021

Spotify.Types.Misc

Documentation

data Copyright Source #

Constructors

Copyright 

Fields

Instances

Instances details
FromJSON Copyright Source # 
Instance details

Defined in Spotify.Types.Misc

Generic Copyright Source # 
Instance details

Defined in Spotify.Types.Misc

Associated Types

type Rep Copyright :: Type -> Type #

Show Copyright Source # 
Instance details

Defined in Spotify.Types.Misc

Eq Copyright Source # 
Instance details

Defined in Spotify.Types.Misc

Ord Copyright Source # 
Instance details

Defined in Spotify.Types.Misc

type Rep Copyright Source # 
Instance details

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 #

Constructors

C 
P 

Instances

Instances details
FromJSON CopyrightType Source # 
Instance details

Defined in Spotify.Types.Misc

Generic CopyrightType Source # 
Instance details

Defined in Spotify.Types.Misc

Associated Types

type Rep CopyrightType :: Type -> Type #

Show CopyrightType Source # 
Instance details

Defined in Spotify.Types.Misc

Eq CopyrightType Source # 
Instance details

Defined in Spotify.Types.Misc

Ord CopyrightType Source # 
Instance details

Defined in Spotify.Types.Misc

type Rep CopyrightType Source # 
Instance details

Defined in Spotify.Types.Misc

type Rep CopyrightType = D1 ('MetaData "CopyrightType" "Spotify.Types.Misc" "spotify-0.1.0.1-DSXk6mPWfQGGnICPbDr6pO-spotify-types" 'False) (C1 ('MetaCons "C" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "P" 'PrefixI 'False) (U1 :: Type -> Type))

data Error Source #

Constructors

Error 

Fields

Instances

Instances details
FromJSON Error Source # 
Instance details

Defined in Spotify.Types.Misc

Generic Error Source # 
Instance details

Defined in Spotify.Types.Misc

Associated Types

type Rep Error :: Type -> Type #

Methods

from :: Error -> Rep Error x #

to :: Rep Error x -> Error #

Show Error Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

showsPrec :: Int -> Error -> ShowS #

show :: Error -> String #

showList :: [Error] -> ShowS #

Eq Error Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

(==) :: Error -> Error -> Bool #

(/=) :: Error -> Error -> Bool #

Ord Error Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

compare :: Error -> Error -> Ordering #

(<) :: Error -> Error -> Bool #

(<=) :: Error -> Error -> Bool #

(>) :: Error -> Error -> Bool #

(>=) :: Error -> Error -> Bool #

max :: Error -> Error -> Error #

min :: Error -> Error -> Error #

type Rep Error Source # 
Instance details

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)))

data Followers Source #

Constructors

Followers 

Fields

Instances

Instances details
FromJSON Followers Source # 
Instance details

Defined in Spotify.Types.Misc

Generic Followers Source # 
Instance details

Defined in Spotify.Types.Misc

Associated Types

type Rep Followers :: Type -> Type #

Show Followers Source # 
Instance details

Defined in Spotify.Types.Misc

Eq Followers Source # 
Instance details

Defined in Spotify.Types.Misc

Ord Followers Source # 
Instance details

Defined in Spotify.Types.Misc

type Rep Followers Source # 
Instance details

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)))

data Image Source #

Constructors

Image 

Fields

Instances

Instances details
FromJSON Image Source # 
Instance details

Defined in Spotify.Types.Misc

Generic Image Source # 
Instance details

Defined in Spotify.Types.Misc

Associated Types

type Rep Image :: Type -> Type #

Methods

from :: Image -> Rep Image x #

to :: Rep Image x -> Image #

Show Image Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

showsPrec :: Int -> Image -> ShowS #

show :: Image -> String #

showList :: [Image] -> ShowS #

Eq Image Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

(==) :: Image -> Image -> Bool #

(/=) :: Image -> Image -> Bool #

Ord Image Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

compare :: Image -> Image -> Ordering #

(<) :: Image -> Image -> Bool #

(<=) :: Image -> Image -> Bool #

(>) :: Image -> Image -> Bool #

(>=) :: Image -> Image -> Bool #

max :: Image -> Image -> Image #

min :: Image -> Image -> Image #

type Rep Image Source # 
Instance details

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)))))

data Paging a Source #

Constructors

Paging 

Fields

Instances

Instances details
(FromJSON a, Typeable a) => FromJSON (Paging a) Source # 
Instance details

Defined in Spotify.Types.Misc

Generic (Paging a) Source # 
Instance details

Defined in Spotify.Types.Misc

Associated Types

type Rep (Paging a) :: Type -> Type #

Methods

from :: Paging a -> Rep (Paging a) x #

to :: Rep (Paging a) x -> Paging a #

Show a => Show (Paging a) Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

showsPrec :: Int -> Paging a -> ShowS #

show :: Paging a -> String #

showList :: [Paging a] -> ShowS #

Eq a => Eq (Paging a) Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

(==) :: Paging a -> Paging a -> Bool #

(/=) :: Paging a -> Paging a -> Bool #

Ord a => Ord (Paging a) Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

compare :: Paging a -> Paging a -> Ordering #

(<) :: Paging a -> Paging a -> Bool #

(<=) :: Paging a -> Paging a -> Bool #

(>) :: Paging a -> Paging a -> Bool #

(>=) :: Paging a -> Paging a -> Bool #

max :: Paging a -> Paging a -> Paging a #

min :: Paging a -> Paging a -> Paging a #

type Rep (Paging a) Source # 
Instance details

Defined in Spotify.Types.Misc

data Tracks Source #

Constructors

Tracks 

Fields

Instances

Instances details
FromJSON Tracks Source # 
Instance details

Defined in Spotify.Types.Misc

Generic Tracks Source # 
Instance details

Defined in Spotify.Types.Misc

Associated Types

type Rep Tracks :: Type -> Type #

Methods

from :: Tracks -> Rep Tracks x #

to :: Rep Tracks x -> Tracks #

Show Tracks Source # 
Instance details

Defined in Spotify.Types.Misc

Eq Tracks Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

(==) :: Tracks -> Tracks -> Bool #

(/=) :: Tracks -> Tracks -> Bool #

Ord Tracks Source # 
Instance details

Defined in Spotify.Types.Misc

type Rep Tracks Source # 
Instance details

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 #

Instances

Instances details
FromJSON DatePrecision Source # 
Instance details

Defined in Spotify.Types.Misc

Generic DatePrecision Source # 
Instance details

Defined in Spotify.Types.Misc

Associated Types

type Rep DatePrecision :: Type -> Type #

Show DatePrecision Source # 
Instance details

Defined in Spotify.Types.Misc

Eq DatePrecision Source # 
Instance details

Defined in Spotify.Types.Misc

Ord DatePrecision Source # 
Instance details

Defined in Spotify.Types.Misc

type Rep DatePrecision Source # 
Instance details

Defined in Spotify.Types.Misc

type Rep DatePrecision = D1 ('MetaData "DatePrecision" "Spotify.Types.Misc" "spotify-0.1.0.1-DSXk6mPWfQGGnICPbDr6pO-spotify-types" 'False) (C1 ('MetaCons "DatePrecisionYear" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DatePrecisionMonth" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DatePrecisionDay" 'PrefixI 'False) (U1 :: Type -> Type)))

data Key Source #

Instances

Instances details
FromJSON Key Source # 
Instance details

Defined in Spotify.Types.Misc

Enum Key Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

succ :: Key -> Key #

pred :: Key -> Key #

toEnum :: Int -> Key #

fromEnum :: Key -> Int #

enumFrom :: Key -> [Key] #

enumFromThen :: Key -> Key -> [Key] #

enumFromTo :: Key -> Key -> [Key] #

enumFromThenTo :: Key -> Key -> Key -> [Key] #

Generic Key Source # 
Instance details

Defined in Spotify.Types.Misc

Associated Types

type Rep Key :: Type -> Type #

Methods

from :: Key -> Rep Key x #

to :: Rep Key x -> Key #

Show Key Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

Eq Key Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

(==) :: Key -> Key -> Bool #

(/=) :: Key -> Key -> Bool #

Ord Key Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

compare :: Key -> Key -> Ordering #

(<) :: Key -> Key -> Bool #

(<=) :: Key -> Key -> Bool #

(>) :: Key -> Key -> Bool #

(>=) :: Key -> Key -> Bool #

max :: Key -> Key -> Key #

min :: Key -> Key -> Key #

type Rep Key Source # 
Instance details

Defined in Spotify.Types.Misc

type Rep Key = D1 ('MetaData "Key" "Spotify.Types.Misc" "spotify-0.1.0.1-DSXk6mPWfQGGnICPbDr6pO-spotify-types" 'False) (((C1 ('MetaCons "KeyC" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KeyCSharp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KeyD" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "KeyDSharp" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KeyE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KeyF" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "KeyFSharp" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KeyG" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KeyGSharp" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "KeyA" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KeyASharp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KeyB" 'PrefixI 'False) (U1 :: Type -> Type)))))

data TrackLink Source #

Constructors

TrackLink 

Instances

data AlbumGroup Source #

Instances

Instances details
FromJSON AlbumGroup Source # 
Instance details

Defined in Spotify.Types.Misc

Generic AlbumGroup Source # 
Instance details

Defined in Spotify.Types.Misc

Associated Types

type Rep AlbumGroup :: Type -> Type #

Show AlbumGroup Source # 
Instance details

Defined in Spotify.Types.Misc

Eq AlbumGroup Source # 
Instance details

Defined in Spotify.Types.Misc

Ord AlbumGroup Source # 
Instance details

Defined in Spotify.Types.Misc

type Rep AlbumGroup Source # 
Instance details

Defined in Spotify.Types.Misc

type Rep AlbumGroup = D1 ('MetaData "AlbumGroup" "Spotify.Types.Misc" "spotify-0.1.0.1-DSXk6mPWfQGGnICPbDr6pO-spotify-types" 'False) ((C1 ('MetaCons "GroupAlbum" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GroupSingle" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GroupCompilation" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AppearsOn" 'PrefixI 'False) (U1 :: Type -> Type)))

data AlbumType Source #

Instances

Instances details
FromJSON AlbumType Source # 
Instance details

Defined in Spotify.Types.Misc

Generic AlbumType Source # 
Instance details

Defined in Spotify.Types.Misc

Associated Types

type Rep AlbumType :: Type -> Type #

Show AlbumType Source # 
Instance details

Defined in Spotify.Types.Misc

Eq AlbumType Source # 
Instance details

Defined in Spotify.Types.Misc

Ord AlbumType Source # 
Instance details

Defined in Spotify.Types.Misc

type Rep AlbumType Source # 
Instance details

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 

Instances

Instances details
FromJSON ExplicitContent Source # 
Instance details

Defined in Spotify.Types.Misc

Generic ExplicitContent Source # 
Instance details

Defined in Spotify.Types.Misc

Associated Types

type Rep ExplicitContent :: Type -> Type #

Show ExplicitContent Source # 
Instance details

Defined in Spotify.Types.Misc

Eq ExplicitContent Source # 
Instance details

Defined in Spotify.Types.Misc

Ord ExplicitContent Source # 
Instance details

Defined in Spotify.Types.Misc

type Rep ExplicitContent Source # 
Instance details

Defined in Spotify.Types.Misc

type Rep ExplicitContent = D1 ('MetaData "ExplicitContent" "Spotify.Types.Misc" "spotify-0.1.0.1-DSXk6mPWfQGGnICPbDr6pO-spotify-types" 'False) (C1 ('MetaCons "ExplicitContent" 'PrefixI 'True) (S1 ('MetaSel ('Just "filterEnabled") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "filterLocked") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))

data Product Source #

Constructors

Premium 
Free 

Instances

Instances details
FromJSON Product Source # 
Instance details

Defined in Spotify.Types.Misc

Generic Product Source # 
Instance details

Defined in Spotify.Types.Misc

Associated Types

type Rep Product :: Type -> Type #

Methods

from :: Product -> Rep Product x #

to :: Rep Product x -> Product #

Show Product Source # 
Instance details

Defined in Spotify.Types.Misc

Eq Product Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

(==) :: Product -> Product -> Bool #

(/=) :: Product -> Product -> Bool #

Ord Product Source # 
Instance details

Defined in Spotify.Types.Misc

type Rep Product Source # 
Instance details

Defined in Spotify.Types.Misc

type Rep Product = D1 ('MetaData "Product" "Spotify.Types.Misc" "spotify-0.1.0.1-DSXk6mPWfQGGnICPbDr6pO-spotify-types" 'False) (C1 ('MetaCons "Premium" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Free" 'PrefixI 'False) (U1 :: Type -> Type))

data Offset Source #

Constructors

Offset 

Fields

Instances

Instances details
ToJSON Offset Source # 
Instance details

Defined in Spotify.Types.Misc

Generic Offset Source # 
Instance details

Defined in Spotify.Types.Misc

Associated Types

type Rep Offset :: Type -> Type #

Methods

from :: Offset -> Rep Offset x #

to :: Rep Offset x -> Offset #

Show Offset Source # 
Instance details

Defined in Spotify.Types.Misc

Eq Offset Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

(==) :: Offset -> Offset -> Bool #

(/=) :: Offset -> Offset -> Bool #

Ord Offset Source # 
Instance details

Defined in Spotify.Types.Misc

type Rep Offset Source # 
Instance details

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))))

newtype Market Source #

Constructors

Market 

Fields

Instances

Instances details
IsString Market Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

fromString :: String -> Market #

Show Market Source # 
Instance details

Defined in Spotify.Types.Misc

Eq Market Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

(==) :: Market -> Market -> Bool #

(/=) :: Market -> Market -> Bool #

Ord Market Source # 
Instance details

Defined in Spotify.Types.Misc

ToHttpApiData Market Source # 
Instance details

Defined in Spotify.Types.Misc

newtype Genre Source #

Constructors

Genre 

Fields

Instances

Instances details
FromJSON Genre Source # 
Instance details

Defined in Spotify.Types.Misc

IsString Genre Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

fromString :: String -> Genre #

Show Genre Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

showsPrec :: Int -> Genre -> ShowS #

show :: Genre -> String #

showList :: [Genre] -> ShowS #

Eq Genre Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

(==) :: Genre -> Genre -> Bool #

(/=) :: Genre -> Genre -> Bool #

Ord Genre Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

compare :: Genre -> Genre -> Ordering #

(<) :: Genre -> Genre -> Bool #

(<=) :: Genre -> Genre -> Bool #

(>) :: Genre -> Genre -> Bool #

(>=) :: Genre -> Genre -> Bool #

max :: Genre -> Genre -> Genre #

min :: Genre -> Genre -> Genre #

newtype Href Source #

Constructors

Href 

Fields

Instances

Instances details
FromJSON Href Source # 
Instance details

Defined in Spotify.Types.Misc

IsString Href Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

fromString :: String -> Href #

Show Href Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

showsPrec :: Int -> Href -> ShowS #

show :: Href -> String #

showList :: [Href] -> ShowS #

Eq Href Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

(==) :: Href -> Href -> Bool #

(/=) :: Href -> Href -> Bool #

Ord Href Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

compare :: Href -> Href -> Ordering #

(<) :: Href -> Href -> Bool #

(<=) :: Href -> Href -> Bool #

(>) :: Href -> Href -> Bool #

(>=) :: Href -> Href -> Bool #

max :: Href -> Href -> Href #

min :: Href -> Href -> Href #

class ToURI a where Source #

Methods

toURI :: a -> URI Source #

Instances

Instances details
ToURI AlbumID Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

toURI :: AlbumID -> URI Source #

ToURI ArtistID Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

toURI :: ArtistID -> URI Source #

ToURI EpisodeID Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

toURI :: EpisodeID -> URI Source #

ToURI PlaylistID Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

toURI :: PlaylistID -> URI Source #

ToURI TrackID Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

toURI :: TrackID -> URI Source #

ToURI UserID Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

toURI :: UserID -> URI Source #

(KnownSymbol s, HasField "unwrap" a Text) => ToURI (URIPrefix s a) Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

toURI :: URIPrefix s a -> URI Source #

newtype URIPrefix (s :: Symbol) a Source #

Constructors

URIPrefix a 

Instances

Instances details
(KnownSymbol s, HasField "unwrap" a Text) => ToURI (URIPrefix s a) Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

toURI :: URIPrefix s a -> URI Source #

newtype DeviceID Source #

Constructors

DeviceID 

Fields

newtype AlbumID Source #

Constructors

AlbumID 

Fields

Instances

Instances details
FromJSON AlbumID Source # 
Instance details

Defined in Spotify.Types.Misc

ToJSON AlbumID Source # 
Instance details

Defined in Spotify.Types.Misc

IsString AlbumID Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

fromString :: String -> AlbumID #

Show AlbumID Source # 
Instance details

Defined in Spotify.Types.Misc

Eq AlbumID Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

(==) :: AlbumID -> AlbumID -> Bool #

(/=) :: AlbumID -> AlbumID -> Bool #

Ord AlbumID Source # 
Instance details

Defined in Spotify.Types.Misc

ToHttpApiData AlbumID Source # 
Instance details

Defined in Spotify.Types.Misc

ToURI AlbumID Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

toURI :: AlbumID -> URI Source #

newtype ArtistID Source #

Constructors

ArtistID 

Fields

Instances

Instances details
FromJSON ArtistID Source # 
Instance details

Defined in Spotify.Types.Misc

ToJSON ArtistID Source # 
Instance details

Defined in Spotify.Types.Misc

IsString ArtistID Source # 
Instance details

Defined in Spotify.Types.Misc

Show ArtistID Source # 
Instance details

Defined in Spotify.Types.Misc

Eq ArtistID Source # 
Instance details

Defined in Spotify.Types.Misc

Ord ArtistID Source # 
Instance details

Defined in Spotify.Types.Misc

ToHttpApiData ArtistID Source # 
Instance details

Defined in Spotify.Types.Misc

ToURI ArtistID Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

toURI :: ArtistID -> URI Source #

newtype EpisodeID Source #

Constructors

EpisodeID 

Fields

Instances

Instances details
FromJSON EpisodeID Source # 
Instance details

Defined in Spotify.Types.Misc

ToJSON EpisodeID Source # 
Instance details

Defined in Spotify.Types.Misc

IsString EpisodeID Source # 
Instance details

Defined in Spotify.Types.Misc

Show EpisodeID Source # 
Instance details

Defined in Spotify.Types.Misc

Eq EpisodeID Source # 
Instance details

Defined in Spotify.Types.Misc

Ord EpisodeID Source # 
Instance details

Defined in Spotify.Types.Misc

ToHttpApiData EpisodeID Source # 
Instance details

Defined in Spotify.Types.Misc

ToURI EpisodeID Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

toURI :: EpisodeID -> URI Source #

newtype TrackID Source #

Constructors

TrackID 

Fields

Instances

Instances details
FromJSON TrackID Source # 
Instance details

Defined in Spotify.Types.Misc

ToJSON TrackID Source # 
Instance details

Defined in Spotify.Types.Misc

IsString TrackID Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

fromString :: String -> TrackID #

Show TrackID Source # 
Instance details

Defined in Spotify.Types.Misc

Eq TrackID Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

(==) :: TrackID -> TrackID -> Bool #

(/=) :: TrackID -> TrackID -> Bool #

Ord TrackID Source # 
Instance details

Defined in Spotify.Types.Misc

ToHttpApiData TrackID Source # 
Instance details

Defined in Spotify.Types.Misc

ToURI TrackID Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

toURI :: TrackID -> URI Source #

newtype UserID Source #

Constructors

UserID 

Fields

Instances

Instances details
FromJSON UserID Source # 
Instance details

Defined in Spotify.Types.Misc

ToJSON UserID Source # 
Instance details

Defined in Spotify.Types.Misc

IsString UserID Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

fromString :: String -> UserID #

Show UserID Source # 
Instance details

Defined in Spotify.Types.Misc

Eq UserID Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

(==) :: UserID -> UserID -> Bool #

(/=) :: UserID -> UserID -> Bool #

Ord UserID Source # 
Instance details

Defined in Spotify.Types.Misc

ToHttpApiData UserID Source # 
Instance details

Defined in Spotify.Types.Misc

ToURI UserID Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

toURI :: UserID -> URI Source #

newtype PlaylistID Source #

Constructors

PlaylistID 

Fields

Instances

Instances details
FromJSON PlaylistID Source # 
Instance details

Defined in Spotify.Types.Misc

ToJSON PlaylistID Source # 
Instance details

Defined in Spotify.Types.Misc

IsString PlaylistID Source # 
Instance details

Defined in Spotify.Types.Misc

Show PlaylistID Source # 
Instance details

Defined in Spotify.Types.Misc

Eq PlaylistID Source # 
Instance details

Defined in Spotify.Types.Misc

Ord PlaylistID Source # 
Instance details

Defined in Spotify.Types.Misc

ToHttpApiData PlaylistID Source # 
Instance details

Defined in Spotify.Types.Misc

ToURI PlaylistID Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

toURI :: PlaylistID -> URI Source #

newtype CategoryID Source #

Constructors

CategoryID 

Fields

Instances

Instances details
FromJSON CategoryID Source # 
Instance details

Defined in Spotify.Types.Misc

ToJSON CategoryID Source # 
Instance details

Defined in Spotify.Types.Misc

IsString CategoryID Source # 
Instance details

Defined in Spotify.Types.Misc

Show CategoryID Source # 
Instance details

Defined in Spotify.Types.Misc

Eq CategoryID Source # 
Instance details

Defined in Spotify.Types.Misc

Ord CategoryID Source # 
Instance details

Defined in Spotify.Types.Misc

ToHttpApiData CategoryID Source # 
Instance details

Defined in Spotify.Types.Misc

newtype SnapshotID Source #

Constructors

SnapshotID 

Fields

Instances

Instances details
FromJSON SnapshotID Source # 
Instance details

Defined in Spotify.Types.Misc

ToJSON SnapshotID Source # 
Instance details

Defined in Spotify.Types.Misc

IsString SnapshotID Source # 
Instance details

Defined in Spotify.Types.Misc

Show SnapshotID Source # 
Instance details

Defined in Spotify.Types.Misc

Eq SnapshotID Source # 
Instance details

Defined in Spotify.Types.Misc

Ord SnapshotID Source # 
Instance details

Defined in Spotify.Types.Misc

ToHttpApiData SnapshotID Source # 
Instance details

Defined in Spotify.Types.Misc

newtype URL Source #

Constructors

URL 

Fields

Instances

Instances details
FromJSON URL Source # 
Instance details

Defined in Spotify.Types.Misc

IsString URL Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

fromString :: String -> URL #

Show URL Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

showsPrec :: Int -> URL -> ShowS #

show :: URL -> String #

showList :: [URL] -> ShowS #

Eq URL Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

(==) :: URL -> URL -> Bool #

(/=) :: URL -> URL -> Bool #

Ord URL Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

compare :: URL -> URL -> Ordering #

(<) :: URL -> URL -> Bool #

(<=) :: URL -> URL -> Bool #

(>) :: URL -> URL -> Bool #

(>=) :: URL -> URL -> Bool #

max :: URL -> URL -> URL #

min :: URL -> URL -> URL #

ToHttpApiData URL Source # 
Instance details

Defined in Spotify.Types.Misc

newtype URI Source #

Constructors

URI 

Fields

Instances

Instances details
FromJSON URI Source # 
Instance details

Defined in Spotify.Types.Misc

ToJSON URI Source # 
Instance details

Defined in Spotify.Types.Misc

IsString URI Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

fromString :: String -> URI #

Show URI Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

showsPrec :: Int -> URI -> ShowS #

show :: URI -> String #

showList :: [URI] -> ShowS #

Eq URI Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

(==) :: URI -> URI -> Bool #

(/=) :: URI -> URI -> Bool #

Ord URI Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

compare :: URI -> URI -> Ordering #

(<) :: URI -> URI -> Bool #

(<=) :: URI -> URI -> Bool #

(>) :: URI -> URI -> Bool #

(>=) :: URI -> URI -> Bool #

max :: URI -> URI -> URI #

min :: URI -> URI -> URI #

newtype Country Source #

Constructors

Country 

Fields

Instances

Instances details
FromJSON Country Source # 
Instance details

Defined in Spotify.Types.Misc

ToJSON Country Source # 
Instance details

Defined in Spotify.Types.Misc

IsString Country Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

fromString :: String -> Country #

Show Country Source # 
Instance details

Defined in Spotify.Types.Misc

Eq Country Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

(==) :: Country -> Country -> Bool #

(/=) :: Country -> Country -> Bool #

Ord Country Source # 
Instance details

Defined in Spotify.Types.Misc

ToHttpApiData Country Source # 
Instance details

Defined in Spotify.Types.Misc

newtype Locale Source #

Constructors

Locale 

Fields

Instances

Instances details
FromJSON Locale Source # 
Instance details

Defined in Spotify.Types.Misc

ToJSON Locale Source # 
Instance details

Defined in Spotify.Types.Misc

IsString Locale Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

fromString :: String -> Locale #

Show Locale Source # 
Instance details

Defined in Spotify.Types.Misc

Eq Locale Source # 
Instance details

Defined in Spotify.Types.Misc

Methods

(==) :: Locale -> Locale -> Bool #

(/=) :: Locale -> Locale -> Bool #

Ord Locale Source # 
Instance details

Defined in Spotify.Types.Misc

ToHttpApiData Locale Source # 
Instance details

Defined in Spotify.Types.Misc

newtype HTTPError Source #

Constructors

HTTPError 

Fields

Instances

Instances details
FromJSON HTTPError Source # 
Instance details

Defined in Spotify.Types.Misc

Show HTTPError Source # 
Instance details

Defined in Spotify.Types.Misc

Eq HTTPError Source # 
Instance details

Defined in Spotify.Types.Misc

Ord HTTPError Source # 
Instance details

Defined in Spotify.Types.Misc