2

我正在寻找解决一个问题,即我从 HTTP 调用构建一些数据,然后基于该数据进行另一个 HTTP 调用,并使用来自第二个调用的信息来丰富原始数据。

我的代码通过 wreq 将 Spotify 最近播放的 API 调用 (JSON) 作为 ByteString 并返回我完全形成的“RecentlyPlayed”数据类型。

但是,为了在 Spotify API 中获取曲目的流派,需要对其艺术家端点进行第二次 HTTP 调用,我不太确定如何修改我的 Track 数据类型以在其中添加“流派”字段我稍后会填充,我也不确定以后如何实际填充它,显然我需要遍历我的原始数据结构,拉出艺术家 ID,调用新服务器 - 但我不确定如何添加这个原始数据类型的附加数据。

{-# 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

这对于单个 API 调用非常有效,它的用法可以在这里看到:

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

我希望能够调用第一个 API,构造我的数据类型,调用第二个 API,然后使用第二个 HTTP 调用返回的数据丰富第一个数据类型。

4

1 回答 1

0

如您所知,与 Javascript 对象不同,Haskell ADT 不可扩展,因此您不能简单地“添加字段”。Maybe在某些情况下,包含一个类型最初设置为Nothing然后被填充的字段可能是有意义的。在极少数情况下,执行非常不安全的操作可能是有意义的,即包含具有最终类型但其值初始化为底部(即undefined)并稍后填充它的字段。

或者,您可以切换到某种显式可扩展的记录类型,例如HList.

然而,最直接的方法,也是按预期使用 Haskell 类型系统的方法,是引入一种新类型来表示增加了流派信息的曲目。如果您有包含Track要重用的字段的其他数据类型,则可以在轨道类型中将它们设置为多态。因此,鉴于上述数据类型,您将引入新类型:

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

(这需要DuplicateRecordFields扩展与 共存Track)并使依赖类型在轨道类型中具有多态性:

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

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

可以使用以下方式完成播放列表的转换:

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

或者使用RecordWildCards扩展名,这将更具可读性,尤其是对于非常大的记录:

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, .. }

或使用 Lens 方法,甚至使用deriving (Functor)实例来完成所有繁重的工作fmap

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

尽管如果有多个扩充(例如,如果您发现要引入一种RecentlyPlayed artist track类型),仿函数方法的扩展性就不是很好。在这种情况下,一种Data.Generics方法可能效果很好。

但是,从更一般的设计角度来看,您可能想问自己为什么要尝试以RecentlyPlayed这种方式增强表示。这是底层 Javascript API 所需部分的良好表示,但在您的程序逻辑的其余部分中使用它是一种较差的表示。

大概,您的程序的其余部分主要处理曲目列表,不应该关注以下nextURL,那么为什么不直接生成流派增强曲目的完整列表呢?

也就是说,给定一个初始RecentlyPlayed列表和一些 IO 函数来获取下一个列表并查找流派信息:

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

你可能想要这样的东西:

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, ..})

第一次尝试。当然,您需要修改它以避免一遍又一遍地查找同一艺术家的流派,但这就是想法。

于 2019-06-04T18:02:24.493 回答