mirror of
https://github.com/xmonad/xmonad.git
synced 2025-08-21 06:23:47 -07:00
add Read instance to Layout.
This commit is contained in:
@@ -351,14 +351,14 @@ instance Message IncMasterN
|
|||||||
|
|
||||||
-- simple fullscreen mode, just render all windows fullscreen.
|
-- simple fullscreen mode, just render all windows fullscreen.
|
||||||
-- a plea for tuple sections: map . (,sc)
|
-- a plea for tuple sections: map . (,sc)
|
||||||
data Full a = Full deriving Show
|
data Full a = Full deriving ( Show, Read )
|
||||||
instance Layout Full a where
|
instance Layout Full a where
|
||||||
doLayout Full sc (W.Stack f _ _) = return ([(f, sc)], Nothing)
|
doLayout Full sc (W.Stack f _ _) = return ([(f, sc)], Nothing)
|
||||||
modifyLayout Full _ = return Nothing -- no changes
|
modifyLayout Full _ = return Nothing -- no changes
|
||||||
--
|
--
|
||||||
-- The tiling mode of xmonad, and its operations.
|
-- The tiling mode of xmonad, and its operations.
|
||||||
--
|
--
|
||||||
data Tall a = Tall Int Rational Rational deriving Show
|
data Tall a = Tall Int Rational Rational deriving ( Show, Read )
|
||||||
instance Layout Tall a where
|
instance Layout Tall a where
|
||||||
doLayout (Tall nmaster _ frac) r =
|
doLayout (Tall nmaster _ frac) r =
|
||||||
return . (\x->(x,Nothing)) .
|
return . (\x->(x,Nothing)) .
|
||||||
@@ -375,10 +375,15 @@ mirrorRect :: Rectangle -> Rectangle
|
|||||||
mirrorRect (Rectangle rx ry rw rh) = (Rectangle ry rx rh rw)
|
mirrorRect (Rectangle rx ry rw rh) = (Rectangle ry rx rh rw)
|
||||||
|
|
||||||
-- | Mirror a layout, compute its 90 degree rotated form.
|
-- | Mirror a layout, compute its 90 degree rotated form.
|
||||||
data Mirror a = forall l. Layout l a => Mirror (l a)
|
data Mirror l a = Layout l a => Mirror (l a)
|
||||||
instance Show (Mirror a) where
|
instance Layout l a => Show (Mirror l a) where
|
||||||
show (Mirror l) = "Mirror "++show l
|
show (Mirror l) = "Mirror "++show l
|
||||||
instance Layout Mirror a where
|
instance Layout l a => Read (Mirror l a) where
|
||||||
|
readsPrec _ s = case take (length "Mirror ") s of
|
||||||
|
"Mirror " -> map (\ (l,s') -> (Mirror l,s')) $ reads $ drop (length "Mirror ") s
|
||||||
|
_ -> []
|
||||||
|
|
||||||
|
instance Layout l a => Layout (Mirror l) a where
|
||||||
doLayout (Mirror l) r s = do (wrs, ml') <- doLayout l (mirrorRect r) s
|
doLayout (Mirror l) r s = do (wrs, ml') <- doLayout l (mirrorRect r) s
|
||||||
return (map (second mirrorRect) wrs, Mirror `fmap` ml')
|
return (map (second mirrorRect) wrs, Mirror `fmap` ml')
|
||||||
modifyLayout (Mirror l) = fmap (fmap Mirror) . modifyLayout l
|
modifyLayout (Mirror l) = fmap (fmap Mirror) . modifyLayout l
|
||||||
|
@@ -134,8 +134,10 @@ atom_WM_STATE = getAtom "WM_STATE"
|
|||||||
data SomeLayout a = forall l. Layout l a => SomeLayout (l a)
|
data SomeLayout a = forall l. Layout l a => SomeLayout (l a)
|
||||||
instance Show (SomeLayout a) where
|
instance Show (SomeLayout a) where
|
||||||
show (SomeLayout l) = show l
|
show (SomeLayout l) = show l
|
||||||
|
instance Read (SomeLayout a) where
|
||||||
|
readsPrec _ _ = [] -- We can't read an existential type!!!
|
||||||
|
|
||||||
class Show (layout a) => Layout layout a where
|
class (Show (layout a), Read (layout a)) => Layout layout a where
|
||||||
doLayout :: layout a -> Rectangle -> Stack a -> X ([(a, Rectangle)], Maybe (layout a))
|
doLayout :: layout a -> Rectangle -> Stack a -> X ([(a, Rectangle)], Maybe (layout a))
|
||||||
modifyLayout :: layout a -> SomeMessage -> X (Maybe (layout a))
|
modifyLayout :: layout a -> SomeMessage -> X (Maybe (layout a))
|
||||||
|
|
||||||
|
Reference in New Issue
Block a user