{-# LANGUAGE FlexibleInstances, TypeSynonymInstances, GeneralizedNewtypeDeriving #-}
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
, defaultSong
) where
import Network.MPD.Commands.Arg (MPDArg(prep), Args(Args))
import Data.Default.Class
import qualified Data.Map as M
import Data.Map.Strict (insertWith)
import Data.Time.Clock (UTCTime)
import Data.String
import Data.Text (Text)
import qualified Data.Text.Encoding as Text
import Data.ByteString (ByteString)
import qualified Data.ByteString.UTF8 as UTF8
class ToString a where
toString :: a -> String
toText :: a -> Text
toUtf8 :: a -> ByteString
type Artist = Value
type Album = Value
type Title = Value
newtype PlaylistName = PlaylistName ByteString
deriving (Eq, Show, MPDArg)
instance ToString PlaylistName where
toString (PlaylistName x) = UTF8.toString x
toText (PlaylistName x) = Text.decodeUtf8 x
toUtf8 (PlaylistName x) = x
instance IsString PlaylistName where
fromString = PlaylistName . UTF8.fromString
newtype Path = Path ByteString
deriving (Eq, Show, MPDArg)
instance ToString Path where
toString (Path x) = UTF8.toString x
toText (Path x) = Text.decodeUtf8 x
toUtf8 (Path x) = x
instance IsString Path where
fromString = Path . UTF8.fromString
data Metadata = Artist
| ArtistSort
| Album
| AlbumArtist
| AlbumArtistSort
| Title
| Track
| Name
| Genre
| Date
| Composer
| Performer
| Comment
| Disc
| MUSICBRAINZ_ARTISTID
| MUSICBRAINZ_ALBUMID
| MUSICBRAINZ_ALBUMARTISTID
| MUSICBRAINZ_TRACKID
| MUSICBRAINZ_RELEASETRACKID
deriving (Eq, Enum, Ord, Bounded, Show)
instance MPDArg Metadata
newtype Value = Value ByteString
deriving (Eq, Show, MPDArg)
instance ToString Value where
toString (Value x) = UTF8.toString x
toText (Value x) = Text.decodeUtf8 x
toUtf8 (Value x) = x
instance IsString Value where
fromString = Value . UTF8.fromString
data ObjectType = SongObj
deriving (Eq, Show)
instance MPDArg ObjectType where
prep SongObj = Args ["song"]
type Seconds = Integer
type Decibels = Integer
data State = Playing
| Stopped
| Paused
deriving (Show, Eq)
data Subsystem
= DatabaseS
| UpdateS
| StoredPlaylistS
| PlaylistS
| PlayerS
| MixerS
| OutputS
| OptionsS
| StickerS
| SubscriptionS
| MessageS
deriving (Eq, Show)
instance MPDArg Subsystem where
prep DatabaseS = Args ["database"]
prep UpdateS = Args ["update"]
prep StoredPlaylistS = Args ["stored_playlist"]
prep PlaylistS = Args ["playlist"]
prep PlayerS = Args ["player"]
prep MixerS = Args ["mixer"]
prep OutputS = Args ["output"]
prep OptionsS = Args ["options"]
prep StickerS = Args ["sticker"]
prep SubscriptionS = Args ["subscription"]
prep MessageS = Args ["message"]
data ReplayGainMode
= Off
| TrackMode
| AlbumMode
deriving (Eq, Show)
instance MPDArg ReplayGainMode where
prep Off = Args ["off"]
prep TrackMode = Args ["track"]
prep AlbumMode = Args ["album"]
data Count =
Count { cSongs :: Integer
, cPlaytime :: Seconds
}
deriving (Eq, Show)
defaultCount :: Count
defaultCount = Count { cSongs = 0, cPlaytime = 0 }
instance Default Count where
def = defaultCount
data LsResult
= LsDirectory Path
| LsSong Song
| LsPlaylist PlaylistName
deriving (Eq, Show)
data Device =
Device { dOutputID :: Int
, dOutputName :: String
, dOutputEnabled :: Bool }
deriving (Eq, Show)
defaultDevice :: Device
defaultDevice =
Device { dOutputID = 0, dOutputName = "", dOutputEnabled = False }
instance Default Device where
def = defaultDevice
data Song = Song
{ sgFilePath :: Path
, sgTags :: M.Map Metadata [Value]
, sgLastModified :: Maybe UTCTime
, sgLength :: Seconds
, sgId :: Maybe Id
, sgIndex :: Maybe Position
} deriving (Eq, Show)
type Position = Int
newtype Id = Id Int
deriving (Eq, Show)
instance (MPDArg Id) where
prep (Id x) = prep x
sgGetTag :: Metadata -> Song -> Maybe [Value]
sgGetTag meta s = M.lookup meta $ sgTags s
sgAddTag :: Metadata -> Value -> Song -> Song
sgAddTag meta value s = s { sgTags = insertWith (++) meta [value] (sgTags s) }
defaultSong :: Path -> Song
defaultSong path =
Song { sgFilePath = path, sgTags = M.empty, sgLastModified = Nothing
, sgLength = 0, sgId = Nothing, sgIndex = Nothing }
data Stats =
Stats { stsArtists :: Integer
, stsAlbums :: Integer
, stsSongs :: Integer
, stsUptime :: Seconds
, stsPlaytime :: Seconds
, stsDbPlaytime :: Seconds
, stsDbUpdate :: Integer
}
deriving (Eq, Show)
defaultStats :: Stats
defaultStats =
Stats { stsArtists = 0, stsAlbums = 0, stsSongs = 0, stsUptime = 0
, stsPlaytime = 0, stsDbPlaytime = 0, stsDbUpdate = 0 }
instance Default Stats where
def = defaultStats
data Status =
Status { stState :: State
, stVolume :: Maybe Int
, stRepeat :: Bool
, stRandom :: Bool
, stPlaylistVersion :: Integer
, stPlaylistLength :: Integer
, stSongPos :: Maybe Position
, stSongID :: Maybe Id
, stNextSongPos :: Maybe Position
, stNextSongID :: Maybe Id
, stTime :: Maybe (Double, Seconds)
, stBitrate :: Maybe Int
, stXFadeWidth :: Seconds
, stMixRampdB :: Double
, stMixRampDelay :: Double
, stAudio :: (Int, Int, Int)
, stUpdatingDb :: Maybe Integer
, stSingle :: Bool
, stConsume :: Bool
, stError :: Maybe String }
deriving (Eq, Show)
defaultStatus :: Status
defaultStatus =
Status { stState = Stopped, stVolume = Just 0, stRepeat = False
, stRandom = False, stPlaylistVersion = 0, stPlaylistLength = 0
, stSongPos = Nothing, stSongID = Nothing, stTime = Nothing
, stNextSongPos = Nothing, stNextSongID = Nothing
, stBitrate = Nothing, stXFadeWidth = 0, stMixRampdB = 0
, stMixRampDelay = 0, stAudio = (0,0,0), stUpdatingDb = Nothing
, stSingle = False, stConsume = False, stError = Nothing }
instance Default Status where
def = defaultStatus