Skip to content

Instantly share code, notes, and snippets.

@lierdakil
Last active May 2, 2016 15:47
Show Gist options
  • Save lierdakil/77db93bd8252c2158a7090d3daa3c5f3 to your computer and use it in GitHub Desktop.
Save lierdakil/77db93bd8252c2158a7090d3daa3c5f3 to your computer and use it in GitHub Desktop.
{-# LANGUAGE Rank2Types, TypeOperators, ConstraintKinds, MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances, FlexibleContexts, UndecidableInstances #-}
import XMonad
import Data.Constraint
import XMonad.Layout.LayoutModifier (LayoutModifier, ModifiedLayout)
import XMonad.Layout.NoBorders
type IsLayout l a = (Read (l a), LayoutClass l a)
class CC m a where
cc :: forall l. m l a -> IsLayout l a :- IsLayout (m l) a
cc _ = Sub dict
dict :: forall l. IsLayout l a => Dict (IsLayout (m l) a)
instance CC Mirror a where dict = Dict
instance LayoutModifier m a => CC (ModifiedLayout m) a where dict = Dict
wrap :: forall m a. (CC m a)
=> (forall l. (LayoutClass l a) => l a -> m l a)
-> Layout a -> Layout a
wrap m (Layout la) = Layout (m la) \\ cc (m la)
test :: Layout Window -> IO ()
test l = xmonad' $ def{layoutHook = wrap Mirror . wrap smartBorders $ l}
where xmonad' :: XConfig Layout -> IO ()
xmonad' cf@ XConfig { layoutHook = Layout l } =
xmonad cf{ layoutHook = l }
main :: IO ()
main = test $ Layout $ Tall 1 0.03 0.5 ||| Full
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment