Skip to content

Commit

Permalink
Move Default instances to MPD proper
Browse files Browse the repository at this point in the history
Conflicts:
	tests/Network/MPD/Applicative/CurrentPlaylistSpec.hs
  • Loading branch information
joachifm committed Jul 2, 2012
1 parent bc20bff commit e31ac00
Show file tree
Hide file tree
Showing 10 changed files with 67 additions and 48 deletions.
10 changes: 5 additions & 5 deletions Network/MPD/Commands/Parse.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,7 @@ import qualified Data.ByteString.UTF8 as UTF8

-- | Builds a 'Count' instance from an assoc. list.
parseCount :: [ByteString] -> Either String Count
parseCount = foldM f defaultCount . toAssocList
parseCount = foldM f def . toAssocList
where f :: Count -> (ByteString, ByteString) -> Either String Count
f a ("songs", x) = return $ parse parseNum
(\x' -> a { cSongs = x'}) a x
Expand All @@ -35,7 +35,7 @@ parseCount = foldM f defaultCount . toAssocList

-- | Builds a list of 'Device' instances from an assoc. list
parseOutputs :: [ByteString] -> Either String [Device]
parseOutputs = mapM (foldM f defaultDevice)
parseOutputs = mapM (foldM f def)
. splitGroups ["outputid"]
. toAssocList
where f a ("outputid", x) = return $ parse parseNum
Expand All @@ -47,7 +47,7 @@ parseOutputs = mapM (foldM f defaultDevice)

-- | Builds a 'Stats' instance from an assoc. list.
parseStats :: [ByteString] -> Either String Stats
parseStats = foldM f defaultStats . toAssocList
parseStats = foldM f def . toAssocList
where
f a ("artists", x) = return $ parse parseNum
(\x' -> a { stsArtists = x' }) a x
Expand All @@ -72,7 +72,7 @@ parseMaybeSong xs | null xs = Right Nothing
-- | Builds a 'Song' instance from an assoc. list.
parseSong :: [(ByteString, ByteString)] -> Either String Song
parseSong xs = case xs of
("file", path):ys -> foldM f (defaultSong $ Path path) ys
("file", path):ys -> foldM f (def { sgFilePath = Path path}) ys
_ -> Left "Got a song without a file path! This indicates a bug in either libmpd-haskell or MPD itself!"

where
Expand Down Expand Up @@ -114,7 +114,7 @@ parseSong xs = case xs of

-- | Builds a 'Status' instance from an assoc. list.
parseStatus :: [ByteString] -> Either String Status
parseStatus = foldM f defaultStatus . toAssocList
parseStatus = foldM f def . toAssocList
where f a ("state", x)
= return $ parse state (\x' -> a { stState = x' }) a x
f a ("volume", x)
Expand Down
46 changes: 45 additions & 1 deletion Network/MPD/Commands/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,10 +7,38 @@
--
-- Various MPD data structures and types

module Network.MPD.Commands.Types where
module Network.MPD.Commands.Types
( ToString(..)
, Artist
, Album
, Title
, PlaylistName(..)
, Path(..)
, Metadata(..)
, Value(..)
, ObjectType(..)
, Seconds
, Decibels
, State(..)
, Subsystem(..)
, ReplayGainMode(..)
, Count(..)
, LsResult(..)
, Device(..)
, Song(..)
, Position
, Id(..)
, sgGetTag
, sgAddTag
, Stats(..)
, Status(..)
, def
) where

import Network.MPD.Commands.Arg (MPDArg(prep), Args(Args))

import Data.Default

import qualified Data.Map as M
import Data.Time.Clock (UTCTime)
import Data.String
Expand Down Expand Up @@ -160,6 +188,9 @@ data Count =
defaultCount :: Count
defaultCount = Count { cSongs = 0, cPlaytime = 0 }

instance Default Count where
def = defaultCount

-- | Result of the lsInfo operation
data LsResult
= LsDirectory Path -- ^ Directory
Expand All @@ -179,6 +210,9 @@ defaultDevice :: Device
defaultDevice =
Device { dOutputID = 0, dOutputName = "", dOutputEnabled = False }

instance Default Device where
def = defaultDevice

