Jacob Clark
Jacob Clark

Reputation: 21

Creating an Aeson model from two wreq API calls

I'm looking to solve a problem where I construct some data from a HTTP call and then based off that data I make another HTTP call and enrich the original data with information from the second call.

I have code which takes a Spotify Recently Played API Call (JSON) via wreq as a ByteString and returns my a fully formed "RecentlyPlayed" data type.

However, in order to get the Genre of a Track in the Spotify API, a second HTTP call is needed to their artist endpoint, I'm not quite sure how I can modify my Track data type to add a "Genre" field in that I will populate later, I'm also unsure on how to actually populate it later too, clearly I need to loop through my original data structure, pull the artist ID out, call the new server - but I'm unsure how to add this additional data to the original data type.

{-# LANGUAGE OverloadedStrings #-}

module Types.RecentlyPlayed where

import qualified Data.ByteString.Lazy as L
import qualified Data.Vector as V
import Data.Aeson
import Data.Either

data Artist = Artist {
  id :: String
  , href :: String
  , artistName :: String
} deriving (Show)

data Track = Track {
  playedAt :: String
  , externalUrls :: String
  , name :: String
  , artists :: [Artist]
  , explicit :: Bool
} deriving (Show)

data Tracks = Tracks {
  tracks :: [Track]
} deriving (Show)

data RecentlyPlayed = RecentlyPlayed {
  recentlyPlayed :: Tracks
  , next :: String
} deriving (Show)

instance FromJSON RecentlyPlayed where
  parseJSON = withObject "items" $ \recentlyPlayed -> RecentlyPlayed 
    <$> recentlyPlayed .: "items"
    <*> recentlyPlayed .: "next"

instance FromJSON Tracks where
  parseJSON = withArray "items" $ \items -> Tracks 
    <$> mapM parseJSON (V.toList items)

instance FromJSON Track where
  parseJSON = withObject "tracks" $ \tracks -> Track 
    <$> tracks .: "played_at" 
    <*> (tracks .: "track" >>= (.: "album") >>= (.: "external_urls") >>= (.: "spotify"))
    <*> (tracks .: "track" >>= (.: "name"))
    <*> (tracks .: "track" >>= (.: "artists"))
    <*> (tracks .: "track" >>= (.: "explicit"))

instance FromJSON Artist where
  parseJSON = withObject "artists" $ \artists -> Artist
    <$> artists .: "id"
    <*> artists .: "href"
    <*> artists .: "name"

marshallRecentlyPlayedData :: L.ByteString -> Either String RecentlyPlayed
marshallRecentlyPlayedData recentlyPlayedTracks = eitherDecode recentlyPlayedTracks

(https://github.com/imjacobclark/Recify/blob/master/src/Types/RecentlyPlayed.hs)

This works brilliantly for a single API call, its usage can be seen here:

recentlyPlayedTrackData <- liftIO $ (getCurrentUsersRecentlyPlayedTracks (textToByteString . getAccessToken . AccessToken $ accessTokenFileData))

let maybeMarshalledRecentlyPlayed = (marshallRecentlyPlayedData recentlyPlayedTrackData)

(https://github.com/imjacobclark/Recify/blob/master/src/Recify.hs#L53-L55)

{-# LANGUAGE OverloadedStrings #-}

module Clients.Spotify.RecentlyPlayed where

import qualified Data.ByteString.Lazy as L
import qualified Data.ByteString.Char8 as B
import qualified Network.Wreq as W
import System.Environment
import Control.Monad.IO.Class
import Control.Lens

recentlyPlayerUri = "https://api.spotify.com/v1/me/player/recently-played"

getCurrentUsersRecentlyPlayedTracks :: B.ByteString -> IO L.ByteString
getCurrentUsersRecentlyPlayedTracks accessToken = do
  let options = W.defaults & W.header "Authorization" .~ [(B.pack "Bearer ") <> accessToken] 
  text <- liftIO $ (W.getWith options recentlyPlayerUri)
  return $ text ^. W.responseBody

(https://github.com/imjacobclark/Recify/blob/master/src/Clients/Spotify/RecentlyPlayed.hs)

I expect to be able to call the first API, construct my data type, call the second API and then enrich the first data type with data returned from the second HTTP call.

Upvotes: 2

Views: 97

Answers (1)

K. A. Buhr
K. A. Buhr

Reputation: 51129

As you undoubtedly know, unlike Javascript objects, Haskell ADTs aren't extensible, so you can't simple "add a field". In certain circumstances, it might make sense to include a field with a Maybe type originally set to Nothing that then gets populated. Rarely, it might make sense to perform the very unsafe operation of including the field with it's final type but its values initialized to bottom (i.e., undefined) and populated it later.

Alternatively, you might switch to some kind of explicitly extensible record type, like HList.

However, the most straightforward approach, and the one that makes use of the Haskell type system as intended, is to introduce a new type to represent a track augmented with genre information. If you have additional data types that incorporate Track fields which you want to reuse, they can be made polymorphic in the track type. So, given your data types above, you would introduce the new type:

data Track' = Track'
  { playedAt :: String
  , externalUrls :: String
  , name :: String
  , artists :: [Artist]
  , genres :: [Genre]     -- added field
  , explicit :: Bool
  }

(which requires the DuplicateRecordFields extension to coexist with Track) and make the dependent types polymorphic in the track type:

data Tracks trk = Tracks
  { tracks :: [trk]
  }

data RecentlyPlayed trk = RecentlyPlayed
  { recentlyPlayed :: Tracks trk
  , next :: String
  }

Conversion of a playlist can be accomplished using:

addGenre :: (Artist -> [Genre]) -> RecentlyPlayed Track -> RecentlyPlayed Track'
addGenre g (RecentlyPlayed (Tracks trks) nxt)
  = RecentlyPlayed (Tracks (map cvtTrack trks)) nxt
  where
    cvtTrack (Track p e n a ex) = Track' p e n a (concatMap g a) ex

or alternatively using the RecordWildCards extension, which will be much more readable especially for very large records:

addGenre' :: (Artist -> [Genre]) -> RecentlyPlayed Track -> RecentlyPlayed Track'
addGenre' g RecentlyPlayed{recentlyPlayed = Tracks trks, ..}
  = RecentlyPlayed{recentlyPlayed = Tracks (map cvtTrack trks), ..}
  where
    cvtTrack (Track{..}) = Track' { genres = concatMap g artists, .. }

or using a Lens approach, or even using deriving (Functor) instances with all the heavy lifting done by fmap:

addGenre'' :: (Artist -> [Genre]) -> RecentlyPlayed Track -> RecentlyPlayed Track'
addGenre'' g = fmap cvtTrack
  where
    cvtTrack (Track{..}) = Track' { genres = concatMap g artists, .. }

though the functor approach doesn't scale very well if multiple augmentations are in place (e.g., if you find you want to introduce a RecentlyPlayed artist track type). A Data.Generics approach might work well in this case.

From a more general design standpoint, though, you might want to ask yourself why you're trying to augment the RecentlyPlayed representation this way. This is a good representation of the required parts of the underlying Javascript API, but it's a poor representation to work with in the rest of your program logic.

Presumably, the rest of your program deals primarily with a list of tracks, and shouldn't concern itself with following next URLs, so why not generate the full list of genre-augmented tracks directly?

That is, given an initial RecentlyPlayed list and some IO functions to get the next list and look up genre information:

firstRecentlyPlayed :: RecentlyPlayed
getNextRecentlyPlayed :: String -> IO RecentlyPlayed
getGenresByArtist :: Artist -> IO [Genre]

you'd probably want something like:

getTracks :: IO [Track']
getTracks = go firstRecentlyPlayed
  where go :: RecentlyPlayed -> IO [Track']
        go (RecentlyPlayed (Tracks trks) next) = do
          trks' <- mapM getGenre trks
          rest <- go =<< getNextRecentlyPlayed next
          return $ trks' ++ rest
        getGenre Track{..} = do
          artistGenres <- mapM getGenresByArtist artists
          return (Track' {genres = concat artistGenres, ..})

for a first attempt. Of course, you'll want to modify this to avoid looking up genres for the same artist over and over, but that's the idea.

Upvotes: 0

Related Questions