{- * Programmer: Piotr Borek * E-mail: piotrborek@op.pl * Copyright 2014 Piotr Borek * * Distributed under the terms of the GPL (GNU Public License) * * This program is free software; you can redistribute it and/or modify * it under the terms of the GNU General Public License as published by * the Free Software Foundation; either version 2 of the License, or * (at your option) any later version. * * This program is distributed in the hope that it will be useful, * but WITHOUT ANY WARRANTY; without even the implied warranty of * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * GNU General Public License for more details. * * You should have received a copy of the GNU General Public License * along with this program; if not, write to the Free Software * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -} module Mp.Player.ServerState where import qualified Control.Monad.State as State import Control.Monad.Catch import Data.Binary import System.Random import Mp.Utils.Shuffle import Mp.Player.PlaySong data PlayingIndex = PlayingIndex Int data ServerState = ServerState { getPlaylist :: ![String], getCurrentPosition :: !Integer, getCurrentDuration :: !Integer, getStatus :: !String, getPlaying :: !Int, getVolume :: !Double, isRepeatMode :: !Bool, isShuffleMode :: !Bool, randomInitializer :: !Int, shuffleFunc :: Int -> Int, shuffleData :: !ShuffleData, errorCounter :: !Int, lastOperation :: !PlaySong } instance Binary PlayingIndex where put (PlayingIndex i) = do put (20150221 :: Word32) put (0 :: Int) put i get = do magic <- get :: Get Word32 if magic /= 20150221 then return defaultPlayingIndex else do version <- get :: Get Int case version of 0 -> getVersion0 _ -> return defaultPlayingIndex where getVersion0 = do index <- get return $ PlayingIndex index defaultPlayingIndex = PlayingIndex 0 instance Binary ServerState where put st = do put (1113 :: Word32) put (1 :: Int) if getStatus st == "Paused" then put "Playing" else put $ getStatus st put $ getVolume st put $ getPlaylist st put $ isRepeatMode st put $ isShuffleMode st put $ randomInitializer st get = do magic <- get :: Get Word32 if magic /= 1113 then return defaultServerState else do version <- get :: Get Int case version of 0 -> getVersion0 1 -> getVersion1 _ -> return defaultServerState where generateShuffle shuffleMode r playlist = let g = mkStdGen r in if shuffleMode then State.runState (shuffleFilled $ length playlist) $ shuffleInitial g else (id, shuffleInitial g) getVersion0 = do playing <- get status <- get volume <- get playlist <- get repeatMode <- get shuffleMode <- get r <- get let (f, d) = generateShuffle shuffleMode r playlist return ServerState { getPlaylist = playlist, getCurrentPosition = 0, getCurrentDuration = 0, getStatus = status, getPlaying = playing, getVolume = volume, isRepeatMode = repeatMode, isShuffleMode = shuffleMode, randomInitializer = r, shuffleFunc = f, shuffleData = d, errorCounter = 0, lastOperation = PlaySongNext } getVersion1 = do status <- get volume <- get playlist <- get repeatMode <- get shuffleMode <- get r <- get let (f, d) = generateShuffle shuffleMode r playlist return ServerState { getPlaylist = playlist, getCurrentPosition = 0, getCurrentDuration = 0, getStatus = status, getPlaying = 0, getVolume = volume, isRepeatMode = repeatMode, isShuffleMode = shuffleMode, randomInitializer = r, shuffleFunc = f, shuffleData = d, errorCounter = 0, lastOperation = PlaySongNext } defaultServerState :: ServerState defaultServerState = ServerState { getPlaylist = [], getCurrentPosition = 0, getCurrentDuration = 0, getStatus = "Stopped", getPlaying = -1, getVolume = 1.0, isRepeatMode = False, isShuffleMode = False, randomInitializer = 0, shuffleFunc = id, shuffleData = shuffleInitial $ mkStdGen 0, errorCounter = 0, lastOperation = PlaySongNext } readStateFromFile :: String -> IO ServerState readStateFromFile file = decodeFile file `catchAll` (\_ -> return defaultServerState) readIndexFromFile :: String -> IO PlayingIndex readIndexFromFile file = decodeFile file `catchAll` (\_ -> return $ PlayingIndex 0)