Skip to content
New issue

Have a question about this project? Sign up for a free GitHub account to open an issue and contact its maintainers and the community.

By clicking “Sign up for GitHub”, you agree to our terms of service and privacy statement. We’ll occasionally send you account related emails.

Already on GitHub? Sign in to your account

[draft] workspace layouts #755

Open
wants to merge 8 commits into
base: master
Choose a base branch
from
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
142 changes: 142 additions & 0 deletions XMonad/Util/OneState.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,142 @@
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -Wall -Werror #-}

module XMonad.Util.OneState
Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

One quick thing: the implementation of this is pretty neat, the only question I have is whether we actually want to unify ExtensibleState and ExtensibleConf into one thing. Personally, I find the current situation quite convenient in terms of having a mental model of what a given piece of code can do, but maybe I'm alone in that (Cc. @liskin as the author of ExtensibleConf)

Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I don't think it's much about the situation being convenient or not. It's just a very elaborate workaround for not being able to initialise/modify (put) ExtensibleState in config-time. Or, to be more precise, not having a nice interface for it, as one can indeed do it using startupHook, but that's ugly, and composes poorly.

(I have yet to take a look at the rest of the code so I don't really have an opinion whether this elaborate workaround is worth it or whether there are easier ways to solve the same problem.)

Copy link
Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I believe OneState was created for two reasons. (1) I found combining state and config to be conceptually simpler and provide more flexibility for free (and at the time I wasn't too focused on thinking about merging into xmonad-contrib); and (2) I wanted to allow modifying the config at runtime, similar to what @liskin is saying.

Currently I don't think (2) is actually used. Originally I wanted to use it in order to allow adjustments to the grid layout at runtime, so you could, for instance, add and remove rows on-demand. I still think this would be worthwhile, although it's not on my TODO list at this moment.

Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Do we want the config to be modifiable at runtime though? I'm not sure

as one can indeed do it using startupHook, but that's ugly, and composes poorly.

@liskin could you elaborate? I mean, we can have a nice interface where we internally collect all defaults from the config, and compose then apply them in the startupHook. Might need some type magic, but I don't see why that's a problem.

Copy link
Member

@liskin liskin Oct 5, 2022

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Yeah, we can have an interface, and OneState is one such interface. Although it doesn't use startupHook, but there's a good reason for it: it really does compose poorly. You can't guarantee that a specific part of startupHook runs before everything else, so if you want to make a general-purpose ExtensibleState-like interface that can be initialised in config-time, you need to make it work even if the hook hasn't run yet. So you need to do exactly what OneState does: look into ExtensibleState and fall back to ExtensibleConf, every single time you access it.

If you didn't need a general-purpose interface and you knew the order of startupHooks doesn't matter in your specific case, then it's okay to just do a single ExtensibleConf → ExtensibleState sync in startupHook. It's not safe to do this in a general-purpose interface though.

Anyway, looks like nobody really needs this functionality now… :-)

Copy link
Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Anyway, looks like nobody really needs this functionality now… :-)