-- | Represents a single song item.
data Song = Song
{ sgFilePath :: Path
Expand Down Expand Up @@ -216,6 +250,10 @@ defaultSong path =
Song { sgFilePath = path, sgTags = M.empty, sgLastModified = Nothing
, sgLength = 0, sgId = Nothing, sgIndex = Nothing }

-- XXX: warning; sgFilePath must be set before using this
instance Default Song where
def = defaultSong undefined

-- | Container for database statistics.
data Stats =
Stats { stsArtists :: Integer -- ^ Number of artists.
Expand All @@ -234,6 +272,9 @@ defaultStats =
Stats { stsArtists = 0, stsAlbums = 0, stsSongs = 0, stsUptime = 0
, stsPlaytime = 0, stsDbPlaytime = 0, stsDbUpdate = 0 }

instance Default Stats where
def = defaultStats

-- | Container for MPD status.
data Status =
Status { stState :: State
Expand Down Expand Up @@ -286,3 +327,6 @@ defaultStatus =
, stBitrate = 0, stXFadeWidth = 0, stMixRampdB = 0
, stMixRampDelay = 0, stAudio = (0,0,0), stUpdatingDb = Nothing
, stSingle = False, stConsume = False, stError = Nothing }

instance Default Status where
def = defaultStatus
2 changes: 1 addition & 1 deletion libmpd.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,6 @@ Extra-Source-Files:
NEWS
tests/Arbitrary.hs
tests/CommandSpec.hs
tests/Defaults.hs
tests/EnvSpec.hs
tests/ParserSpec.hs
tests/StringConn.hs
Expand All @@ -48,6 +47,7 @@ Library
, old-locale >= 1.0 && < 2.0
, time >= 1.1 && < 2.0
, containers >= 0.3 && < 0.5
, data-default >= 0.4.0 && < 0.5
, bytestring >= 0.9 && < 1
, text >= 0.11 && < 0.12
, attoparsec >= 0.10.1 && < 0.11
Expand Down
4 changes: 1 addition & 3 deletions tests/CommandSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,6 @@
module CommandSpec (main, spec) where

import Arbitrary ()
import Defaults ()
import StringConn
import TestUtil
import Unparse
Expand All @@ -25,7 +24,6 @@ import Network.MPD.Commands
import Network.MPD.Commands.Extensions

import Prelude hiding (repeat)
import Data.Default (Default(def))

main :: IO ()
main = hspec spec
Expand Down Expand Up @@ -222,7 +220,7 @@ testListAll =

-- XXX: generalize to arbitrary input
testLsInfo = do
let song = defaultSong "Bar.ogg"
let song = def { sgFilePath = "Bar.ogg" }
cmd [("lsinfo \"\"", Right $ "directory: Foo\n" ++ unparse song ++ "playlist: Quux\nOK")]
(Right [LsDirectory "Foo", LsSong song, LsPlaylist "Quux"])
(lsInfo "")
Expand Down
21 changes: 0 additions & 21 deletions tests/Defaults.hs

This file was deleted.

16 changes: 8 additions & 8 deletions tests/Network/MPD/Applicative/CurrentPlaylistSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -76,7 +76,7 @@ spec = do
-- XXX: generalize to arbitrary SongS and Query
describe "playlistFind" $ do
it "searches for songs in the current playlist" $ do
let obj = defaultSong "Foo.ogg"
let obj = def { sgFilePath = "Foo.ogg" }
resp = unparse obj
playlistFind (Artist =? "Foo")
`with` [("playlistfind Artist \"Foo\"", Right $ resp ++ "\nOK")]
Expand All @@ -85,22 +85,22 @@ spec = do
-- XXX: generalize to arbitrary SongS
describe "playlistInfo" $ do
it "retrieves metadata for all songs in the current playlist" $ do
let obj = defaultSong "Foo.ogg"
let obj = def { sgFilePath = "Foo.ogg" }
resp = unparse obj
playlistInfo Nothing
`with` [("playlistinfo", Right $ resp ++ "\nOK")]
`shouldBe` Right [obj]

it "can optionally return only metadata for a position" $ do
let obj = defaultSong "Foo.ogg"
let obj = def { sgFilePath = "Foo.ogg" }
resp = unparse obj ++ "OK"
playlistInfo (Just 1)
`with` [("playlistinfo 1", Right resp)]
`shouldBe` Right [obj]

describe "playlistInfoRange" $ do
it "is like playlistInfo but can restrict to a range of songs" $ do
let obj = defaultSong "Foo.ogg"
let obj = def { sgFilePath = "Foo.ogg" }
resp = unparse obj ++ "OK"
playlistInfoRange (Just (0, 1))
`with` [("playlistinfo 0:1", Right resp)]
Expand All @@ -109,30 +109,30 @@ spec = do
-- XXX: generlize to arbitrary SongS
describe "playlistId" $ do
it "retrieves metadata for all songs in the current playlist" $ do
let obj = defaultSong "Foo.ogg"
let obj = def { sgFilePath = "Foo.ogg" }
resp = unparse obj
playlistId Nothing
`with` [("playlistid", Right $ resp ++ "\nOK")]
`shouldBe` Right [obj]

it "can optionally return info only for a position" $ do
let obj = defaultSong "Foo.ogg"
let obj = def { sgFilePath = "Foo.ogg" }
resp = unparse obj
playlistId (Just $ Id 0)
`with` [("playlistid 0", Right $ resp ++ "\nOK")]
`shouldBe` Right [obj]

describe "playlistSearch" $ do
it "returns songs matching an inexact query" $ do
let obj = defaultSong "Foo.ogg"
let obj = def { sgFilePath = "Foo.ogg" }
resp = unparse obj
playlistSearch (Title =? "Foo")
`with` [("playlistsearch Title \"Foo\"", Right $ resp ++ "\nOK")]
`shouldBe` Right [obj]

describe "plChanges" $ do
it "returns songs that have changed since the given playlist version" $ do
let obj = defaultSong "foo.ogg"
let obj = def { sgFilePath = "foo.ogg" }
plChanges 1
`with` [("plchanges 1"
, Right (unparse obj ++ "OK"))
Expand Down
10 changes: 5 additions & 5 deletions tests/Network/MPD/Applicative/DatabaseSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@ spec = do

describe "find" $ do
it "returns songs exactly matching a query" $ do
let obj = defaultSong "Bar.ogg"
let obj = def { sgFilePath = "Bar.ogg" }
resp = unparse obj ++ "OK"
find (Title =? "Foo")
`with` [("find Title \"Foo\"", Right resp)]
Expand Down Expand Up @@ -67,7 +67,7 @@ spec = do

describe "lsInfo" $ do
it "returns a non-recursive listing of a database directory" $ do
let song = defaultSong "Bar.ogg"
let song = def { sgFilePath = "Bar.ogg" }
resp = "directory: Foo\n" ++ unparse song
++ "\nplaylist: Quux\nOK"
lsInfo ""
Expand All @@ -87,11 +87,11 @@ spec = do

describe "search" $ do
it "returns songs matching a case-insensitive query" $ do
let obj = [defaultSong "Bar.ogg"]
resp = unlines (map unparse obj) ++ "\nOK"
let obj = def { sgFilePath = "Bar.ogg" }
resp = unparse obj ++ "OK"
search (Title =? "Foo")
`with` [("search Title \"Foo\"", Right resp)]
`shouldBe` Right obj
`shouldBe` Right [obj]

describe "update" $ do
it "updates the entire collection by default" $ do
Expand Down
1 change: 0 additions & 1 deletion tests/Network/MPD/Applicative/StatusSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,6 @@

module Network.MPD.Applicative.StatusSpec (main, spec) where

import Defaults ()
import TestUtil
import Unparse

Expand Down
4 changes: 2 additions & 2 deletions tests/Network/MPD/Applicative/StoredPlaylistsSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -24,10 +24,10 @@ spec = do

describe "listPlaylistInfo" $ do
it "returns metadata for songs in a playlist" $ do
let obj = defaultSong "foo.ogg"
let obj = def { sgFilePath = "foo.ogg" }
listPlaylistInfo "foo"
`with` [("listplaylistinfo \"foo\""
, Right (unparse obj ++ "\nOK")
, Right (unparse obj ++ "OK")
)]
`shouldBe` Right [obj]

Expand Down
1 change: 0 additions & 1 deletion tests/ParserSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,6 @@
module ParserSpec (main, spec) where

import Arbitrary ()
import Defaults ()
import Unparse

import Test.Hspec.Monadic
Expand Down

0 comments on commit e31ac00

Please sign in to comment.