REF update compiler flags

This commit is contained in:
Nathan Dwarshuis 2023-02-12 23:08:05 -05:00
parent 7d5a82bd07
commit 71e86f2233
31 changed files with 128 additions and 159 deletions

View File

@ -1,6 +1,3 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
-- | Start a VirtualBox instance with a sentinel wrapper process. -- | Start a VirtualBox instance with a sentinel wrapper process.
-- --
-- The only reason why this is needed is because I want to manage virtualboxes -- The only reason why this is needed is because I want to manage virtualboxes

View File

@ -1,5 +1,3 @@
{-# LANGUAGE OverloadedStrings #-}
-- | Xmobar binary -- | Xmobar binary
-- --
-- Features: -- Features:
@ -19,6 +17,7 @@ import qualified RIO.ByteString.Lazy as BL
import RIO.List import RIO.List
import RIO.Process import RIO.Process
import qualified RIO.Text as T import qualified RIO.Text as T
import XMonad.Config.Prime (enumFrom)
import XMonad.Core hiding (config) import XMonad.Core hiding (config)
import XMonad.Internal.Command.Desktop import XMonad.Internal.Command.Desktop
import XMonad.Internal.Command.Power import XMonad.Internal.Command.Power
@ -308,8 +307,7 @@ iconIO_
iconIO_ = iconSometimes' And_ Only_ iconIO_ = iconSometimes' And_ Only_
iconDBus iconDBus
:: SafeClient c :: T.Text
=> T.Text
-> XPQuery -> XPQuery
-> (Fontifier -> DBusTree c p -> Root CmdSpec) -> (Fontifier -> DBusTree c p -> Root CmdSpec)
-> DBusTree c p -> DBusTree c p
@ -317,8 +315,7 @@ iconDBus
iconDBus = iconSometimes' And1 $ Only_ . DBusIO iconDBus = iconSometimes' And1 $ Only_ . DBusIO
iconDBus_ iconDBus_
:: SafeClient c :: T.Text
=> T.Text
-> XPQuery -> XPQuery
-> (Fontifier -> DBusTree_ c -> Root CmdSpec) -> (Fontifier -> DBusTree_ c -> Root CmdSpec)
-> DBusTree_ c -> DBusTree_ c

View File

@ -1,8 +1,4 @@
{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE ImplicitPrelude #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- XMonad binary -- XMonad binary
@ -51,6 +47,7 @@ import XMonad.Internal.DBus.Removable
import XMonad.Internal.DBus.Screensaver import XMonad.Internal.DBus.Screensaver
import XMonad.Internal.Shell hiding (proc) import XMonad.Internal.Shell hiding (proc)
import qualified XMonad.Internal.Theme as XT import qualified XMonad.Internal.Theme as XT
import XMonad.Layout.Decoration
import XMonad.Layout.MultiToggle import XMonad.Layout.MultiToggle
import XMonad.Layout.NoBorders import XMonad.Layout.NoBorders
import XMonad.Layout.NoFrillsDecoration import XMonad.Layout.NoFrillsDecoration
@ -464,6 +461,10 @@ myLayouts tt =
mkToggle (single HIDE) $ mkToggle (single HIDE) $
tall ||| fulltab ||| full tall ||| fulltab ||| full
where where
addTopBar
:: (Eq a)
=> l a
-> ModifiedLayout (Decoration NoFrillsDecoration DefaultShrinker) l a
addTopBar = noFrillsDeco shrinkText tt addTopBar = noFrillsDeco shrinkText tt
tall = tall =
renamed [Replace "Tall"] $ renamed [Replace "Tall"] $

View File

@ -1,7 +1,3 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE OverloadedStrings #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Common internal DBus functions -- Common internal DBus functions
@ -115,11 +111,11 @@ type DIO env c = RIO (DBusEnv env c)
instance HasClient (DBusEnv SimpleApp) where instance HasClient (DBusEnv SimpleApp) where
clientL = lens dClient (\x y -> x {dClient = y}) clientL = lens dClient (\x y -> x {dClient = y})
instance SafeClient c => HasLogFunc (DBusEnv SimpleApp c) where instance HasLogFunc (DBusEnv SimpleApp c) where
logFuncL = lens dEnv (\x y -> x {dEnv = y}) . logFuncL logFuncL = lens dEnv (\x y -> x {dEnv = y}) . logFuncL
withDIO withDIO
:: (MonadUnliftIO m, MonadReader env m, SafeClient c) :: (MonadUnliftIO m, MonadReader env m)
=> c => c
-> DIO env c a -> DIO env c a
-> m a -> m a
@ -204,7 +200,6 @@ type SignalCallback m = [Variant] -> m ()
addMatchCallback addMatchCallback
:: ( MonadReader (env c) m :: ( MonadReader (env c) m
, HasLogFunc (env c)
, MonadUnliftIO m , MonadUnliftIO m
, SafeClient c , SafeClient c
, HasClient env , HasClient env

View File

@ -1,11 +1,4 @@
{-# LANGUAGE DeriveFunctor #-} {-# LANGUAGE ImplicitPrelude #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Functions for handling dependencies -- Functions for handling dependencies
@ -425,7 +418,7 @@ data XEnv = XEnv
instance HasLogFunc XEnv where instance HasLogFunc XEnv where
logFuncL = lens xLogFun (\x y -> x {xLogFun = y}) logFuncL = lens xLogFun (\x y -> x {xLogFun = y})
instance SafeClient c => HasLogFunc (DBusEnv XEnv c) where instance HasLogFunc (DBusEnv XEnv c) where
logFuncL = lens dEnv (\x y -> x {dEnv = y}) . logFuncL logFuncL = lens dEnv (\x y -> x {dEnv = y}) . logFuncL
instance HasProcessContext XEnv where instance HasProcessContext XEnv where

View File

@ -1,5 +1,3 @@
{-# LANGUAGE OverloadedStrings #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Dmenu (Rofi) Commands -- Dmenu (Rofi) Commands
@ -210,7 +208,7 @@ runClipMenu = sometimesIO_ "clipboard manager" "rofi greenclip" tree act
-- Shortcut menu -- Shortcut menu
runShowKeys runShowKeys
:: (MonadReader env m, HasLogFunc env, MonadUnliftIO m) :: (MonadReader env m, MonadUnliftIO m)
=> Always ([((KeyMask, KeySym), NamedAction)] -> m ()) => Always ([((KeyMask, KeySym), NamedAction)] -> m ())
runShowKeys = runShowKeys =
Always "keyboard menu" $ Always "keyboard menu" $
@ -225,7 +223,7 @@ runShowKeys =
defNoteError {body = Just $ Text "could not display keymap"} defNoteError {body = Just $ Text "could not display keymap"}
showKeysDMenu showKeysDMenu
:: (MonadReader env m, HasLogFunc env, MonadUnliftIO m) :: (MonadReader env m, MonadUnliftIO m)
=> SubfeatureRoot ([((KeyMask, KeySym), NamedAction)] -> m ()) => SubfeatureRoot ([((KeyMask, KeySym), NamedAction)] -> m ())
showKeysDMenu = showKeysDMenu =
Subfeature Subfeature
@ -234,7 +232,7 @@ showKeysDMenu =
} }
showKeys showKeys
:: (MonadReader env m, HasLogFunc env, MonadUnliftIO m) :: (MonadReader env m, MonadUnliftIO m)
=> [((KeyMask, KeySym), NamedAction)] => [((KeyMask, KeySym), NamedAction)]
-> m () -> m ()
showKeys kbs = do showKeys kbs = do

View File

@ -1,5 +1,3 @@
{-# LANGUAGE OverloadedStrings #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- General commands -- General commands

View File

@ -1,5 +1,3 @@
{-# LANGUAGE OverloadedStrings #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Commands for controlling power -- Commands for controlling power
@ -181,17 +179,20 @@ data PowerMaybeAction
| Reboot | Reboot
deriving (Eq) deriving (Eq)
instance Enum PowerMaybeAction where fromPMA :: PowerMaybeAction -> Int
toEnum 0 = Poweroff fromPMA a = case a of
toEnum 1 = Shutdown Poweroff -> 0
toEnum 2 = Hibernate Shutdown -> 1
toEnum 3 = Reboot Hibernate -> 2
toEnum _ = errorWithoutStackTrace "Main.Enum.PowerMaybeAction.toEnum: bad argument" Reboot -> 3
fromEnum Poweroff = 0 toPMA :: Int -> Maybe PowerMaybeAction
fromEnum Shutdown = 1 toPMA x = case x of
fromEnum Hibernate = 2 0 -> Just Poweroff
fromEnum Reboot = 3 1 -> Just Shutdown
2 -> Just Hibernate
3 -> Just Reboot
_ -> Nothing
data PowerPrompt = PowerPrompt data PowerPrompt = PowerPrompt
@ -223,9 +224,11 @@ powerPrompt lock fb = mkXPrompt PowerPrompt theme comp executeMaybeAction
, (xK_Return, quit) , (xK_Return, quit)
, (xK_Escape, quit) , (xK_Escape, quit)
] ]
sendMaybeAction a = setInput (show $ fromEnum a) >> setSuccess True >> setDone True sendMaybeAction a = setInput (show $ fromPMA a) >> setSuccess True >> setDone True
executeMaybeAction a = case toEnum $ read a of executeMaybeAction a = case toPMA =<< readMaybe a of
Poweroff -> liftIO runPowerOff Just Poweroff -> liftIO runPowerOff
Shutdown -> lock >> liftIO runSuspend Just Shutdown -> lock >> liftIO runSuspend
Hibernate -> lock >> liftIO runHibernate Just Hibernate -> lock >> liftIO runHibernate
Reboot -> liftIO runReboot Just Reboot -> liftIO runReboot
-- TODO log an error here since this should never happen
Nothing -> skip

View File

@ -1,6 +1,3 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Concurrent module to handle events from acpid -- Concurrent module to handle events from acpid
@ -33,15 +30,18 @@ data ACPIEvent
| LidClose | LidClose
deriving (Eq) deriving (Eq)
instance Enum ACPIEvent where fromACPIEvent :: ACPIEvent -> Int
toEnum 0 = Power fromACPIEvent x = case x of
toEnum 1 = Sleep Power -> 0
toEnum 2 = LidClose Sleep -> 1
toEnum _ = errorWithoutStackTrace "ACPI.Enum.ACPIEvent.toEnum: bad argument" LidClose -> 2
fromEnum Power = 0 toACPIEvent :: Int -> Maybe ACPIEvent
fromEnum Sleep = 1 toACPIEvent x = case x of
fromEnum LidClose = 2 0 -> Just Power
1 -> Just Sleep
2 -> Just LidClose
_ -> Nothing
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Internal functions -- Internal functions
@ -64,7 +64,7 @@ parseLine line =
-- | Send an ACPIEvent to the X server as a ClientMessage -- | Send an ACPIEvent to the X server as a ClientMessage
sendACPIEvent :: ACPIEvent -> IO () sendACPIEvent :: ACPIEvent -> IO ()
sendACPIEvent = sendXMsg ACPI . show . fromEnum sendACPIEvent = sendXMsg ACPI . show . fromACPIEvent
isDischarging :: IO (Maybe Bool) isDischarging :: IO (Maybe Bool)
isDischarging = do isDischarging = do
@ -91,7 +91,7 @@ socketDep = Only_ $ pathR acpiPath [Package Official "acpid"]
-- Xmonad's event hook) -- Xmonad's event hook)
handleACPI :: FontBuilder -> X () -> String -> X () handleACPI :: FontBuilder -> X () -> String -> X ()
handleACPI fb lock tag = do handleACPI fb lock tag = do
let acpiTag = toEnum <$> readMaybe tag :: Maybe ACPIEvent let acpiTag = toACPIEvent =<< readMaybe tag :: Maybe ACPIEvent
forM_ acpiTag $ \case forM_ acpiTag $ \case
Power -> powerPrompt lock fb Power -> powerPrompt lock fb
Sleep -> suspendPrompt fb Sleep -> suspendPrompt fb

View File

@ -28,6 +28,7 @@ import Graphics.X11.Xlib.Atom
import Graphics.X11.Xlib.Display import Graphics.X11.Xlib.Display
import Graphics.X11.Xlib.Event import Graphics.X11.Xlib.Event
import Graphics.X11.Xlib.Extras import Graphics.X11.Xlib.Extras
import RIO
import XMonad.Internal.IO import XMonad.Internal.IO
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
@ -42,14 +43,18 @@ data XMsgType
| Unknown | Unknown
deriving (Eq, Show) deriving (Eq, Show)
instance Enum XMsgType where fromXMsgType :: XMsgType -> Int
toEnum 0 = ACPI fromXMsgType x = case x of
toEnum 1 = Workspace ACPI -> 0
toEnum _ = errorWithoutStackTrace "ACPI.Enum.ACPIEvent.toEnum: bad argument" Workspace -> 1
Unknown -> 2
fromEnum ACPI = 0 toXMsgType :: Int -> Maybe XMsgType
fromEnum Workspace = 1 toXMsgType x = case x of
fromEnum Unknown = 2 0 -> Just ACPI
1 -> Just Workspace
2 -> Just Unknown
_ -> Nothing
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Exported API -- Exported API
@ -58,9 +63,9 @@ instance Enum XMsgType where
-- type and payload -- type and payload
splitXMsg :: (Integral a) => [a] -> (XMsgType, String) splitXMsg :: (Integral a) => [a] -> (XMsgType, String)
splitXMsg [] = (Unknown, "") splitXMsg [] = (Unknown, "")
splitXMsg (x : xs) = (xtype, tag) splitXMsg (x : xs) = (fromMaybe Unknown xtype, tag)
where where
xtype = toEnum $ fromIntegral x xtype = toXMsgType $ fromIntegral x
tag = chr . fromIntegral <$> takeWhile (/= 0) xs tag = chr . fromIntegral <$> takeWhile (/= 0) xs
-- | Emit a ClientMessage event to the X server with the given type and payloud -- | Emit a ClientMessage event to the X server with the given type and payloud
@ -86,5 +91,5 @@ sendXMsg xtype tag = withOpenDisplay $ \dpy -> do
setClientMessageEvent' e root bITMAP 8 (x : t) setClientMessageEvent' e root bITMAP 8 (x : t)
sendEvent dpy root False substructureNotifyMask e sendEvent dpy root False substructureNotifyMask e
where where
x = fromIntegral $ fromEnum xtype x = fromIntegral $ fromXMsgType xtype
t = fmap (fromIntegral . fromEnum) tag t = fmap (fromIntegral . fromEnum) tag

View File

@ -1,5 +1,3 @@
{-# LANGUAGE OverloadedStrings #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Automatically Manage Dynamic Workspaces -- Automatically Manage Dynamic Workspaces
-- This is a somewhat convoluted wrapper for the Dymamic Workspaces module -- This is a somewhat convoluted wrapper for the Dymamic Workspaces module

View File

@ -1,6 +1,3 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- VirtualBox-specific functions -- VirtualBox-specific functions
@ -36,7 +33,7 @@ vmInstanceConfig vmName = do
vmDirectory :: IO (Either String String) vmDirectory :: IO (Either String String)
vmDirectory = do vmDirectory = do
p <- vmConfig p <- vmConfig
s <- tryIO $ readFile p s <- tryIO $ readFileUtf8 p
return $ case s of return $ case s of
(Left _) -> Left "could not read VirtualBox config file" (Left _) -> Left "could not read VirtualBox config file"
(Right x) -> (Right x) ->

View File

@ -1,6 +1,3 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- DBus module for Clevo Keyboard control -- DBus module for Clevo Keyboard control
@ -142,7 +139,6 @@ callGetBrightnessCK = callGetBrightness clevoKeyboardConfig
matchSignalCK matchSignalCK
:: ( SafeClient c :: ( SafeClient c
, HasLogFunc (env c)
, HasClient env , HasClient env
, MonadReader (env c) m , MonadReader (env c) m
, MonadUnliftIO m , MonadUnliftIO m

View File

@ -1,7 +1,3 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TupleSections #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- DBus module for DBus brightness controls -- DBus module for DBus brightness controls
@ -88,7 +84,6 @@ signalDep BrightnessConfig {bcPath = p, bcInterface = i} =
matchSignal matchSignal
:: ( HasClient env :: ( HasClient env
, HasLogFunc (env c)
, MonadReader (env c) m , MonadReader (env c) m
, MonadUnliftIO m , MonadUnliftIO m
, SafeClient c , SafeClient c

View File

@ -1,6 +1,3 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- DBus module for Intel Backlight control -- DBus module for Intel Backlight control
@ -128,7 +125,6 @@ callGetBrightnessIB = callGetBrightness intelBacklightConfig
matchSignalIB matchSignalIB
:: ( SafeClient c :: ( SafeClient c
, HasLogFunc (env c)
, HasClient env , HasClient env
, MonadReader (env c) m , MonadReader (env c) m
, MonadUnliftIO m , MonadUnliftIO m

View File

@ -1,6 +1,3 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- High-level interface for managing XMonad's DBus -- High-level interface for managing XMonad's DBus
@ -80,6 +77,7 @@ connectDBus = do
disconnectDBus :: MonadUnliftIO m => DBusState -> m () disconnectDBus :: MonadUnliftIO m => DBusState -> m ()
disconnectDBus db = disc dbSesClient >> disc dbSysClient disconnectDBus db = disc dbSesClient >> disc dbSysClient
where where
disc :: (MonadUnliftIO m, SafeClient c) => (DBusState -> Maybe c) -> m ()
disc f = maybe (return ()) disconnectDBusClient $ f db disc f = maybe (return ()) disconnectDBusClient $ f db
-- | Connect to the DBus and request the XMonad name -- | Connect to the DBus and request the XMonad name

View File

@ -1,6 +1,3 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Module for monitoring removable drive events -- Module for monitoring removable drive events
-- --
@ -83,7 +80,6 @@ playSoundMaybe p b = when b $ io $ playSound p
-- enable the udisks2 service at boot; however this is not default behavior. -- enable the udisks2 service at boot; however this is not default behavior.
listenDevices listenDevices
:: ( HasClient (DBusEnv env) :: ( HasClient (DBusEnv env)
, HasLogFunc (DBusEnv env SysClient)
, MonadReader env m , MonadReader env m
, MonadUnliftIO m , MonadUnliftIO m
) )
@ -99,7 +95,6 @@ listenDevices cl = do
runRemovableMon runRemovableMon
:: ( HasClient (DBusEnv env) :: ( HasClient (DBusEnv env)
, HasLogFunc (DBusEnv env SysClient)
, MonadReader env m , MonadReader env m
, MonadUnliftIO m , MonadUnliftIO m
) )

View File

@ -1,6 +1,3 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- DBus module for X11 screensave/DPMS control -- DBus module for X11 screensave/DPMS control
@ -147,8 +144,7 @@ callQuery = do
return $ either (const Nothing) bodyGetCurrentState reply return $ either (const Nothing) bodyGetCurrentState reply
matchSignal matchSignal
:: ( HasLogFunc (env SesClient) :: ( HasClient env
, HasClient env
, MonadReader (env SesClient) m , MonadReader (env SesClient) m
, MonadUnliftIO m , MonadUnliftIO m
) )

View File

@ -1,5 +1,3 @@
{-# LANGUAGE ViewPatterns #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Random IO-ish functions used throughtout xmonad -- Random IO-ish functions used throughtout xmonad
-- --
@ -41,7 +39,7 @@ import System.Process
-- read -- read
readInt :: MonadIO m => (Read a, Integral a) => FilePath -> m a readInt :: MonadIO m => (Read a, Integral a) => FilePath -> m a
readInt = fmap (read . takeWhile isDigit . T.unpack) . readFileUtf8 readInt = fmap (fromMaybe 0 . readMaybe . takeWhile isDigit . T.unpack) . readFileUtf8
readBool :: MonadIO m => FilePath -> m Bool readBool :: MonadIO m => FilePath -> m Bool
readBool = fmap (== (1 :: Int)) . readInt readBool = fmap (== (1 :: Int)) . readInt
@ -49,7 +47,7 @@ readBool = fmap (== (1 :: Int)) . readInt
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- write -- write
writeInt :: MonadIO m => (Show a, Integral a) => FilePath -> a -> m () writeInt :: (MonadIO m, Show a) => FilePath -> a -> m ()
writeInt f = writeFileUtf8 f . T.pack . show writeInt f = writeFileUtf8 f . T.pack . show
writeBool :: MonadIO m => FilePath -> Bool -> m () writeBool :: MonadIO m => FilePath -> Bool -> m ()
@ -62,7 +60,7 @@ writeBool f b = writeInt f ((if b then 1 else 0) :: Int)
-- value. Assume that the file being read has a min of 0 and an unchanging max -- value. Assume that the file being read has a min of 0 and an unchanging max
-- given by a runtime argument, which is scaled linearly to the range 0-100 -- given by a runtime argument, which is scaled linearly to the range 0-100
-- (percent). -- (percent).
rawToPercent :: (Integral a, Integral b, Read b, RealFrac c) => (a, a) -> b -> c rawToPercent :: (Integral a, Integral b, RealFrac c) => (a, a) -> b -> c
rawToPercent (lower, upper) raw = rawToPercent (lower, upper) raw =
100 * (fromIntegral raw - fromIntegral lower) / fromIntegral (upper - lower) 100 * (fromIntegral raw - fromIntegral lower) / fromIntegral (upper - lower)

View File

@ -1,5 +1,3 @@
{-# LANGUAGE OverloadedStrings #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Functions for formatting and sending notifications -- Functions for formatting and sending notifications
-- --

View File

@ -1,5 +1,3 @@
{-# LANGUAGE OverloadedStrings #-}
-- Functions for formatting and spawning shell commands -- Functions for formatting and spawning shell commands
module XMonad.Internal.Shell module XMonad.Internal.Shell
@ -85,10 +83,7 @@ spawn :: MonadIO m => T.Text -> m ()
spawn = X.spawn . T.unpack spawn = X.spawn . T.unpack
-- | Run 'XMonad.Run.Utils.spawnPipe' with 'Text' input. -- | Run 'XMonad.Run.Utils.spawnPipe' with 'Text' input.
spawnPipe spawnPipe :: MonadUnliftIO m => T.Text -> m Handle
:: (MonadReader env m, HasLogFunc env, MonadUnliftIO m)
=> T.Text
-> m Handle
spawnPipe = liftIO . XR.spawnPipe . T.unpack spawnPipe = liftIO . XR.spawnPipe . T.unpack
-- spawnPipeRW -- spawnPipeRW

View File

@ -1,5 +1,3 @@
{-# LANGUAGE OverloadedStrings #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Theme for XMonad and Xmobar -- Theme for XMonad and Xmobar
@ -33,6 +31,7 @@ where
import Data.Colour import Data.Colour
import Data.Colour.SRGB import Data.Colour.SRGB
import RIO
import qualified RIO.Text as T import qualified RIO.Text as T
import qualified XMonad.Layout.Decoration as D import qualified XMonad.Layout.Decoration as D
import qualified XMonad.Prompt as P import qualified XMonad.Prompt as P

View File

@ -1,5 +1,3 @@
{-# LANGUAGE OverloadedStrings #-}
-- Common backlight plugin bits -- Common backlight plugin bits
-- --
-- Use the custom DBus interface exported by the XMonad process so I can react -- Use the custom DBus interface exported by the XMonad process so I can react

View File

@ -1,5 +1,3 @@
{-# LANGUAGE OverloadedStrings #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Bluetooth plugin -- Bluetooth plugin
-- --

View File

@ -1,5 +1,3 @@
{-# LANGUAGE OverloadedStrings #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Clevo Keyboard plugin -- Clevo Keyboard plugin
-- --
@ -12,6 +10,7 @@ module Xmobar.Plugins.ClevoKeyboard
) )
where where
import RIO
import qualified RIO.Text as T import qualified RIO.Text as T
import XMonad.Internal.DBus.Brightness.ClevoKeyboard import XMonad.Internal.DBus.Brightness.ClevoKeyboard
import Xmobar import Xmobar

View File

@ -1,5 +1,3 @@
{-# LANGUAGE OverloadedStrings #-}
module Xmobar.Plugins.Common module Xmobar.Plugins.Common
( colorText ( colorText
, startListener , startListener
@ -33,8 +31,7 @@ data Colors = Colors
deriving (Eq, Show, Read) deriving (Eq, Show, Read)
startListener startListener
:: ( HasLogFunc (env c) :: ( HasClient env
, HasClient env
, MonadReader (env c) m , MonadReader (env c) m
, MonadUnliftIO m , MonadUnliftIO m
, SafeClient c , SafeClient c

View File

@ -1,6 +1,3 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Device plugin -- Device plugin
-- --

View File

@ -1,5 +1,3 @@
{-# LANGUAGE OverloadedStrings #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Intel backlight plugin -- Intel backlight plugin
-- --
@ -12,6 +10,7 @@ module Xmobar.Plugins.IntelBacklight
) )
where where
import RIO
import qualified RIO.Text as T import qualified RIO.Text as T
import XMonad.Internal.DBus.Brightness.IntelBacklight import XMonad.Internal.DBus.Brightness.IntelBacklight
import Xmobar import Xmobar

View File

@ -1,5 +1,3 @@
{-# LANGUAGE OverloadedStrings #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Screensaver plugin -- Screensaver plugin
-- --
@ -13,6 +11,7 @@ module Xmobar.Plugins.Screensaver
where where
import Data.Internal.DBus import Data.Internal.DBus
import RIO
import qualified RIO.Text as T import qualified RIO.Text as T
import XMonad.Internal.DBus.Screensaver import XMonad.Internal.DBus.Screensaver
import Xmobar import Xmobar

View File

@ -1,6 +1,3 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- VPN plugin -- VPN plugin
-- --
@ -57,7 +54,7 @@ data VEnv c = VEnv
, vEnv :: !SimpleApp , vEnv :: !SimpleApp
} }
instance SafeClient c => HasLogFunc (VEnv c) where instance HasLogFunc (VEnv c) where
logFuncL = lens vEnv (\x y -> x {vEnv = y}) . logFuncL logFuncL = lens vEnv (\x y -> x {vEnv = y}) . logFuncL
instance HasClient VEnv where instance HasClient VEnv where

View File

@ -13,6 +13,43 @@ extra-source-files:
- scripts/* - scripts/*
- sound/* - sound/*
default-extensions:
- OverloadedStrings
- FlexibleContexts
- FlexibleInstances
- InstanceSigs
- MultiParamTypeClasses
- EmptyCase
- LambdaCase
- MultiWayIf
- NamedFieldPuns
- TupleSections
- DeriveFoldable
- DeriveFunctor
- DeriveGeneric
- DeriveLift
- DeriveTraversable
- DerivingStrategies
- DeriveDataTypeable
- EmptyDataDecls
- PartialTypeSignatures
- GeneralizedNewtypeDeriving
- StandaloneDeriving
- BangPatterns
- TypeOperators
- ScopedTypeVariables
- TypeApplications
- ConstraintKinds
- RankNTypes
- GADTs
- DefaultSignatures
- NoImplicitPrelude
- FunctionalDependencies
- DataKinds
- TypeFamilies
- BinaryLiterals
- ViewPatterns
dependencies: dependencies:
- rio >= 0.1.21.0 - rio >= 0.1.21.0
- X11 >= 1.9.1 - X11 >= 1.9.1
@ -37,14 +74,20 @@ dependencies:
- unliftio >= 0.2.21.0 - unliftio >= 0.2.21.0
- optparse-applicative >= 0.16.1.0 - optparse-applicative >= 0.16.1.0
library:
source-dirs: lib/
ghc-options: ghc-options:
- -Wall - -Wall
- -Werror - -Wcompat
- -Widentities
- -Wincomplete-record-updates
- -Wincomplete-uni-patterns
- -Wredundant-constraints
- -Wpartial-fields - -Wpartial-fields
- -Werror
- -O2 - -O2
library:
source-dirs: lib/
executables: executables:
xmobar: &bin xmobar: &bin
main: xmobar.hs main: xmobar.hs
@ -53,21 +96,15 @@ executables:
- xmonad-config - xmonad-config
ghc-options: ghc-options:
- -threaded - -threaded
- -Wall
- -Werror
- -Wpartial-fields
- -O2
xmonad: xmonad:
<<: *bin <<: *bin
main: xmonad.hs main: xmonad.hs
ghc-options: ghc-options:
- -threaded - -threaded
- -Wall
- -Werror
- -Wpartial-fields
- -O2
# this is needed to avoid writing super complex layout types # this is needed to avoid writing super complex layout types
- -fno-warn-missing-signatures - -fno-warn-missing-signatures
vbox-start: vbox-start:
<<: *bin <<: *bin
main: vbox-start.hs main: vbox-start.hs
ghc-options:
- -threaded