slotThe 2469269119 New module: XMonad.Prelude
This is a convenience module in order to have less import noise.  It
re-exports the following:

  a) Commonly used modules in full (Data.Foldable, Data.Applicative, and
     so on); though only those that play nicely with each other, so that
     XMonad.Prelude can be imported unqualified without any problems.
     This prevents things like `Prelude.(.)` and `Control.Category.(.)`
     fighting with each other.

  b) Helper functions that don't necessarily fit in any other module;
     e.g., the often used abbreviation `fi = fromIntegral`.
2021-05-13 17:44:47 +02:00

50 lines
1.2 KiB
Haskell

{-# LANGUAGE GeneralizedNewtypeDeriving #-}
-- experimental, not expected to work
{- our goal:
config = do
add layout Full
set terminal "urxvt"
add keys [blah blah blah]
-}
{-
ideas:
composability!
"only once" features like avoidStruts, ewmhDesktops
-}
module XMonad.Config.Monad where
import XMonad hiding (terminal, keys)
import qualified XMonad as X
import Control.Monad.Writer
import XMonad.Prelude
import Data.Accessor
import Data.Accessor.Basic hiding (set)
-- Ugly! To fix this we'll need to change the kind of XConfig.
newtype LayoutList a = LL [Layout a] deriving Monoid
type W = Dual (Endo (XConfig LayoutList))
mkW = Dual . Endo
newtype Config a = C (WriterT W IO a)
deriving (Functor, Monad, MonadWriter W)
-- references:
layout = fromSetGet (\x c -> c { layoutHook = x }) layoutHook
terminal = fromSetGet (\x c -> c { X.terminal = x }) X.terminal
keys = fromSetGet (\x c -> c { X.keys = x }) X.keys
set :: Accessor (XConfig LayoutList) a -> a -> Config ()
set r x = tell (mkW $ r ^= x)
add r x = tell (mkW (r ^: mappend x))
--
example :: Config ()
example = do
add layout $ LL [Layout $ Full] -- make this better
set terminal "urxvt"