Brightness now changing with volume
authorDylan Lloyd <dylan@dylansserver.com>
Mon, 27 Feb 2012 03:35:31 +0000 (22:35 -0500)
committerDylan Lloyd <dylan@dylansserver.com>
Mon, 27 Feb 2012 03:35:31 +0000 (22:35 -0500)
powermate.hs

index 16a783f..cdb4bed 100755 (executable)
@@ -3,21 +3,25 @@ module Main where
 import PowerMate
 import System.IO
 import System.Process
+import Control.Monad
+import Text.Regex.Posix
 
 data State = State {
   stPowerMate  :: Handle,
-  stVolume     :: Int
+  stVolume     :: Int,
+  stDir        :: Int
 }
 
 processEvent :: State -> Event -> IO State
 processEvent state (Button True) = do
   createProcess (proc "music-toggle" [])
   return state
-processEvent state (Button False) = return state
+processEvent state (Button False) = do
+  return state
 
 processEvent state (Rotate dir) = do
-  if dir < 2 then createProcess (proc "volume-up" [])
-  else createProcess (proc "volume-down" [])
+  state <- (if dir < 2 then volumeUp else volumeDown) state
+  updateBrightness state
   return state
 
 processEvent state (StatusChange status) = do
@@ -33,12 +37,45 @@ next state func = do
   next newstate func
   return ()
 
+updateBrightness :: State -> IO ()
+updateBrightness state = do
+  let brightness = (stVolume state)
+  writeStatus (stPowerMate state) $
+    statusInit { brightness=brightness }
+
+volumeUp  :: State -> IO State
+volumeUp state = do
+  createProcess (proc "volume-up" [])
+  state <- readState $ State {
+    stPowerMate=(stPowerMate state),
+    stVolume=(max 0 $ 1+(stVolume state)),
+    stDir=(stDir state) }
+  return state
+
+volumeDown  :: State -> IO State
+volumeDown state = do
+  createProcess (proc "volume-down" [])
+  state <- readState $ State {
+    stPowerMate=(stPowerMate state),
+    stVolume=(max 0 $ (stVolume state)-1),
+    stDir=(stDir state) }
+  return state
 
 loop :: FilePath -> IO ()
 loop devname = do
   powermate <- openDevice devname
 
-  state <- readState $ State { stPowerMate=powermate, stVolume=0 }
+  alsaMixers <- readProcess "amixer" ["get", "Master"] []
+  let alsaMaster = (alsaMixers =~ "\\[([0-9]{1,2})%\\]" :: String)
+  let volume = read (drop 1
+                      (take
+                        (subtract 2
+                          (length alsaMaster)) alsaMaster)) :: Int
+  state <- readState $ State {
+    stPowerMate=powermate,
+    stVolume=volume,
+    stDir=1 }
+  updateBrightness state
 
   next state $ \call -> do
     event <- readEventWithSkip powermate Nothing