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