mirror of
https://github.com/xmonad/xmonad.git
synced 2025-08-03 13:41:54 -07:00
Constrain layout messages to be members of a Message class
Using Typeables as the only constraint on layout messages is a bit scary, as a user can send arbitrary values to layoutMsg, whether they make sense or not: there's basically no type feedback on the values you supply to layoutMsg. Folloing Simon Marlow's dynamically extensible exceptions paper, we use an existential type, and a Message type class, to constrain valid arguments to layoutMsg to be valid members of Message. That is, a user writes some data type for messages their layout algorithm accepts: data MyLayoutEvent = Zoom | Explode | Flaming3DGlassEffect deriving (Typeable) and they then add this to the set of valid message types: instance Message MyLayoutEvent Done. We also reimplement the dynamic type check while we're here, to just directly use 'cast', rather than expose a raw fromDynamic/toDyn. With this, I'm much happier about out dynamically extensible layout event subsystem.
This commit is contained in:
@@ -16,7 +16,6 @@ module Operations where
|
||||
import Data.List
|
||||
import Data.Maybe
|
||||
import Data.Bits
|
||||
import Data.Dynamic ( Typeable, toDyn, fromDynamic )
|
||||
import qualified Data.Map as M
|
||||
|
||||
import Control.Monad.State
|
||||
@@ -73,41 +72,46 @@ clearEnterEvents = do
|
||||
-- uppermost.
|
||||
--
|
||||
switchLayout :: X ()
|
||||
switchLayout = layout (\(x, xs) -> let xs' = xs ++ [x]
|
||||
in (head xs', tail xs'))
|
||||
switchLayout = layout (\(x, xs) -> let xs' = xs ++ [x] in (head xs', tail xs'))
|
||||
|
||||
-- | Throw an (extensible) message value to the current Layout scheme,
|
||||
-- possibly modifying how we layout the windows, then refresh.
|
||||
--
|
||||
-- TODO, using Typeable for extensible stuff is a bit gunky. Check --
|
||||
-- 'extensible exceptions' paper for other ideas.
|
||||
-- TODO, this will refresh on Nothing.
|
||||
--
|
||||
-- Basically this thing specifies the basic operations that vary between
|
||||
-- layouts.
|
||||
--
|
||||
data ShrinkOrExpand = Shrink | Expand deriving (Typeable, Eq)
|
||||
|
||||
layoutMsg :: Typeable a => a -> X () -- FIXME: The below shouldn't refresh on Nothing
|
||||
layoutMsg a = layout $ \x@(l, ls) -> maybe x (flip (,) ls) (modifyLayout l (toDyn a))
|
||||
sendMessage :: Message a => a -> X ()
|
||||
sendMessage a = layout $ \x@(l, ls) -> maybe x (flip (,) ls) (modifyLayout l (SomeMessage a))
|
||||
|
||||
------------------------------------------------------------------------
|
||||
--
|
||||
-- Standard layout algorithms:
|
||||
-- Builtin layout algorithms:
|
||||
--
|
||||
-- fullscreen mode
|
||||
-- tall mode
|
||||
-- wide mode
|
||||
--
|
||||
-- The latter algorithms support the following operations:
|
||||
--
|
||||
-- Shrink
|
||||
-- Expand
|
||||
--
|
||||
|
||||
data Resize = Shrink | Expand deriving (Typeable, Show)
|
||||
instance Message Resize
|
||||
|
||||
full :: Layout
|
||||
full = Layout { doLayout = \sc ws -> [ (w,sc) | w <- ws ]
|
||||
, modifyLayout = const Nothing } -- no changes
|
||||
|
||||
tall, wide :: Rational -> Rational -> Layout
|
||||
|
||||
full = Layout { doLayout = \sc ws -> [ (w,sc) | w <- ws ]
|
||||
, modifyLayout = const Nothing }
|
||||
|
||||
wide delta frac = mirrorLayout (tall delta frac)
|
||||
|
||||
tall delta frac = Layout { doLayout = tile frac
|
||||
, modifyLayout = fmap f . fromDynamic }
|
||||
, modifyLayout = fmap handler . fromMessage }
|
||||
|
||||
where f s = tall delta ((op s) frac delta)
|
||||
op Shrink = (-) ; op Expand = (+)
|
||||
where handler s = tall delta $ (case s of
|
||||
Shrink -> (-)
|
||||
Expand -> (+)) frac delta
|
||||
|
||||
-- | Mirror a rectangle
|
||||
mirrorRect :: Rectangle -> Rectangle
|
||||
|
Reference in New Issue
Block a user