halved sensitivity
[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   stPrevDir     :: Int,
13   stPrevAction  :: Int
14 }
15
16 processEvent :: State -> Event -> IO State
17 processEvent state (Button True) = do
18   createProcess (proc "music-toggle" [])
19   return state
20 processEvent state (Button False) = do
21   return state
22
23 processEvent state (Rotate dir) = do
24   state <- (if dir < 2
25               && (stPrevDir state) == 1
26               && (stPrevAction state) == 1
27                 then volumeUp
28               else return) state
29   state <- (if dir > 2
30               && (stPrevDir state) == 0
31               && (stPrevAction state) == 0
32                 then volumeDown
33               else return) state
34   state <- updatePrevState state (if dir < 2 then 1 else 0)
35   updateBrightness state
36   state <- updatePrevAction state (if (stPrevAction state) == 1 then 0 else 1)
37   return state
38
39 processEvent state (StatusChange status) = do
40   return state
41
42 readState :: State -> IO State
43 readState state = do
44   return state
45
46 next :: a -> (a -> IO a) -> IO ()
47 next state func = do
48   newstate <- func state
49   next newstate func
50   return ()
51
52 updateBrightness :: State -> IO ()
53 updateBrightness state = do
54   let brightness = (stVolume state)
55   writeStatus (stPowerMate state) $
56     statusInit { brightness=brightness }
57
58 volumeUp :: State -> IO State
59 volumeUp state = do
60   createProcess (proc "volume-up" [])
61   state <- readState $ State {
62     stPowerMate=(stPowerMate state),
63     stVolume=(max 0 $ 1+(stVolume state)),
64     stPrevAction=(stPrevAction state),
65     stPrevDir=(stPrevDir state) }
66   state <- updatePrevAction state 1
67   return state
68
69 volumeDown :: State -> IO State
70 volumeDown state = do
71   createProcess (proc "volume-down" [])
72   state <- readState $ State {
73     stPowerMate=(stPowerMate state),
74     stVolume=(max 0 $ (stVolume state)-1),
75     stPrevAction=(stPrevAction state),
76     stPrevDir=(stPrevDir state) }
77   state <- updatePrevAction state 0
78   return state
79
80 updatePrevState :: State -> Int -> IO State
81 updatePrevState state dir = do
82   state <- readState $ State {
83     stPowerMate=(stPowerMate state),
84     stVolume=(stVolume state),
85     stPrevAction=(stPrevAction state),
86     stPrevDir=dir }
87   return state
88
89 updatePrevAction :: State -> Int -> IO State
90 updatePrevAction state action = do
91   state <- readState $ State {
92     stPowerMate=(stPowerMate state),
93     stVolume=(stVolume state),
94     stPrevAction=action,
95     stPrevDir=(stPrevDir state) }
96   return state
97
98 loop :: FilePath -> IO ()
99 loop devname = do
100   powermate <- openDevice devname
101
102   alsaMixers <- readProcess "amixer" ["get", "Master"] []
103   let alsaMaster = (alsaMixers =~ "\\[([0-9]{1,2})%\\]" :: String)
104   let volume = read (drop 1
105                       (take
106                         (subtract 2
107                           (length alsaMaster)) alsaMaster)) :: Int
108   state <- readState $ State {
109     stPowerMate=powermate,
110     stVolume=volume,
111     stPrevAction=0,
112     stPrevDir=0 }
113   updateBrightness state
114
115   next state $ \call -> do
116     event <- readEventWithSkip powermate Nothing
117     case event of
118       Nothing -> return call
119       Just event -> processEvent call event
120
121 main :: IO ()
122 main = do
123   powermate <- searchForDevice
124   case powermate of
125     Nothing  -> return ()
126     Just work -> do
127       loop work