{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
-- | Lastfm track API
--
-- This module is intended to be imported qualified:
--
-- @
-- import qualified Network.Lastfm.Track as Track
-- @
module Network.Lastfm.Track
  ( ArtistTrackOrMBID
  , addTags, ban, getBuyLinks, getCorrection, getFingerprintMetadata
  , getInfo, getShouts, getSimilar, getTags, getTopFans
  , getTopTags, love, removeTag, scrobble, item
  , search, share, unban, unlove, updateNowPlaying
  ) where

import           Control.Applicative
import           Data.List.NonEmpty (NonEmpty)
import qualified Data.List.NonEmpty as N

import Network.Lastfm.Internal (absorbQuery, indexedWith, wrap)
import Network.Lastfm.Request


-- | Unify ('Artist' -> 'Track' -> …) and ('MBID' -> …)
class ArtistTrackOrMBID a

instance ArtistTrackOrMBID (MBID -> APIKey -> Ready)
instance ArtistTrackOrMBID (Artist -> Track -> APIKey -> Ready)


-- | Tag a track using a list of user supplied tags.
--
-- <http://www.last.fm/api/show/track.addTags>
addTags :: Request f (Artist -> Track -> [Tag] -> APIKey -> SessionKey -> Sign)
addTags = api "track.addTags" <* post
{-# INLINE addTags #-}


-- | Ban a track for a given user profile.
--
-- <http://www.last.fm/api/show/track.ban>
ban :: Request f (Artist -> Track -> APIKey -> SessionKey -> Sign)
ban = api "track.ban" <* post
{-# INLINE ban #-}


-- | Get a list of Buy Links for a particular track.
--
-- Optional: 'autocorrect'
--
-- <http://www.last.fm/api/show/track.getBuylinks>
getBuyLinks :: ArtistTrackOrMBID t => Request f (Country -> t)
getBuyLinks = api "track.getBuyLinks"
{-# INLINE getBuyLinks #-}


-- | Use the last.fm corrections data to check whether
-- the supplied track has a correction to a canonical track.
--
-- <http://www.last.fm/api/show/track.getCorrection>
getCorrection :: Request f (Artist -> Track -> APIKey -> Ready)
getCorrection = api "track.getCorrection"
{-# INLINE getCorrection #-}


-- | Retrieve track metadata associated with a fingerprint id
-- generated by the Last.fm Fingerprinter. Returns track
-- elements, along with a 'rank' value between 0 and 1 reflecting the confidence for each match.
--
-- <http://www.last.fm/api/show/track.getFingerprintMetadata>
getFingerprintMetadata :: Request f (Fingerprint -> APIKey -> Ready)
getFingerprintMetadata = api "track.getFingerprintMetadata"
{-# INLINE getFingerprintMetadata #-}


-- | Get the metadata for a track on Last.fm.
--
-- Optional: 'autocorrect', 'username'
--
-- <http://www.last.fm/api/show/track.getInfo>
getInfo :: ArtistTrackOrMBID t => Request f t
getInfo = api "track.getInfo"
{-# INLINE getInfo #-}


-- | Get shouts for this track. Also available as an rss feed.
--
-- Optional: 'autocorrect', 'limit', 'page'
--
-- <http://www.last.fm/api/show/track.getShouts>
getShouts :: ArtistTrackOrMBID t => Request f t
getShouts = api "track.getShouts"
{-# INLINE getShouts #-}


-- | Get the similar tracks for this track on Last.fm, based on listening data.
--
-- Optional: 'autocorrect', 'limit'
--
-- <http://www.last.fm/api/show/track.getSimilar>
getSimilar :: ArtistTrackOrMBID t => Request f t
getSimilar = api "track.getSimilar"
{-# INLINE getSimilar #-}


-- | Get the tags applied by an individual user to a track on Last.fm.
--
-- Optional: 'autocorrect', 'user'
--
-- <http://www.last.fm/api/show/track.getTags>
getTags :: ArtistTrackOrMBID t => Request f t
getTags = api "track.getTags"
{-# INLINE getTags #-}


-- | Get the top fans for this track on Last.fm, based on listening data.
--
-- Optional: 'autocorrect'
--
-- <http://www.last.fm/api/show/track.getTopFans>
getTopFans :: ArtistTrackOrMBID t => Request f t
getTopFans = api "track.getTopFans"
{-# INLINE getTopFans #-}


-- | Get the top tags for this track on Last.fm, ordered by tag count.
--
-- Optional: 'autocorrect'
--
-- <http://www.last.fm/api/show/track.getTopTags>
getTopTags :: ArtistTrackOrMBID t => Request f t
getTopTags = api "track.getTopTags"
{-# INLINE getTopTags #-}


-- | Love a track for a user profile.
--
-- <http://www.last.fm/api/show/track.love>
love :: Request f (Artist -> Track -> APIKey -> SessionKey -> Sign)
love = api "track.love" <* post
{-# INLINE love #-}


-- | Remove a user's tag from a track.
--
-- <http://www.last.fm/api/show/track.removeTag>
removeTag :: Request f (Artist -> Track -> Tag -> APIKey -> SessionKey -> Sign)
removeTag = api "track.removeTag" <* post
{-# INLINE removeTag #-}


-- | Add played tracks to the user profile.
--
-- Scrobbles 50 first list elements
--
-- <http://www.last.fm/api/show/track.scrobble>
scrobble :: NonEmpty (Request f Scrobble) -> Request f (APIKey -> SessionKey -> Sign)
scrobble batch = api "track.scrobble" <* items <* post
 where
  items = absorbQuery (N.zipWith indexedWith (N.fromList [0..49]) batch)
  {-# INLINE items #-}
{-# INLINE scrobble #-}

-- | What track to scrobble?
--
-- Optional: 'album', 'albumArtist', 'chosenByUser', 'context',
-- 'duration', 'mbid', 'streamId', 'trackNumber'
item :: Request f (Artist -> Track -> Timestamp -> Scrobble)
item = wrap id
{-# INLINE item #-}


-- | Search for a track by track name. Returns track matches sorted by relevance.
--
-- Optional: 'artist', 'limit', 'page'
--
-- <http://www.last.fm/api/show/track.search>
search :: Request f (Track -> APIKey -> Ready)
search = api "track.search"
{-# INLINE search #-}


-- | Share a track twith one or more Last.fm users or other friends.
--
-- Optional: 'public', 'message', 'recipient'
--
-- <http://www.last.fm/api/show/track.share>
share :: Request f (Artist -> Track -> Recipient -> APIKey -> SessionKey -> Sign)
share = api "track.share" <* post
{-# INLINE share #-}


-- | Unban a track for a user profile.
--
-- <http://www.last.fm/api/show/track.unban>
unban :: Request f (Artist -> Track -> APIKey -> SessionKey -> Sign)
unban = api "track.unban" <* post
{-# INLINE unban #-}


-- | Unlove a track for a user profile.
--
-- <http://www.last.fm/api/show/track.unlove>
unlove :: Request f (Artist -> Track -> APIKey -> SessionKey -> Sign)
unlove = api "track.unlove" <* post
{-# INLINE unlove #-}


-- | Used to notify Last.fm that a user has started listening
-- to a track. Parameter names are case sensitive.
--
-- Optional: 'album', 'albumArtist', 'context',
-- 'duration', 'mbid', 'trackNumber'
--
-- <http://www.last.fm/api/show/track.updateNowPlaying>
updateNowPlaying :: Request f (Artist -> Track -> APIKey -> SessionKey -> Sign)
updateNowPlaying = api "track.updateNowPlaying" <* post
{-# INLINE updateNowPlaying #-}