N.M.Commands.hs: replaced intercalate with concat . intersperse for compatibility...
[libmpd_haskell.git] / Network / MPD / Commands.hs
blob2e7421b6a2a16c384952478dce51c14be48877d1
1 {-# LANGUAGE PatternGuards #-}
2 {-
3 libmpd for Haskell, an MPD client library.
4 Copyright (C) 2005-2008 Ben Sinclair <bsinclai@turing.une.edu.au>
6 This library is free software; you can redistribute it and/or
7 modify it under the terms of the GNU Lesser General Public
8 License as published by the Free Software Foundation; either
9 version 2.1 of the License, or (at your option) any later version.
11 This library is distributed in the hope that it will be useful,
12 but WITHOUT ANY WARRANTY; without even the implied warranty of
13 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
14 Lesser General Public License for more details.
16 You should have received a copy of the GNU Lesser General Public
17 License along with this library; if not, write to the Free Software
18 Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA
21 -- | Module : Network.MPD.Commands
22 -- Copyright : (c) Ben Sinclair 2005-2008
23 -- License : LGPL
24 -- Maintainer : bsinclai@turing.une.edu.au
25 -- Stability : alpha
26 -- Portability : unportable (uses PatternGuards)
28 -- Interface to the user commands supported by MPD.
30 module Network.MPD.Commands (
31 -- * Command related data types
32 State(..), Status(..), Stats(..),
33 Device(..),
34 Query(..), Meta(..),
35 Artist, Album, Title, Seconds, PlaylistName, Path,
36 PLIndex(..), Song(..), Count(..),
38 -- * Admin commands
39 disableOutput, enableOutput, kill, outputs, update,
41 -- * Database commands
42 find, list, listAll, listAllInfo, lsInfo, search, count,
44 -- * Playlist commands
45 -- $playlist
46 add, add_, addId, clear, currentSong, delete, load, move,
47 playlistInfo, listPlaylist, listPlaylistInfo, playlist, plChanges,
48 plChangesPosId, playlistFind, playlistSearch, rm, rename, save, shuffle,
49 swap,
51 -- * Playback commands
52 crossfade, next, pause, play, previous, random, repeat, seek, setVolume,
53 volume, stop,
55 -- * Miscellaneous commands
56 clearError, close, commands, notCommands, password, ping, reconnect, stats,
57 status, tagTypes, urlHandlers,
59 -- * Extensions\/shortcuts
60 addMany, deleteMany, complete, crop, prune, lsDirs, lsFiles, lsPlaylists,
61 findArtist, findAlbum, findTitle, listArtists, listAlbums, listAlbum,
62 searchArtist, searchAlbum, searchTitle, getPlaylist, toggle, updateId
63 ) where
65 import Network.MPD.Core
66 import Network.MPD.Utils
67 import Network.MPD.Parse
69 import Control.Monad (liftM, unless)
70 import Control.Monad.Error (throwError)
71 import Prelude hiding (repeat)
72 import Data.List (findIndex, intersperse, isPrefixOf)
73 import Data.Maybe
74 import System.FilePath (dropFileName)
77 -- Data types
80 type Artist = String
81 type Album = String
82 type Title = String
84 -- | Used for commands which require a playlist name.
85 -- If empty, the current playlist is used.
86 type PlaylistName = String
88 -- | Used for commands which require a path within the database.
89 -- If empty, the root path is used.
90 type Path = String
92 -- | Available metadata types\/scope modifiers, used for searching the
93 -- database for entries with certain metadata values.
94 data Meta = Artist | Album | Title | Track | Name | Genre | Date
95 | Composer | Performer | Disc | Any | Filename
96 deriving Show
98 -- | A query is composed of a scope modifier and a query string.
100 -- To match entries where album equals \"Foo\", use:
102 -- > Query Album "Foo"
104 -- To match entries where album equals \"Foo\" and artist equals \"Bar\", use:
106 -- > MultiQuery [Query Album "Foo", Query Artist "Bar"]
107 data Query = Query Meta String -- ^ Simple query.
108 | MultiQuery [Query] -- ^ Query with multiple conditions.
110 instance Show Query where
111 show (Query meta query) = show meta ++ " " ++ show query
112 show (MultiQuery xs) = show xs
113 showList xs _ = unwords $ map show xs
116 -- Admin commands
119 -- | Turn off an output device.
120 disableOutput :: Int -> MPD ()
121 disableOutput = getResponse_ . ("disableoutput " ++) . show
123 -- | Turn on an output device.
124 enableOutput :: Int -> MPD ()
125 enableOutput = getResponse_ . ("enableoutput " ++) . show
127 -- | Retrieve information for all output devices.
128 outputs :: MPD [Device]
129 outputs = getResponse "outputs" >>= runParser parseOutputs
131 -- | Update the server's database.
132 -- If no paths are given, all paths will be scanned.
133 -- Unreadable or non-existent paths are silently ignored.
134 update :: [Path] -> MPD ()
135 update [] = getResponse_ "update"
136 update [x] = getResponse_ ("update " ++ show x)
137 update xs = getResponses (map (("update " ++) . show) xs) >> return ()
140 -- Database commands
143 -- | List all metadata of metadata (sic).
144 list :: Meta -- ^ Metadata to list
145 -> Maybe Query -> MPD [String]
146 list mtype query = liftM takeValues (getResponse cmd)
147 where cmd = "list " ++ show mtype ++ maybe "" ((" "++) . show) query
149 -- | Non-recursively list the contents of a database directory.
150 lsInfo :: Path -> MPD [Either Path Song]
151 lsInfo = lsInfo' "lsinfo"
153 -- | List the songs (without metadata) in a database directory recursively.
154 listAll :: Path -> MPD [Path]
155 listAll path = liftM (map snd . filter ((== "file") . fst) . toAssoc)
156 (getResponse ("listall " ++ show path))
158 -- | Recursive 'lsInfo'.
159 listAllInfo :: Path -> MPD [Either Path Song]
160 listAllInfo = lsInfo' "listallinfo"
162 -- Helper for lsInfo and listAllInfo.
163 lsInfo' :: String -> Path -> MPD [Either Path Song]
164 lsInfo' cmd path = do
165 liftM (extractEntries (Just . Right, const Nothing, Just . Left)) $
166 takeEntries =<< getResponse (cmd ++ " " ++ show path)
168 -- | Search the database for entries exactly matching a query.
169 find :: Query -> MPD [Song]
170 find query = getResponse ("find " ++ show query) >>= takeSongs
172 -- | Search the database using case insensitive matching.
173 search :: Query -> MPD [Song]
174 search query = getResponse ("search " ++ show query) >>= takeSongs
176 -- | Count the number of entries matching a query.
177 count :: Query -> MPD Count
178 count query = getResponse ("count " ++ show query) >>= runParser parseCount
181 -- Playlist commands
183 -- $playlist
184 -- Unless otherwise noted all playlist commands operate on the current
185 -- playlist.
187 -- This might do better to throw an exception than silently return 0.
188 -- | Like 'add', but returns a playlist id.
189 addId :: Path -> MPD Integer
190 addId p = getResponse1 ("addid " ++ show p) >>=
191 parse parseNum id . snd . head . toAssoc
193 -- | Like 'add_' but returns a list of the files added.
194 add :: PlaylistName -> Path -> MPD [Path]
195 add plname x = add_ plname x >> listAll x
197 -- | Add a song (or a whole directory) to a playlist.
198 -- Adds to current if no playlist is specified.
199 -- Will create a new playlist if the one specified does not already exist.
200 add_ :: PlaylistName -> Path -> MPD ()
201 add_ "" = getResponse_ . ("add " ++) . show
202 add_ plname = getResponse_ .
203 (("playlistadd " ++ show plname ++ " ") ++) . show
205 -- | Clear a playlist. Clears current playlist if no playlist is specified.
206 -- If the specified playlist does not exist, it will be created.
207 clear :: PlaylistName -> MPD ()
208 clear = getResponse_ . cmd
209 where cmd "" = "clear"
210 cmd pl = "playlistclear " ++ show pl
212 -- | Remove a song from a playlist.
213 -- If no playlist is specified, current playlist is used.
214 -- Note that a playlist position ('Pos') is required when operating on
215 -- playlists other than the current.
216 delete :: PlaylistName -> PLIndex -> MPD ()
217 delete "" (Pos x) = getResponse_ ("delete " ++ show x)
218 delete "" (ID x) = getResponse_ ("deleteid " ++ show x)
219 delete plname (Pos x) =
220 getResponse_ ("playlistdelete " ++ show plname ++ " " ++ show x)
221 delete _ _ = fail "'delete' within a playlist doesn't accept a playlist ID"
223 -- | Load an existing playlist.
224 load :: PlaylistName -> MPD ()
225 load = getResponse_ . ("load " ++) . show
227 -- | Move a song to a given position.
228 -- Note that a playlist position ('Pos') is required when operating on
229 -- playlists other than the current.
230 move :: PlaylistName -> PLIndex -> Integer -> MPD ()
231 move "" (Pos from) to =
232 getResponse_ ("move " ++ show from ++ " " ++ show to)
233 move "" (ID from) to =
234 getResponse_ ("moveid " ++ show from ++ " " ++ show to)
235 move plname (Pos from) to =
236 getResponse_ ("playlistmove " ++ show plname ++ " " ++ show from ++
237 " " ++ show to)
238 move _ _ _ = fail "'move' within a playlist doesn't accept a playlist ID"
240 -- | Delete existing playlist.
241 rm :: PlaylistName -> MPD ()
242 rm = getResponse_ . ("rm " ++) . show
244 -- | Rename an existing playlist.
245 rename :: PlaylistName -- ^ Original playlist
246 -> PlaylistName -- ^ New playlist name
247 -> MPD ()
248 rename plname new =
249 getResponse_ ("rename " ++ show plname ++ " " ++ show new)
251 -- | Save the current playlist.
252 save :: PlaylistName -> MPD ()
253 save = getResponse_ . ("save " ++) . show
255 -- | Swap the positions of two songs.
256 -- Note that the positions must be of the same type, i.e. mixing 'Pos' and 'ID'
257 -- will result in a no-op.
258 swap :: PLIndex -> PLIndex -> MPD ()
259 swap (Pos x) (Pos y) = getResponse_ ("swap " ++ show x ++ " " ++ show y)
260 swap (ID x) (ID y) = getResponse_ ("swapid " ++ show x ++ " " ++ show y)
261 swap _ _ = fail "'swap' cannot mix position and ID arguments"
263 -- | Shuffle the playlist.
264 shuffle :: MPD ()
265 shuffle = getResponse_ "shuffle"
267 -- | Retrieve metadata for songs in the current playlist.
268 playlistInfo :: Maybe PLIndex -> MPD [Song]
269 playlistInfo x = getResponse cmd >>= takeSongs
270 where cmd = case x of
271 Just (Pos x') -> "playlistinfo " ++ show x'
272 Just (ID x') -> "playlistid " ++ show x'
273 Nothing -> "playlistinfo"
275 -- | Retrieve metadata for files in a given playlist.
276 listPlaylistInfo :: PlaylistName -> MPD [Song]
277 listPlaylistInfo plname =
278 takeSongs =<< (getResponse . ("listplaylistinfo " ++) $ show plname)
280 -- | Retrieve a list of files in a given playlist.
281 listPlaylist :: PlaylistName -> MPD [Path]
282 listPlaylist = liftM takeValues . getResponse . ("listplaylist " ++) . show
284 -- | Retrieve file paths and positions of songs in the current playlist.
285 -- Note that this command is only included for completeness sake; it's
286 -- deprecated and likely to disappear at any time, please use 'playlistInfo'
287 -- instead.
288 playlist :: MPD [(PLIndex, Path)]
289 playlist = mapM f =<< getResponse "playlist"
290 where f s | (pos, name) <- breakChar ':' s
291 , Just pos' <- parseNum pos
292 = return (Pos pos', name)
293 | otherwise = throwError . Unexpected $ show s
295 -- | Retrieve a list of changed songs currently in the playlist since
296 -- a given playlist version.
297 plChanges :: Integer -> MPD [Song]
298 plChanges version =
299 takeSongs =<< (getResponse . ("plchanges " ++) $ show version)
301 -- | Like 'plChanges' but only returns positions and ids.
302 plChangesPosId :: Integer -> MPD [(PLIndex, PLIndex)]
303 plChangesPosId plver =
304 getResponse ("plchangesposid " ++ show plver) >>=
305 mapM f . splitGroups [("cpos",id)] . toAssoc
306 where f xs | [("cpos", x), ("Id", y)] <- xs
307 , Just (x', y') <- pair parseNum (x, y)
308 = return (Pos x', ID y')
309 | otherwise = throwError . Unexpected $ show xs
311 -- | Search for songs in the current playlist with strict matching.
312 playlistFind :: Query -> MPD [Song]
313 playlistFind q = takeSongs =<< (getResponse . ("playlistfind " ++) $ show q)
315 -- | Search case-insensitively with partial matches for songs in the
316 -- current playlist.
317 playlistSearch :: Query -> MPD [Song]
318 playlistSearch q =
319 takeSongs =<< (getResponse . ("playlistsearch " ++) $ show q)
321 -- | Get the currently playing song.
322 currentSong :: MPD (Maybe Song)
323 currentSong = do
324 cs <- status
325 if stState cs == Stopped
326 then return Nothing
327 else getResponse1 "currentsong" >>=
328 fmap Just . runParser parseSong . toAssoc
331 -- Playback commands
334 -- | Set crossfading between songs.
335 crossfade :: Seconds -> MPD ()
336 crossfade = getResponse_ . ("crossfade " ++) . show
338 -- | Begin\/continue playing.
339 play :: Maybe PLIndex -> MPD ()
340 play Nothing = getResponse_ "play"
341 play (Just (Pos x)) = getResponse_ ("play " ++ show x)
342 play (Just (ID x)) = getResponse_ ("playid " ++ show x)
344 -- | Pause playing.
345 pause :: Bool -> MPD ()
346 pause = getResponse_ . ("pause " ++) . showBool
348 -- | Stop playing.
349 stop :: MPD ()
350 stop = getResponse_ "stop"
352 -- | Play the next song.
353 next :: MPD ()
354 next = getResponse_ "next"
356 -- | Play the previous song.
357 previous :: MPD ()
358 previous = getResponse_ "previous"
360 -- | Seek to some point in a song.
361 -- Seeks in current song if no position is given.
362 seek :: Maybe PLIndex -> Seconds -> MPD ()
363 seek (Just (Pos x)) time =
364 getResponse_ ("seek " ++ show x ++ " " ++ show time)
365 seek (Just (ID x)) time =
366 getResponse_ ("seekid " ++ show x ++ " " ++ show time)
367 seek Nothing time = do
368 st <- status
369 unless (stState st == Stopped) (seek (stSongID st) time)
371 -- | Set random playing.
372 random :: Bool -> MPD ()
373 random = getResponse_ . ("random " ++) . showBool
375 -- | Set repeating.
376 repeat :: Bool -> MPD ()
377 repeat = getResponse_ . ("repeat " ++) . showBool
379 -- | Set the volume (0-100 percent).
380 setVolume :: Int -> MPD ()
381 setVolume = getResponse_ . ("setvol " ++) . show
383 -- | Increase or decrease volume by a given percent, e.g.
384 -- 'volume 10' will increase the volume by 10 percent, while
385 -- 'volume (-10)' will decrease it by the same amount.
386 -- Note that this command is only included for completeness sake ; it's
387 -- deprecated and may disappear at any time, please use 'setVolume' instead.
388 volume :: Int -> MPD ()
389 volume = getResponse_ . ("volume " ++) . show
392 -- Miscellaneous commands
395 -- | Clear the current error message in status.
396 clearError :: MPD ()
397 clearError = getResponse_ "clearerror"
399 -- | Retrieve a list of available commands.
400 commands :: MPD [String]
401 commands = liftM takeValues (getResponse "commands")
403 -- | Retrieve a list of unavailable (due to access restrictions) commands.
404 notCommands :: MPD [String]
405 notCommands = liftM takeValues (getResponse "notcommands")
407 -- | Retrieve a list of available song metadata.
408 tagTypes :: MPD [String]
409 tagTypes = liftM takeValues (getResponse "tagtypes")
411 -- | Retrieve a list of supported urlhandlers.
412 urlHandlers :: MPD [String]
413 urlHandlers = liftM takeValues (getResponse "urlhandlers")
415 -- XXX should the password be quoted?
416 -- | Send password to server to authenticate session.
417 -- Password is sent as plain text.
418 password :: String -> MPD ()
419 password = getResponse_ . ("password " ++)
421 -- | Check that the server is still responding.
422 ping :: MPD ()
423 ping = getResponse_ "ping"
425 -- | Get server statistics.
426 stats :: MPD Stats
427 stats = getResponse "stats" >>= runParser parseStats
429 -- | Get the server's status.
430 status :: MPD Status
431 status = getResponse "status" >>= runParser parseStatus
434 -- Extensions\/shortcuts.
437 -- | Like 'update', but returns the update job id.
438 updateId :: [Path] -> MPD Integer
439 updateId paths = liftM (read . head . takeValues) cmd
440 where cmd = case map show paths of
441 [] -> getResponse "update"
442 [x] -> getResponse ("update " ++ x)
443 xs -> getResponses (map ("update " ++) xs)
445 -- | Toggles play\/pause. Plays if stopped.
446 toggle :: MPD ()
447 toggle = status >>= \st -> case stState st of Playing -> pause True
448 _ -> play Nothing
450 -- | Add a list of songs\/folders to a playlist.
451 -- Should be more efficient than running 'add' many times.
452 addMany :: PlaylistName -> [Path] -> MPD ()
453 addMany _ [] = return ()
454 addMany plname [x] = add_ plname x
455 addMany plname xs = getResponses (map ((cmd ++) . show) xs) >> return ()
456 where cmd = case plname of "" -> "add "
457 pl -> "playlistadd " ++ show pl ++ " "
459 -- | Delete a list of songs from a playlist.
460 -- If there is a duplicate then no further songs will be deleted, so
461 -- take care to avoid them (see 'prune' for this).
462 deleteMany :: PlaylistName -> [PLIndex] -> MPD ()
463 deleteMany _ [] = return ()
464 deleteMany plname [x] = delete plname x
465 deleteMany "" xs = getResponses (map cmd xs) >> return ()
466 where cmd (Pos x) = "delete " ++ show x
467 cmd (ID x) = "deleteid " ++ show x
468 deleteMany plname xs = getResponses (map cmd xs) >> return ()
469 where cmd (Pos x) = "playlistdelete " ++ show plname ++ " " ++ show x
470 cmd _ = ""
472 -- | Returns all songs and directories that match the given partial
473 -- path name.
474 complete :: String -> MPD [Either Path Song]
475 complete path = do
476 xs <- liftM matches . lsInfo $ dropFileName path
477 case xs of
478 [Left dir] -> complete $ dir ++ "/"
479 _ -> return xs
480 where
481 matches = filter (isPrefixOf path . takePath)
482 takePath = either id sgFilePath
484 -- | Crop playlist.
485 -- The bounds are inclusive.
486 -- If 'Nothing' or 'ID' is passed the cropping will leave your playlist alone
487 -- on that side.
488 crop :: Maybe PLIndex -> Maybe PLIndex -> MPD ()
489 crop x y = do
490 pl <- playlistInfo Nothing
491 let x' = case x of Just (Pos p) -> fromInteger p
492 Just (ID i) -> fromMaybe 0 (findByID i pl)
493 Nothing -> 0
494 -- ensure that no songs are deleted twice with 'max'.
495 ys = case y of Just (Pos p) -> drop (max (fromInteger p) x') pl
496 Just (ID i) -> maybe [] (flip drop pl . max x' . (+1))
497 (findByID i pl)
498 Nothing -> []
499 deleteMany "" . mapMaybe sgIndex $ take x' pl ++ ys
500 where findByID i = findIndex ((==) i . (\(ID j) -> j) . fromJust . sgIndex)
502 -- | Remove duplicate playlist entries.
503 prune :: MPD ()
504 prune = findDuplicates >>= deleteMany ""
506 -- Find duplicate playlist entries.
507 findDuplicates :: MPD [PLIndex]
508 findDuplicates =
509 liftM (map ((\(ID x) -> ID x) . fromJust . sgIndex) . flip dups ([],[])) $
510 playlistInfo Nothing
511 where dups [] (_, dup) = dup
512 dups (x:xs) (ys, dup)
513 | x `elem` xs && x `notElem` ys = dups xs (ys, x:dup)
514 | otherwise = dups xs (x:ys, dup)
516 -- | List directories non-recursively.
517 lsDirs :: Path -> MPD [Path]
518 lsDirs path =
519 liftM (extractEntries (const Nothing,const Nothing, Just)) $
520 takeEntries =<< getResponse ("lsinfo " ++ show path)
522 -- | List files non-recursively.
523 lsFiles :: Path -> MPD [Path]
524 lsFiles path =
525 liftM (extractEntries (Just . sgFilePath, const Nothing, const Nothing)) $
526 takeEntries =<< getResponse ("lsinfo " ++ show path)
528 -- | List all playlists.
529 lsPlaylists :: MPD [PlaylistName]
530 lsPlaylists =
531 liftM (extractEntries (const Nothing, Just, const Nothing)) $
532 takeEntries =<< getResponse "lsinfo"
534 -- | Search the database for songs relating to an artist.
535 findArtist :: Artist -> MPD [Song]
536 findArtist = find . Query Artist
538 -- | Search the database for songs relating to an album.
539 findAlbum :: Album -> MPD [Song]
540 findAlbum = find . Query Album
542 -- | Search the database for songs relating to a song title.
543 findTitle :: Title -> MPD [Song]
544 findTitle = find . Query Title
546 -- | List the artists in the database.
547 listArtists :: MPD [Artist]
548 listArtists = liftM takeValues (getResponse "list artist")
550 -- | List the albums in the database, optionally matching a given
551 -- artist.
552 listAlbums :: Maybe Artist -> MPD [Album]
553 listAlbums artist = liftM takeValues (getResponse ("list album" ++
554 maybe "" ((" artist " ++) . show) artist))
556 -- | List the songs in an album of some artist.
557 listAlbum :: Artist -> Album -> MPD [Song]
558 listAlbum artist album = find (MultiQuery [Query Artist artist
559 ,Query Album album])
561 -- | Search the database for songs relating to an artist using 'search'.
562 searchArtist :: Artist -> MPD [Song]
563 searchArtist = search . Query Artist
565 -- | Search the database for songs relating to an album using 'search'.
566 searchAlbum :: Album -> MPD [Song]
567 searchAlbum = search . Query Album
569 -- | Search the database for songs relating to a song title.
570 searchTitle :: Title -> MPD [Song]
571 searchTitle = search . Query Title
573 -- | Retrieve the current playlist.
574 -- Equivalent to @playlistinfo Nothing@.
575 getPlaylist :: MPD [Song]
576 getPlaylist = playlistInfo Nothing
579 -- Miscellaneous functions.
582 -- Run getResponse but discard the response.
583 getResponse_ :: String -> MPD ()
584 getResponse_ x = getResponse x >> return ()
586 -- Get the lines of the daemon's response to a list of commands.
587 getResponses :: [String] -> MPD [String]
588 getResponses cmds = getResponse . concat $ intersperse "\n" cmds'
589 where cmds' = "command_list_begin" : cmds ++ ["command_list_end"]
591 -- Helper that throws unexpected error if input is empty.
592 failOnEmpty :: [String] -> MPD [String]
593 failOnEmpty [] = throwError $ Unexpected "Non-empty response expected."
594 failOnEmpty xs = return xs
596 -- A wrapper for getResponse that fails on non-empty responses.
597 getResponse1 :: String -> MPD [String]
598 getResponse1 x = getResponse x >>= failOnEmpty
601 -- Parsing.
604 -- Run 'toAssoc' and return only the values.
605 takeValues :: [String] -> [String]
606 takeValues = snd . unzip . toAssoc
608 data EntryType
609 = SongEntry Song
610 | PLEntry String
611 | DirEntry String
612 deriving Show
614 -- Separate the result of an lsinfo\/listallinfo call into directories,
615 -- playlists, and songs.
616 takeEntries :: [String] -> MPD [EntryType]
617 takeEntries = mapM toEntry . splitGroups wrappers . toAssoc . reverse
618 where
619 toEntry xs@(("file",_):_) = liftM SongEntry $ runParser parseSong xs
620 toEntry (("directory",d):_) = return $ DirEntry d
621 toEntry (("playlist",pl):_) = return $ PLEntry pl
622 toEntry _ = error "takeEntries: splitGroups is broken"
623 wrappers = [("file",id), ("directory",id), ("playlist",id)]
625 -- Extract a subset of songs, directories, and playlists.
626 extractEntries :: (Song -> Maybe a, String -> Maybe a, String -> Maybe a)
627 -> [EntryType] -> [a]
628 extractEntries (fSong,fPlayList,fDir) = catMaybes . map f
629 where
630 f (SongEntry s) = fSong s
631 f (PLEntry pl) = fPlayList pl
632 f (DirEntry d) = fDir d
634 -- Build a list of song instances from a response.
635 takeSongs :: [String] -> MPD [Song]
636 takeSongs = mapM (runParser parseSong) . splitGroups [("file",id)] . toAssoc