Safe Haskell | None |
---|---|
Language | Haskell2010 |
Utils.Spoty.Types
Description
Object declarations and lenses. Should not be imported by user code. Please view the official documentation.
Note that the distinction between full and simple objects is implemented as an optional Maybe field with details.
- type URL = Text
- type SpotID = Text
- type SpotURI = Text
- require :: FromJSON a => Text -> HashMap Text Value -> Parser (Maybe a)
- parseStrMap :: MonadPlus m => HashMap k Value -> (k -> Text -> a) -> m [a]
- data ExternalID = ExternalID {
- _idType :: Text
- _idIdentifier :: Text
- class HasType c e | c -> e where
- class HasIdentifier c e | c -> e where
- identifier :: Lens' c e
- _idTypeLens :: Lens' ExternalID Text
- _idIdentifierLens :: Lens' ExternalID Text
- data ExternalURL = ExternalURL {}
- _urlTypeLens :: Lens' ExternalURL Text
- data Image = Image {
- _imageHeight :: Maybe Int
- _imagePath :: URL
- _imageWidth :: Maybe Int
- class HasHeight c e | c -> e where
- class HasPath c e | c -> e where
- class HasWidth c e | c -> e where
- _imageWidthLens :: Lens' Image (Maybe Int)
- _imagePathLens :: Lens' Image URL
- _imageHeightLens :: Lens' Image (Maybe Int)
- data Paging a = Paging {
- _pagingHref :: Text
- _pagingItems :: [a]
- _pagingLimit :: Int
- _pagingNext :: Maybe URL
- _pagingOffset :: Int
- _pagingPrevious :: Maybe URL
- _pagingTotal :: Int
- class HasHref c e | c -> e where
- class HasItems c e | c -> e where
- class HasLimit c e | c -> e where
- class HasNext c e | c -> e where
- class HasOffset c e | c -> e where
- class HasPrevious c e | c -> e where
- class HasTotal c e | c -> e where
- _pagingTotalLens :: forall a. Lens' (Paging a) Int
- _pagingPreviousLens :: forall a. Lens' (Paging a) (Maybe URL)
- _pagingOffsetLens :: forall a. Lens' (Paging a) Int
- _pagingNextLens :: forall a. Lens' (Paging a) (Maybe URL)
- _pagingLimitLens :: forall a. Lens' (Paging a) Int
- _pagingItemsLens :: forall a a. Lens (Paging a) (Paging a) [a] [a]
- _pagingHrefLens :: forall a. Lens' (Paging a) Text
- data User = User {}
- class HasExternalUrls c e | c -> e where
- externalUrls :: Lens' c e
- class HasSpotifyID c e | c -> e where
- class HasSpotifyURI c e | c -> e where
- spotifyURI :: Lens' c e
- _userSpotifyURILens :: Lens' User SpotURI
- _userSpotifyIDLens :: Lens' User SpotID
- _userHrefLens :: Lens' User URL
- _userExternalUrlsLens :: Lens' User [ExternalURL]
- data ArtistDetails = ArtistDetails {
- _artistGenres :: [Text]
- _artistImages :: [Image]
- _artistPopularity :: Int
- class HasGenres c e | c -> e where
- class HasImages c e | c -> e where
- class HasPopularity c e | c -> e where
- popularity :: Lens' c e
- _artistPopularityLens :: Lens' ArtistDetails Int
- _artistImagesLens :: Lens' ArtistDetails [Image]
- _artistGenresLens :: Lens' ArtistDetails [Text]
- data Artist = Artist {}
- class HasName c e | c -> e where
- class HasDetails c e | c -> e where
- _artistSpotifyURILens :: Lens' Artist SpotURI
- _artistSpotifyIDLens :: Lens' Artist SpotID
- _artistNameLens :: Lens' Artist Text
- _artistHrefLens :: Lens' Artist URL
- _artistExternalUrlsLens :: Lens' Artist [ExternalURL]
- _artistDetailsLens :: Lens' Artist (Maybe ArtistDetails)
- data TrackDetails = TrackDetails {}
- class HasAvailableMarkets c e | c -> e where
- availableMarkets :: Lens' c e
- class HasExternalIDs c e | c -> e where
- externalIDs :: Lens' c e
- _trackPopularityLens :: Lens' TrackDetails Int
- _trackExternalIDsLens :: Lens' TrackDetails [ExternalID]
- _trackAvailableMarketsLens :: Lens' TrackDetails [Text]
- data Track = Track {}
- class HasArtists c e | c -> e where
- class HasDiscNumber c e | c -> e where
- discNumber :: Lens' c e
- class HasDurationMs c e | c -> e where
- durationMs :: Lens' c e
- class HasExplicit c e | c -> e where
- class HasPreviewURL c e | c -> e where
- previewURL :: Lens' c e
- class HasNumber c e | c -> e where
- _trackSpotifyURILens :: Lens' Track SpotURI
- _trackSpotifyIDLens :: Lens' Track SpotID
- _trackPreviewURLLens :: Lens' Track URL
- _trackNumberLens :: Lens' Track Int
- _trackNameLens :: Lens' Track Text
- _trackHrefLens :: Lens' Track URL
- _trackExternalUrlsLens :: Lens' Track [ExternalURL]
- _trackExplicitLens :: Lens' Track Bool
- _trackDurationMsLens :: Lens' Track Int
- _trackDiscNumberLens :: Lens' Track Int
- _trackDetailsLens :: Lens' Track (Maybe TrackDetails)
- _trackArtistsLens :: Lens' Track [Artist]
- data AlbumDetails = AlbumDetails {}
- class HasReleaseDate c e | c -> e where
- releaseDate :: Lens' c e
- class HasReleaseDatePrecision c e | c -> e where
- releaseDatePrecision :: Lens' c e
- class HasTracks c e | c -> e where
- _albumTracksLens :: Lens' AlbumDetails (Paging Track)
- _albumReleaseDatePrecisionLens :: Lens' AlbumDetails Text
- _albumReleaseDateLens :: Lens' AlbumDetails Text
- _albumPopularityLens :: Lens' AlbumDetails Int
- _albumGenresLens :: Lens' AlbumDetails [Text]
- _albumExternalIDsLens :: Lens' AlbumDetails [ExternalID]
- _albumArtistsLens :: Lens' AlbumDetails [Artist]
- data Album = Album {}
- class HasExternalURLs c e | c -> e where
- externalURLs :: Lens' c e
- _albumTypeLens :: Lens' Album Text
- _albumSpotifyURILens :: Lens' Album SpotURI
- _albumSpotifyIDLens :: Lens' Album SpotID
- _albumNameLens :: Lens' Album Text
- _albumImagesLens :: Lens' Album [Image]
- _albumHrefLens :: Lens' Album Text
- _albumExternalURLsLens :: Lens' Album [ExternalURL]
- _albumDetailsLens :: Lens' Album (Maybe AlbumDetails)
- _albumAvailableMarketsLens :: Lens' Album [Text]
Documentation
require :: FromJSON a => Text -> HashMap Text Value -> Parser (Maybe a) Source
Require that a field is present before parsing the corresponding value.
parseStrMap :: MonadPlus m => HashMap k Value -> (k -> Text -> a) -> m [a] Source
Parse a map of key-value entries, wrapped in the given constructor.
data ExternalID Source
Constructors
ExternalID | |
Fields
|
data ExternalURL Source
Constructors
ExternalURL | |
Constructors
Image | |
Fields
|
Constructors
Paging | |
Fields
|
Instances
HasTracks AlbumDetails (Paging Track) | |
Eq a => Eq (Paging a) | |
Ord a => Ord (Paging a) | |
Show a => Show (Paging a) | |
FromJSON a => FromJSON (Paging a) | |
HasTotal (Paging a) Int | |
HasOffset (Paging a) Int | |
HasLimit (Paging a) Int | |
HasHref (Paging a) Text | |
HasPrevious (Paging a) (Maybe URL) | |
HasNext (Paging a) (Maybe URL) | |
HasItems (Paging a) [a] |
class HasPrevious c e | c -> e where Source
Instances
HasPrevious (Paging a) (Maybe URL) |
_pagingTotalLens :: forall a. Lens' (Paging a) Int Source
_pagingOffsetLens :: forall a. Lens' (Paging a) Int Source
_pagingLimitLens :: forall a. Lens' (Paging a) Int Source
_pagingItemsLens :: forall a a. Lens (Paging a) (Paging a) [a] [a] Source
_pagingHrefLens :: forall a. Lens' (Paging a) Text Source
Constructors
User | |
Fields
|
class HasExternalUrls c e | c -> e where Source
Methods
externalUrls :: Lens' c e Source
class HasSpotifyID c e | c -> e where Source
class HasSpotifyURI c e | c -> e where Source
Methods
spotifyURI :: Lens' c e Source
data ArtistDetails Source
Constructors
ArtistDetails | |
Fields
|
class HasPopularity c e | c -> e where Source
Methods
popularity :: Lens' c e Source
Constructors
Artist | |
Fields |
class HasDetails c e | c -> e where Source
Instances
data TrackDetails Source
Constructors
TrackDetails | |
Fields
|
class HasAvailableMarkets c e | c -> e where Source
Methods
availableMarkets :: Lens' c e Source
Instances
Constructors
Track | |
Fields
|
Instances
class HasArtists c e | c -> e where Source
Instances
class HasExplicit c e | c -> e where Source
Instances
data AlbumDetails Source
Constructors
AlbumDetails | |
Fields
|
Instances
class HasReleaseDatePrecision c e | c -> e where Source
Methods
releaseDatePrecision :: Lens' c e Source
Instances
Constructors
Album | |
Fields
|