{-# OPTIONS_GHC -fno-warn-name-shadowing -fno-warn-unused-binds #-}
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses
, PatternGuards, DeriveDataTypeable, ExistentialQuantification
, FlexibleContexts #-}
module XMonad.Layout.ZoomRow (
ZoomRow
, zoomRow
, ZoomMessage(..)
, zoomIn
, zoomOut
, zoomReset
, zoomRowWith
, EQF(..)
, ClassEQ(..)
) where
import XMonad
import qualified XMonad.StackSet as W
import XMonad.Util.Stack
import XMonad.Layout.Decoration (fi)
import Data.Maybe (fromMaybe)
import Control.Arrow (second)
zoomRow :: (Eq a, Show a, Read a) => ZoomRow ClassEQ a
zoomRow = ZC ClassEQ emptyZ
zoomRowWith :: (EQF f a, Show (f a), Read (f a), Show a, Read a)
=> f a -> ZoomRow f a
zoomRowWith f = ZC f emptyZ
data ZoomRow f a = ZC { zoomEq :: f a
, zoomRatios :: (Zipper (Elt a))
}
deriving (Show, Read, Eq)
class EQF f a where
eq :: f a -> a -> a -> Bool
data ClassEQ a = ClassEQ
deriving (Show, Read, Eq)
instance Eq a => EQF ClassEQ a where
eq _ a b = a == b
data Elt a = E { elt :: a
, ratio :: Rational
, full :: Bool
}
deriving (Show, Read, Eq)
getRatio :: Elt a -> (a, Rational)
getRatio (E a r _) = (a,r)
lookupBy :: (a -> a -> Bool) -> a -> [Elt a] -> Maybe (Elt a)
lookupBy _ _ [] = Nothing
lookupBy f a (E a' r b : _) | f a a' = Just $ E a r b
lookupBy f a (_:es) = lookupBy f a es
setFocus :: Zipper a -> a -> Zipper a
setFocus Nothing a = Just $ W.Stack a [] []
setFocus (Just s) a = Just s { W.focus = a }
data ZoomMessage = Zoom Rational
| ZoomTo Rational
| ZoomFull Bool
| ZoomFullToggle
deriving (Typeable, Show)
instance Message ZoomMessage
zoomIn :: ZoomMessage
zoomIn = Zoom 1.5
zoomOut :: ZoomMessage
zoomOut = Zoom $ 2/3
zoomReset :: ZoomMessage
zoomReset = ZoomTo 1
instance (EQF f a, Show a, Read a, Show (f a), Read (f a))
=> LayoutClass (ZoomRow f) a where
description (ZC _ Nothing) = "ZoomRow"
description (ZC _ (Just s)) = "ZoomRow" ++ if full $ W.focus s
then " (Max)"
else ""
emptyLayout (ZC _ Nothing) _ = return ([], Nothing)
emptyLayout (ZC f _) _ = return ([], Just $ ZC f Nothing)
doLayout (ZC f zelts) r@(Rectangle _ _ w _) s
= let elts = W.integrate' zelts
zelts' = mapZ_ (\a -> fromMaybe (E a 1 False)
$ lookupBy (eq f) a elts) $ Just s
elts' = W.integrate' zelts'
maybeL' = if zelts `noChange` zelts'
then Nothing
else Just $ ZC f zelts'
total = sum $ map ratio elts'
widths = map (second ((* fi w) . (/total)) . getRatio) elts'
in case getFocusZ zelts' of
Just (E a _ True) -> return ([(a, r)], maybeL')
_ -> return (makeRects r widths, maybeL')
where makeRects :: Rectangle -> [(a, Rational)] -> [(a, Rectangle)]
makeRects r pairs = let as = map fst pairs
widths = map snd pairs
discreteWidths = snd $ foldr discretize (0, []) widths
rectangles = snd $ foldr makeRect (r, []) discreteWidths
in zip as rectangles
makeRect :: Dimension -> (Rectangle, [Rectangle]) -> (Rectangle, [Rectangle])
makeRect w (Rectangle x y w0 h, rs) = ( Rectangle x y (w0-w) h
, Rectangle (x+fi w0-fi w) y w h : rs )
discretize :: Rational -> (Rational, [Dimension]) -> (Rational, [Dimension])
discretize r (carry, ds) = let (d, carry') = properFraction $ carry+r
in (carry', d:ds)
noChange z1 z2 = toTags z1 `helper` toTags z2
where helper [] [] = True
helper (Right a:as) (Right b:bs) = a `sameAs` b && as `helper` bs
helper (Left a:as) (Left b:bs) = a `sameAs` b && as `helper` bs
helper _ _ = False
E a1 r1 b1 `sameAs` E a2 r2 b2 = (eq f a1 a2) && (r1 == r2) && (b1 == b2)
pureMessage (ZC f zelts) sm | Just (ZoomFull False) <- fromMessage sm
, Just (E a r True) <- getFocusZ zelts
= Just $ ZC f $ setFocus zelts $ E a r False
pureMessage (ZC f zelts) sm | Just (ZoomFull True) <- fromMessage sm
, Just (E a r False) <- getFocusZ zelts
= Just $ ZC f $ setFocus zelts $ E a r True
pureMessage (ZC f zelts) sm | Just (E a r b) <- getFocusZ zelts
= case fromMessage sm of
Just (Zoom r') -> Just $ ZC f $ setFocus zelts $ E a (r*r') b
Just (ZoomTo r') -> Just $ ZC f $ setFocus zelts $ E a r' b
Just ZoomFullToggle -> pureMessage (ZC f zelts)
$ SomeMessage $ ZoomFull $ not b
_ -> Nothing
pureMessage _ _ = Nothing