Well, I would like to export an all-powerful (State -> State) -> X () function from Grid so that users may modify their grid layout at runtime if they would like. (While one can certainly do without such a capability, I think it's also a reasonable desire)

( OneState (..)
, get
, put
, modify
, add
, once
, onceM
) where

import Control.Monad ((>=>))
import Data.Maybe (fromMaybe)
import XMonad hiding (config, get, modify, put,
state, trace)
import qualified XMonad.Util.ExtensibleConf as XC
import qualified XMonad.Util.ExtensibleState as XS


{- |

OneState is a replacement for both @XMonad.Util.ExtensibleState@ and @XMonad.Util.ExtensibleConf@

A comparison of these three modules is as follows:

- @ExtensibleConf@ allows the programmer to accept a user-supplied value at config-time.
However, this value cannot be changed during runtime.

- @ExtensibleState@ allows the programmer to keep mutable state.
However, the initial value for this state must be known at compile-time and is not
configurable at config-time.

- @OneState@ proves an API which matches the power of both @ExtensibleConf@ and @ExtensibleState@,
allowing the programmer to keep mutable state *and* allowing this mutable state to be configured
at config-time.

-}


class Typeable state => OneState state where

-- | Associated type of config-time modifications to state
type Mod state

-- |
--
-- How to apply a modification
--
-- This operation may have effects in the X monad. However, no strong
-- guarantees are made about its evaluation, such as guarantees about
-- timing or multiplicity. Beware!
merge :: Mod state -> (state -> X state)

-- | Default value for the state
defaultState :: state


-- hook into ExtensibleState
newtype State state = State (Maybe state)
deriving (Typeable)

instance OneState state => ExtensionClass (State state) where
initialValue = State Nothing

-- hook into ExtensibleConf
newtype Config state = Config [Mod state]
deriving newtype (Typeable, Semigroup)

trivialConfig :: Config state
trivialConfig = Config []


-- |
--
-- Like @ExtensibleState.get@
--
-- Retrieve the current state value
--
-- * If the state has been explicitly set during runtime, then the most recent
-- set value will be returned
--
-- * Otherwise, if the state was configured during config-time, then all the
-- config-time @Mod state@ values will be applied to @defaultState@, and
-- that will be returned
--
-- * Otherwise, @default@ is returned
get :: forall state. OneState state => X state
get = XS.get >>= \case
State (Just state) -> pure state
State Nothing -> foldConfig

where

foldConfig :: X state
foldConfig = do
Config deltas :: Config state <- fromMaybe trivialConfig <$> XC.ask
let bigDelta = foldr (>=>) pure $ merge <$> deltas
result <- bigDelta defaultState
put result -- modifications are monadic; ensure we only perform them once
pure result


-- | Like @ExtensibleState.put@
put :: OneState state => state -> X ()
put = XS.put . State . Just

-- | Like @ExtensibleState.modify@
modify :: OneState state => (state -> state) -> X ()
modify f = put =<< (f <$> get)


-- | Like @ExtensibleConf.onceM@
onceM
:: forall state m l
. (OneState state, Applicative m)
=> (XConfig l -> m (XConfig l))
-> Mod state
-> (XConfig l -> m (XConfig l))
onceM modX modState = XC.onceM modX (Config @state . one $ modState)
where one x = [x]

-- | Like @ExtensibleConf.once@
once
:: forall state l
. OneState state
=> (XConfig l -> XConfig l)
-> Mod state
-> (XConfig l -> XConfig l)
once modX modState = XC.once modX (Config @state . one $ modState)
where one x = [x]

-- | Like @ExtensibleConf.add@
add :: forall state l. OneState state => Mod state -> (XConfig l -> XConfig l)
add = once @state id
64 changes: 64 additions & 0 deletions XMonad/WorkspaceLayout/Core.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,64 @@
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -Wall -Werror #-}

{- |

Generic operations for workspace layouts

See 'XMonad.WorkspaceLayout.Grid'

-}

module XMonad.WorkspaceLayout.Core where

import Prelude hiding (span)

import Control.Category ((>>>))
import Data.Function (on)
import Data.List (elemIndex)
import GHC.Generics (Generic)
import XMonad hiding (config, modify, state,
trace, workspaces)
import XMonad.Hooks.StatusBar.PP (PP (..))
import XMonad.StackSet (tag)
import XMonad.Util.WorkspaceCompare (mkWsSort)


-- |
--
-- Encompasses information needed to render a workspace layout
data WorkspaceLayoutView = WSLView
{ label :: String
, neighborhood :: [WorkspaceId]
, toName :: WorkspaceId -> String
} deriving (Generic)


-- | Render a workspace layout onto an existing 'PP'
modPPWithWorkspaceLayout :: WorkspaceLayoutView -> (PP -> PP)
modPPWithWorkspaceLayout (WSLView { neighborhood, toName, label }) pp =
pp
-- display the workspace names
{ ppRename = (fmap . fmap) toName (ppRename pp)

-- display only a subset of workspaces (the "neighborhood") of the current workspace
, ppSort = do
oldSort <- ppSort pp
newSort <- do
sortIt <- (mkWsSort . pure) (compare `on` flip elemIndex neighborhood)
let filterIt = filter (tag >>> (`elem` neighborhood))
pure $ filterIt >>> sortIt
pure $ newSort . oldSort

-- display label to the left
, ppOrder = ppOrder pp >>> (\(ws : rest) -> (label <> ws) : rest)
}
126 changes: 126 additions & 0 deletions XMonad/WorkspaceLayout/Cycle.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,126 @@
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -Wall -Werror #-}

{- |

Cyclic one-dimensional workspace layouts for XMonad

This module is intended mostly to serve as another example workspace
layout other than 'XMonad.WorkspaceLayout.Grid'.

However, a cyclic layout is not particularly useful, and so this
module isn't /really/ intended to be used. Feel free to if you want,
though. It should still work!

-}

module XMonad.WorkspaceLayout.Cycle
( Coord (..)
, Config (..)
, BoundsMode (..)
, move
, swap
, hook
, getView
) where

import Prelude

import Control.Monad.State (execState)
import GHC.Generics (Generic)
import qualified XMonad
import XMonad hiding (config, state, trace,
workspaces)
import XMonad.StackSet (greedyView, shift)

import qualified XMonad.Util.OneState as St
import XMonad.Util.OneState (OneState (..))
import XMonad.WorkspaceLayout.Core (WorkspaceLayoutView (..))
import XMonad.WorkspaceLayout.Util (affineMod, (!%))



data Coord = Coord
{ offset :: Int
, position :: Int
}
deriving (Show, Eq, Ord, Generic)

data Config = Config
{ width :: Int
, workspaces :: [WorkspaceId]
}
deriving (Show, Generic)

data State = State
{ coord :: Coord
, config :: Config
}
deriving (Show, Generic)

instance OneState State where
type Mod State = State -> State
merge ma s = pure (ma s)
defaultState = State
{ coord = Coord 0 0
, config = Config 5 (single <$> ['a' .. 'j'])
}
where single = (:[])


data BoundsMode = Clamp | Wrap

move :: BoundsMode -> (Coord -> Coord) -> X ()
move mode f = do
(coord', wid') <- calc mode f
St.modify $ \st -> st { coord = coord' }
windows (greedyView wid')

swap :: BoundsMode -> (Coord -> Coord) -> X ()
swap mode f = do
(_, wid') <- calc mode f
windows (shift wid')

calc :: BoundsMode -> (Coord -> Coord) -> X (Coord, WorkspaceId)
calc mode f = do
State coord (Config { width, workspaces }) <- St.get
let coord' = flip execState coord $ do
modify f
offset' <- offset <$> get
modify $
let updatePosition =
(let lo = offset' - width `div` 2
hi = offset' + width `div` 2
in case mode of
Clamp -> max lo . min hi
Wrap -> affineMod (lo, hi))
in \st -> st { position = updatePosition (position st) }
let wid = workspaces !% (position coord')
pure (coord', wid)


hook :: Config -> XConfig l -> XConfig l
hook config = St.once @State
(\xc -> xc { XMonad.workspaces = workspaces config })
(\state -> state { config = config })

getView :: X WorkspaceLayoutView
getView = do
State (Coord { offset }) (Config { width, workspaces }) <- St.get
pure $ WSLView
{ toName = id
, label = ""
, neighborhood =
(do pos <- [offset - width `div` 2 .. offset + width `div` 2]
pure $ workspaces !% (pos `mod` length workspaces)
)
}

Loading