{- Defines a number of types used throughout the application. - Also overides the 'get' and 'set' functions from the - Control.Monad.State package to allow transparent access - to the state MVar -} module Hmpf.ApplicationTypes where import Control.Concurrent (ThreadId,myThreadId) import Control.Concurrent.MVar import qualified Control.Monad.State as S import System.Posix.Types (EpochTime) import System.IO (Handle,stdin) import Network.URI ( URI ) import Network.Socket ( PortNumber ) data AppState = State { lcdSocket :: Handle ,scheduler :: MVar MonitorState ,musicMonitor :: ThreadId ,scrobble :: Maybe Scrobble ,generate :: Bool ,cache :: MVar ([String],[String],[String]) ,mpdConf :: MVar (String,PortNumber) ,lcdConf :: (String,PortNumber) ,lastfmUser :: Maybe (String, String) ,lircConf :: FilePath ,timer :: Int } type Session a = S.StateT (MVar AppState) IO a type Action = ( EpochTime , ( String , Session ()) ) data MonitorState = MonitorState { pending :: [Action] , thread :: ThreadId } -- uri , token , interval type Scrobble = ( URI , String , Int ) mpdConfDefault = ("10.1.1.4", toEnum 6600 :: PortNumber ) lcdConfDefault = ("10.1.1.4", toEnum 13666 :: PortNumber ) empty :: IO (MVar AppState) empty = do threadid <- myThreadId m <- newMVar (MonitorState [] threadid) cch <- newMVar ([],[],[]) mpdC <- newMVar mpdConfDefault newMVar (State stdin m threadid Nothing False cch mpdC lcdConfDefault Nothing "/dev/lircd" 0 ) lower :: Session a -> Session ( IO a ) lower fn = do mvar <- S.get return ( ( S.runStateT fn mvar) >>= (return . fst) ) get :: Session AppState get = do mvar <- S.get S.lift $ readMVar mvar put :: AppState -> Session () put st = do mvar <- S.get S.lift $ swapMVar mvar st return () lift :: IO a -> Session a lift = S.lift data Switch = Off | On deriving ( Show , Eq , Enum )