From 4866f2e367dfcf22a9591231ba40948826a1b438 Mon Sep 17 00:00:00 2001 From: Spencer Janssen Date: Thu, 1 Nov 2007 21:10:59 +0100 Subject: Hierarchify darcs-hash:20071101201059-a5988-fc1f1262bec1b69e13ba18ae7cefeafc8c4471d4.gz --- Maximize.hs | 73 ------------------------------------------------------------- 1 file changed, 73 deletions(-) delete mode 100644 Maximize.hs (limited to 'Maximize.hs') diff --git a/Maximize.hs b/Maximize.hs deleted file mode 100644 index 2138917..0000000 --- a/Maximize.hs +++ /dev/null @@ -1,73 +0,0 @@ -{-# OPTIONS_GHC -fglasgow-exts #-} -- For deriving Data/Typeable -{-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses, TypeSynonymInstances #-} - ------------------------------------------------------------------------------ --- | --- Module : XMonadContrib.Maximize --- Copyright : (c) 2007 James Webb --- License : BSD3-style (see LICENSE) --- --- Maintainer : xmonad#jwebb,sygneca,com --- Stability : unstable --- Portability : unportable --- --- Temporarily yanks the focused window out of the layout to mostly fill --- the screen. --- ------------------------------------------------------------------------------ - -module XMonadContrib.Maximize ( - -- * Usage - -- $usage - maximize, - maximizeRestore - ) where - -import Graphics.X11.Xlib -import XMonad -import XMonadContrib.LayoutModifier -import Data.List ( partition ) - --- $usage --- You can use this module with the following in your Config.hs file: --- --- > import XMonadContrib.Maximize --- --- > layouts = ... --- > , Layout $ maximize $ tiled ... --- > ... --- --- > keys = ... --- > , ((modMask, xK_backslash), withFocused (sendMessage . maximizeRestore)) --- > ... - --- %import XMonadContrib.Maximize --- %layout , Layout $ maximize $ tiled - -data Maximize a = Maximize (Maybe Window) deriving ( Read, Show ) -maximize :: LayoutClass l Window => l Window -> ModifiedLayout Maximize l Window -maximize = ModifiedLayout $ Maximize Nothing - -data MaximizeRestore = MaximizeRestore Window deriving ( Typeable, Eq ) -instance Message MaximizeRestore -maximizeRestore :: Window -> MaximizeRestore -maximizeRestore = MaximizeRestore - -instance LayoutModifier Maximize Window where - modifierDescription (Maximize _) = "Maximize" - redoLayout (Maximize mw) rect _ wrs = case mw of - Just win -> - return (maxed ++ rest, Nothing) - where - maxed = map (\(w, _) -> (w, maxRect)) toMax - (toMax, rest) = partition (\(w, _) -> w == win) wrs - maxRect = Rectangle (rect_x rect + 50) (rect_y rect + 50) - (rect_width rect - 100) (rect_height rect - 100) - Nothing -> return (wrs, Nothing) - handleMess (Maximize mw) m = case fromMessage m of - Just (MaximizeRestore w) -> case mw of - Just _ -> return $ Just $ Maximize Nothing - Nothing -> return $ Just $ Maximize $ Just w - _ -> return Nothing - --- vim: sw=4:et -- cgit v1.2.3