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