-- PowerMate+MPD utility. -- Copyright (C) 2006 Evan Martin module Main where import qualified PowerMate import qualified MPD import System.IO debug :: Bool debug = False ifDebug :: IO () -> IO () ifDebug _ | debug = return () ifDebug _ | otherwise = return () mpdAddress :: (String, Int) mpdAddress = ("localhost", 6600) data State = State { stConn :: MPD.ReconnectableConnection, stPowerMate :: Handle, stVolume :: Int } processEvent :: State -> PowerMate.Event -> IO State processEvent state (PowerMate.Button True) = do MPD.rcDo (stConn state) $ \conn -> MPD.runCommand_ conn "pause" return state processEvent state (PowerMate.Button False) = return state processEvent state (PowerMate.Rotate dir) = do let newvol = max 0 $ min 100 $ (stVolume state) + dir ifDebug $ do putStr (if dir > 0 then "+" else "-") hFlush stdout putStrLn $ show newvol MPD.rcDo (stConn state) $ \conn -> MPD.setVolume conn newvol updateBrightness state return $ state { stVolume=newvol } processEvent state (PowerMate.StatusChange status) = do ifDebug $ do putStrLn "New status:" putStrLn $ " Brightness: " ++ show (PowerMate.brightness status) putStrLn $ " Pulse Speed: " ++ show (PowerMate.pulse_speed status) putStrLn $ " Pulse Mode: " ++ show (PowerMate.pulse_mode status) putStrLn $ " Pulse Asleep: " ++ show (PowerMate.pulse_asleep status) putStrLn $ " Pulse Awake: " ++ show (PowerMate.pulse_awake status) return state readMPDStatus :: State -> IO State readMPDStatus state = do volume <- MPD.rcDo (stConn state) $ MPD.getVolume return $ state { stVolume=volume } updateBrightness :: State -> IO () updateBrightness state = do let brightness = (stVolume state)*255 `div` 100 PowerMate.writeStatus (stPowerMate state) $ PowerMate.statusInit { PowerMate.brightness=brightness } loop :: a -> (a -> IO a) -> IO () loop state func = do newstate <- func state loop newstate func return () -- never reached mainLoop :: FilePath -> IO () mainLoop devname = do pm <- PowerMate.openDevice devname --PowerMate.writeStatus pm $ PowerMate.statusInit { PowerMate.brightness=100, PowerMate.pulse_asleep = True } conn <- MPD.rcConnect mpdAddress state <- readMPDStatus $ State { stConn=conn, stPowerMate=pm, stVolume=0 } updateBrightness state loop state $ \stat -> do event <- PowerMate.readEventWithSkip pm Nothing case event of Nothing -> return stat Just ev -> processEvent stat ev main :: IO () main = do powermate_device <- PowerMate.searchForDevice case powermate_device of Nothing -> return () Just pmd -> do mainLoop pmd -- vim: set ts=2 sw=2 et ft=haskell :