summaryrefslogtreecommitdiffhomepage
path: root/lib
diff options
context:
space:
mode:
authorjao <jao@gnu.org>2022-11-04 23:58:06 +0000
committerjao <jao@gnu.org>2022-11-04 23:58:06 +0000
commitc300eff998d758bf867abbb7f39bf6fdfecf7a2e (patch)
treefcf0641ea3a35db733fd31504e5312029edb3f63 /lib
parent07c093c9b351466e60b93692c7d05b949bd71b0c (diff)
downloadxmobar-config-c300eff998d758bf867abbb7f39bf6fdfecf7a2e.tar.gz
xmobar-config-c300eff998d758bf867abbb7f39bf6fdfecf7a2e.tar.bz2
cleanups and unused code removed
Diffstat (limited to 'lib')
-rw-r--r--lib/Attic.hs51
-rw-r--r--lib/Config.hs9
-rw-r--r--lib/Monitors.hs102
-rw-r--r--lib/Music.hs8
4 files changed, 88 insertions, 82 deletions
diff --git a/lib/Attic.hs b/lib/Attic.hs
new file mode 100644
index 0000000..3697b82
--- /dev/null
+++ b/lib/Attic.hs
@@ -0,0 +1,51 @@
+module Attic where
+
+import Xmobar
+import Config
+import Control.Concurrent
+import Control.Concurrent.Async (async)
+import Control.Concurrent.STM
+import qualified Data.Char as Char
+import qualified Text.Printf as Printf
+
+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 <- newTVarIO ""
+ stb <- newTVarIO ""
+ _ <- async $ start a (atomically . writeTVar sta)
+ _ <- async $ start b (atomically . writeTVar stb)
+ go sta stb
+ where go sta' stb' = do
+ s <- readTVarIO sta'
+ t <- readTVarIO stb'
+ cmb s t
+ tenthSeconds $ min (rate b) (rate a)
+ go sta' stb'
+
+guardedMonitor a p = CombinedMonitor (PipeReader p (alias a ++ "_g")) a f
+ where f s t = if null s || head s == '0' then "" else t
+
+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)
+toggleMonitor path a = altMonitor (guardedMonitor a path)
+
+-- compMPD p = concatMonitor " " mpd (autoMPD "150" (pIsLight p))
+-- alt x p = altMonitor (mpris p x 165) (compMPD p)
+
+-- config cl p =
+-- if cl == "mpd"
+-- then mpdConfig p
+-- else Bottom.config [Run (alt cl p)] "|mpris2_mpd_autompd|" p
diff --git a/lib/Config.hs b/lib/Config.hs
index 7e1b2bb..a388e1e 100644
--- a/lib/Config.hs
+++ b/lib/Config.hs
@@ -85,14 +85,7 @@ baseConfig p = defaultConfig {
, borderColor = pBorder p
, fgColor = pForeground p
, bgColor = pBackground p
- , additionalFonts = [ "xft:Symbola-9"
- , "xft:Symbola-10"
- , "xft:Symbola-11"
- , "xft:Symbola-11"
- , "xft:Symbola-12"
- , "xft:FontAwesome-10"
- , "xft:FontAwesome-9"]
-
+ , additionalFonts = ["FontAwesome 9"]
, border = NoBorder
, alpha = pAlpha p
, overrideRedirect = True
diff --git a/lib/Monitors.hs b/lib/Monitors.hs
index d154ec3..ddff5b4 100644
--- a/lib/Monitors.hs
+++ b/lib/Monitors.hs
@@ -8,40 +8,6 @@ import Control.Concurrent.STM
import qualified Data.Char as Char
import qualified Text.Printf as Printf
-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 (atomically . writeTVar sta)
- _ <- async $ start b (atomically . writeTVar stb)
- go sta stb
- where go sta' stb' = do
- s <- readTVarIO sta'
- t <- readTVarIO stb'
- cmb s t
- tenthSeconds $ min (rate b) (rate a)
- go sta' stb'
-
-guardedMonitor a p = CombinedMonitor (PipeReader p (alias a ++ "_g")) a f
- where f s t = if null s || head s == '0' then "" else t
-
-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)
-toggleMonitor path a = altMonitor (guardedMonitor a path)
-
topProc p = TopProc (p <~> ["-t" , "<mboth3> <mboth2> <mboth1> \
\ยท <both3> <both2> <both1>"
, "-w", "10", "-L" , "10", "-H", "80"]) 15
@@ -80,32 +46,32 @@ uptime p = Uptime (p <~> [ "-t" , "<days> <hours>", "-m", "3", "-c", "0", "-S"
weather' tmp st p =
WeatherX st
- [ ("", fc (pDim p) (fn 4 "๐ŸŒก"))
- , ("clear", fn 4 "๐ŸŒฃ")
- , ("sunny", fc (pHigh p) $ fn 4 "๐ŸŒฃ")
- , ("fair", fn 4 "๐ŸŒฃ")
- , ("mostly clear", fn 4 "๐ŸŒค")
- , ("mostly sunny", fn 4 "๐ŸŒค")
- , ("partly sunny", fn 3 "โ›…")
- , ("obscured", fn 4 "๐ŸŒ") -- ๐ŸŒซ
- , ("mist", fn 4 "๐ŸŒ")
- , ("cloudy", fn 3 "โ˜")
- , ("overcast", fn 3 "โ˜๏ธ")
- , ("partly cloudy", fn 3 "โ›…")
- , ("mostly cloudy", fn 3 "โ˜๏ธ")
- , ("considerable cloudiness", fn 3 "โ˜๏ธ")
- , ("light rain", fn 4 "๐ŸŒง")
- , ("rain", fn 4 "โ›†")
- , ("ice crystals", snow)
- , ("light snow", fn 3 "๐ŸŒจ")
- , ("snow", snow)
+ [ ("", "\129695")
+ , ("clear", "๐Ÿ”†")
+ , ("sunny", "๐Ÿ”†")
+ , ("fair", "๐Ÿ”†")
+ , ("mostly clear", "๐ŸŒค๏ธ")
+ , ("mostly sunny", "๐ŸŒค๏ธ")
+ , ("partly sunny", "โ›…")
+ , ("obscured", "๐ŸŒ")
+ , ("fog", "๐ŸŒซ๏ธ")
+ , ("foggy", "๐ŸŒซ๏ธ")
+ , ("cloudy", "โ˜๏ธ")
+ , ("overcast", "โ˜๏ธ")
+ , ("partly cloudy", "โ›…")
+ , ("mostly cloudy", "โ˜๏ธ")
+ , ("considerable cloudiness", "๐ŸŒ‚")
+ , ("light rain", "๐ŸŒฆ๏ธ")
+ , ("rain", "๐ŸŒจ๏ธ")
+ , ("ice crystals", "โ„๏ธ")
+ , ("light snow", "๐ŸŒจ๏ธ")
+ , ("snow", "โ„๏ธ")
]
- (mkArgs p ["-t", tmp , "-L","10", "-H", "25" , "-T", "25", "-E", ".."]
+ (mkArgs p ["-t", tmp , "-L", "10", "-H", "25" , "-T", "25", "-E", "โ€ฆ"]
["-w", ""])
18000
- where snow = fni "\xf2dc"
-weather = weather' "<skyConditionS> <tempC>ยฐ <rh>% <windKmh> (<hour>)"
+weather = weather' "<skyConditionS> <tempC>ยฐ <windKmh> <weather>"
-- "https://wttr.in?format=" ++ fnn 3 "%c" ++ "+%t+%C+%w++" ++ fnn 1 "%m"
-- , Run (ComX "curl" [wttrURL "Edinburgh"] "" "wttr" 18000)
@@ -128,9 +94,9 @@ batt p =
, "-P"
, "-a", "notify-send -u critical 'Battery running out!!!!!!'"
, "-A", "7"
- , "-i", fn 2 "\9211"
- , "-O", fn 2 " \9211" ++ " <timeleft> <watts>"
- , "-o", fn 2 " ๐Ÿ”‹" ++ " <timeleft> <watts>"
+ , "-i", fn 1 "\9211"
+ , "-O", fn 1 " \9211" ++ " <timeleft> <watts>"
+ , "-o", fn 1 " ๐Ÿ”‹" ++ " <timeleft> <watts>"
, "-H", "10", "-L", "7"
, "-h", pHigh p, "-l", pLow p] 50 "batt0"
@@ -140,15 +106,15 @@ iconBatt p =
, "-S", "Off", "-d", "0", "-m", "2"
, "-L", "10", "-H", "90", "-p", "2"
, "-W", "0", "-f",
- "\xf244\xf243\xf243\xf243\xf242\xf242\xf242\xf241\xf241\xf240"
+ "\xf244\xf243\xf243\xf242\xf242\xf242\xf241\xf241\xf241\xf240"
, "--low", pHigh p, "--normal", pNormal p, "--high", pLow p
, "--"
, "-P"
, "-a", "notify-send -u critical 'Battery running out!!!!!!'"
, "-A", "5"
- , "-i", fni "\xf011"
- , "-O", fni "\xf1e6 <leftbar>" ++ " <left> <watts> <timeleft>"
- , "-o", fni "<leftbar>" ++ " <left> <watts> <timeleft>"
+ , "-i", fn 1 "\xf011"
+ , "-O", fn 1 "\xf1e6 <leftbar>" ++ " <left> <watts> <timeleft>"
+ , "-o", fn 1 "<leftbar>" ++ " <left> <watts> <timeleft>"
, "-H", "10", "-L", "7"
, "-h", pHigh p, "-l", pLow p] 50 "batt0"
@@ -202,18 +168,22 @@ mail p = MailX [ ("I", "jao/inbox", pHigh p)
[ "-d", "~/var/mail", "-s", " "]
"mail"
+nmmail = NotmuchMail "mail" [MailItem "J" "" qj, MailItem "B" "" qb] 100
+ where qb = "(tag:bigml or tag:alba) and tag:new"
+ qj = "(tag:jao or tag:hacking or tag:bills) and tag:new"
+
masterVol p =
Volume "default" "Master"
["-t", "<status> <volume>"
, "--", "-C", pForeground p, "-c", "#8b4726"
- , "-O", fni "\xf025" -- "\xf130" fn 4 "๐ŸŽง"
- , "-o", fn 4 "๐Ÿ”‡"
+ , "-O", fn 1 "\xf025"
+ , "-o", fn 1 "\xf131"
] 10
captureVol = Volume "default" "Capture" ["-t", "<volume>"] 10
kbd p = Kbd [("us", ""), ("us(intl)", kbi pHigh)] -- kbi pDim
- where kbi a = fc (a p) (fni " \xf11c")
+ where kbi a = fc (a p) (fn 1 " \xf11c")
brightness = Brightness ["--", "-D", "intel_backlight"] 10
brightness' = Brightness ["--", "-D", "amdgpu_bl0", "-C", "brightness"] 10
diff --git a/lib/Music.hs b/lib/Music.hs
index 7f0215a..3b7bec4 100644
--- a/lib/Music.hs
+++ b/lib/Music.hs
@@ -41,11 +41,3 @@ mpdConfig p =
{
textOffsets = [defaultHeight - 7, defaultHeight - 6]
}
-
-compMPD p = concatMonitor " " mpd (autoMPD "150" (pIsLight p))
-alt x p = altMonitor (mpris p x 165) (compMPD p)
-
-config cl p =
- if cl == "mpd"
- then mpdConfig p
- else Bottom.config [Run (alt cl p)] "|mpris2_mpd_autompd|" p