cdb4bed024dee8b4b2c70c58b1551b44cab7a608
[powermate.git] / powermate.hs
1 module Main where
2
3 import PowerMate
4 import System.IO
5 import System.Process
6 import Control.Monad
7 import Text.Regex.Posix
8
9 data State = State {
10   stPowerMate  :: Handle,
11   stVolume     :: Int,
12   stDir        :: Int
13 }
14
15 processEvent :: State -> Event -> IO State
16 processEvent state (Button True) = do
17   createProcess (proc "music-toggle" [])
18   return state
19 processEvent state (Button False) = do
20   return state
21
22 processEvent state (Rotate dir) = do
23   state <- (if dir < 2 then volumeUp else volumeDown) state
24   updateBrightness state
25   return state
26
27 processEvent state (StatusChange status) = do
28   return state
29
30 readState :: State -> IO State
31 readState state = do
32   return state
33
34 next :: a -> (a -> IO a) -> IO ()
35 next state func = do
36   newstate <- func state
37   next newstate func
38   return ()
39
40 updateBrightness :: State -> IO ()
41 updateBrightness state = do
42   let brightness = (stVolume state)
43   writeStatus (stPowerMate state) $
44     statusInit { brightness=brightness }
45
46 volumeUp  :: State -> IO State
47 volumeUp state = do
48   createProcess (proc "volume-up" [])
49   state <- readState $ State {
50     stPowerMate=(stPowerMate state),
51     stVolume=(max 0 $ 1+(stVolume state)),
52     stDir=(stDir state) }
53   return state
54
55 volumeDown  :: State -> IO State
56 volumeDown state = do
57   createProcess (proc "volume-down" [])
58   state <- readState $ State {
59     stPowerMate=(stPowerMate state),
60     stVolume=(max 0 $ (stVolume state)-1),
61     stDir=(stDir state) }
62   return state
63
64 loop :: FilePath -> IO ()
65 loop devname = do
66   powermate <- openDevice devname
67
68   alsaMixers <- readProcess "amixer" ["get", "Master"] []
69   let alsaMaster = (alsaMixers =~ "\\[([0-9]{1,2})%\\]" :: String)
70   let volume = read (drop 1
71                       (take
72                         (subtract 2
73                           (length alsaMaster)) alsaMaster)) :: Int
74   state <- readState $ State {
75     stPowerMate=powermate,
76     stVolume=volume,
77     stDir=1 }
78   updateBrightness state
79
80   next state $ \call -> do
81     event <- readEventWithSkip powermate Nothing
82     case event of
83       Nothing -> return call
84       Just event -> processEvent call event
85
86 main :: IO ()
87 main = do
88   powermate <- searchForDevice
89   case powermate of
90     Nothing  -> return ()
91     Just work -> do
92       loop work