Skip to content

Instantly share code, notes, and snippets.

@LSLeary
Created March 15, 2018 03:02
Show Gist options
  • Save LSLeary/003bbccfa4d0c1a061d00659efe9bb9a to your computer and use it in GitHub Desktop.
Save LSLeary/003bbccfa4d0c1a061d00659efe9bb9a to your computer and use it in GitHub Desktop.
Optimise any focus-independent layout by caching rectangles?
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
module Cached
( Cached
, cached
) where
import XMonad
import qualified XMonad.StackSet as W
import Data.Maybe (fromMaybe)
data Cache a = Cache !(Maybe [(a, Rectangle)]) ![a]
deriving (Show, Read)
data Cached l a = Cached !(Cache a) !(l a)
deriving (Show, Read)
instance (Show a, Eq a, LayoutClass l a) => LayoutClass (Cached l) a where
runLayout (W.Workspace i (Cached (Cache mwrs ois) cl) ms) sr = case mwrs of
Just wrs | ois == nis -> return (wrs, Nothing)
_ -> do
(nwrs, mncl) <- runLayout (W.Workspace i cl ms) sr
return (nwrs, Just $ Cached (Cache (Just nwrs) nis) (fromMaybe cl mncl))
where nis = W.integrate' ms
handleMessage (Cached (Cache _ ois) cl) =
(fmap . fmap) (Cached $ Cache Nothing ois) . handleMessage cl
cached :: l a -> Cached l a
cached = Cached (Cache Nothing [])
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment