summaryrefslogtreecommitdiffhomepage
path: root/src/lib/Monitors.hs
blob: d5ddd6bafdf9910d59f822d09e3f297133eb7064 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
module Monitors where

import Xmobar
import Config
import Control.Concurrent
import Control.Concurrent.Async (async)
import Control.Concurrent.STM

data CombinedMonitor a b = CombinedMonitor a b (String -> String -> String)

instance (Show a, Show b) => Show (CombinedMonitor a b) where
  show (CombinedMonitor a b _) = "Alt (" ++ show a ++ ") (" ++ show b ++ ")"

instance (Read a, Read b) => Read (CombinedMonitor a b) where
  readsPrec _ = undefined

instance (Exec a, Exec b) => Exec (CombinedMonitor a b) where
  alias (CombinedMonitor a b _) = (alias a) ++ "_" ++ (alias b)
  rate (CombinedMonitor a b _) = min (rate a) (rate b)
  start (CombinedMonitor a b comb) cb
    = startMonitors a b (\s t -> cb $ comb s t)

startMonitors a b cmb =  do
    sta <- atomically $ newTVar ""
    stb <- atomically $ newTVar ""
    _ <- async $ start a (\x -> atomically $ writeTVar sta x)
    _ <- async $ start b (\x -> atomically $ writeTVar stb x)
    go sta stb cmb
      where go sta' stb' cmb' = do
              s <- atomically $ readTVar sta'
              t <- atomically $ readTVar stb'
              cmb' s t
              tenthSeconds $ min (rate b) (rate a)
              go sta' stb' cmb'

altMonitor a b = CombinedMonitor a b (\s t -> if null s then t else s)
concatMonitor sep a b = CombinedMonitor a b (\s t -> s ++ sep ++ t)

topProc p = TopProc (p <~> ["-t" , "<mboth3>  <mboth2>  <mboth1> \
                                   \· <both3>  <both2>  <both1>"
                           , "-w", "10", "-L" , "10", "-H", "80"]) 15

wireless p = Wireless "wlp2s0" (p <~> ["-t" , "<essid> <quality>"
                                      , "-W", "5", "-M", "15" , "-m", "3"
                                      , "-L", "20", "-H", "80"]) 20

multiCPU p = MultiCpu (p <~> ["-t", "<autototal>"
                             , "-S", "on", "-b", " ", "-f", "*"
                             , "-c", " " , "-L", "30", "-H", "70"
                             , "-p", "3", "-a", "l"]) 10

cpuFreq p = CpuFreq (p <~> ["-t" , "<cpu0> <cpu1> <cpu2> <cpu3>"
                           , "-L", "1", "-H", "2", "-S", "Off" , "-d", "2"]) 50

-- ⤒⤊⍐ ⊼ ⇧  ⇩ ⎗ ⎘
dynNetwork p = DynNetwork (p <~> ["-t", "<fn=2>↑</fn> <tx>  <fn=2>↓</fn> <rx>"
                                 , "-L", "20", "-H", "1024000"
                                 , "-m", "5", "-W", "10", "-S", "Off"]) 10

uptime p = Uptime (p <~> [ "-t" , "<days> <hours>", "-m", "3", "-c", "0", "-S"
                         , "On" , "-L", "10", "-H", "100"]) 600

weather st =
  Weather st ["-t", "<tempC>° <rh>%  <windKmh> <skyCondition> (<hour>)"
             , "-L","10", "-H", "25", "--normal", "black",
               "--high", "lightgoldenrod4", "--low", "darkseagreen4"] 18000

batt p =
  BatteryN ["BAT0"]
           ((p <~> ["-t", "<left>%<acstatus>"
                   , "-S", "Off", "-d", "0", "-m", "3"
                   , "-L", "10", "-H", "80", "-p", "3"])
            ++ [ "--"
               , "-i", "", "-O", " <timeleft> <watts>"
               , "-o", " <timeleft> <watts>"
               , "-H", "16", "-L", "10"
               , "-h", "sienna4", "-l", "gray20"]) 50 "batt0"

coreTemp p =
  CoreTemp (p <~> ["-t", "<core1>° <core2>°"
                  , "-L", "50", "-H", "75", "-d", "0"]) 50

diskU p =
  DiskU [("dm-1", "<used>") , ("/media/sdb", " s <used>")]
        (p <~> ["-L", "20", "-H", "70", "-m", "1", "-p", "3"])
        20

diskIO p =
  DiskIO [("dm-1" , "<fn=2>⎗</fn> <read> <fn=2>⎘</fn> <write>")]
         (p <~> ["-f", "░", "-b", " ", "-L", "200000", "-H" , "10000000"
                , "-W", "5", "-w", "5", "-p", "3"])
         10

mbox = MBox [ ("I", "inbox", "darkseagreen4")
            , ("B", "bigml.spool", "sienna4")
            , ("S", "bigsup.spool", "sienna4")
            , ("G", "geiser.spool", "darkseagreen4")
            , ("X", "xmobar.spool", "darkseagreen4")
            , ("g", "gnu.spool", "")
            , ("k", "books.spool", "")
            ] ["-d", "/home/jao/var/mail", "-p", " ", "-s", ""] "mbox"

masterVol =
  Volume "default" "Master"
                  ["-t", "<status> <volume>"
                  , "--", "-C", "black", "-c", "sienna4", "-O", ""
                  , "-o", " ×"] 10

captureVol = Volume "default" "Capture" ["-t", "<volume>"] 10

kbd = Kbd [("us", ""), ("us(intl)", "   ⃣")]

brightness = Brightness ["--", "-D", "intel_backlight"] 10

memory = Memory ["-t","<available> M", "-p", "2"] 20

tun0 = Network "tun0" ["-t", "<dev>:", "-x", ""] 20

laTime = DateZone "%H" "en_US" "US/Pacific" "laTime" 10
localTime = Date "%R" "datetime" 10

trayPadding = Com "padding-icon.sh" [] "tray" 20