From 56a292496f1630e39fd4b355762aaf14bc8e5677 Mon Sep 17 00:00:00 2001
From: Alexander Foremny <aforemny@posteo.de>
Date: Mon, 6 May 2024 13:01:07 +0200
Subject: feat: add `--icons`

astatusbar can be started with the option `--icons` and will replace
sensor labels with appropriate icons. The user is expected to have Nerd
Fonts, in particular IosevkaTerm Nerd Font, installed.
---
 app/Main.hs | 40 ++++++++++++++++++++++++++--------------
 1 file changed, 26 insertions(+), 14 deletions(-)

(limited to 'app')

diff --git a/app/Main.hs b/app/Main.hs
index 8dc5d5f..30a40df 100644
--- a/app/Main.hs
+++ b/app/Main.hs
@@ -4,6 +4,7 @@
 {-# LANGUAGE RecordWildCards #-}
 {-# LANGUAGE StrictData #-}
 {-# LANGUAGE TypeFamilies #-}
+{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
 
 module Main where
 
@@ -18,12 +19,23 @@ import GHC.Ptr (Ptr)
 import Graphics.X11 qualified as X
 import Graphics.X11.Xft qualified as X
 import Graphics.X11.Xlib.Extras qualified as X
+import Options.Applicative qualified as O
 import Pretty qualified as P
 import Sensor
 import Ui hiding (Env)
 import Ui qualified
 import UnliftIO.STM
 
+data Args = Args
+  { icons :: Bool
+  }
+
+args :: O.ParserInfo Args
+args = O.info (Args <$> iconsArg) O.idm
+
+iconsArg :: O.Parser Bool
+iconsArg = O.switch (O.long "icons")
+
 data Env = Env
   { dpy :: X.Display,
     win :: X.Window,
@@ -50,8 +62,9 @@ data State = State
 
 main :: IO ()
 main = do
-  bracket createWindow destroyWindow $ \(env, stateT) ->
-    withColors env (run env stateT)
+  O.execParser args >>= \args -> do
+    bracket (createWindow args) destroyWindow $ \(env, stateT) ->
+      withColors env (run env stateT)
 
 data LastRun = LastRun
   { pUi :: Ui Identity P.Doc,
@@ -122,8 +135,8 @@ destroyWindow :: (Env, TVar State) -> IO ()
 destroyWindow (Env {..}, _) = do
   X.destroyWindow dpy win
 
-createWindow :: IO (Env, TVar State)
-createWindow = do
+createWindow :: Args -> IO (Env, TVar State)
+createWindow args = do
   dpy <- X.openDisplay ""
   let scrn = X.defaultScreen dpy
       scr = X.defaultScreenOfDisplay dpy
@@ -169,7 +182,7 @@ createWindow = do
   pixm <- X.createPixmap dpy win (fi wwidth) (fi wheight) dpth
   gc <- X.createGC dpy win
   drw <- X.xftDrawCreate dpy pixm vis cmap
-  fnt <- X.xftFontOpen dpy scr "Free Mono:size=15"
+  fnt <- X.xftFontOpen dpy scr "IosevkaTerm Nerd Font:size=14"
   X.mapWindow dpy win
   let dirty = True
   ui <-
@@ -177,15 +190,14 @@ createWindow = do
       intercalate [lit " "] $
         [ [sens wmWorkspaces],
           [sens wmName, fill],
-          [lit "cpu ", sens cpu],
-          [lit "mem ", sens mem],
-          [lit "disk ", sens disk],
-          [lit "io ", sens io],
-          [lit "net ", sens net],
-          [lit "snd ", sens Sensor.snd],
-          [lit "bat ", sens bat],
-          [lit "date ", sens date],
-          [lit "time ", sens time]
+          [lit (if args.icons then "\xf4bc  " else "cpu "), sens cpu],
+          [lit (if args.icons then "\xf035b  " else "mem "), sens mem],
+          [lit (if args.icons then "\xf0a0  " else "disk "), sens disk],
+          [lit (if args.icons then "\xf1638  " else "io "), sens io],
+          [lit (if args.icons then "\xf0200  " else "net "), sens net],
+          [lit (if args.icons then "\xf028  " else "snd "), sens Sensor.snd],
+          [lit (if args.icons then "\xf240  " else "bat "), sens bat],
+          [lit " ", sens date, lit ", ", sens time]
         ]
   let env = Env {..}
   stateT <- newTVarIO State {..}
-- 
cgit v1.2.3