-Wall police, and turn on -fno-warn-orphans

This commit is contained in:
Don Stewart
2007-06-17 05:23:22 +00:00
parent dbd58faffe
commit be08dd80ec
2 changed files with 3 additions and 8 deletions

View File

@@ -1,4 +1,4 @@
{-# OPTIONS -fglasgow-exts #-} {-# OPTIONS -fno-warn-orphans -fglasgow-exts #-}
-- \^^ deriving Typeable -- \^^ deriving Typeable
-- -------------------------------------------------------------------------- -- --------------------------------------------------------------------------
-- | -- |
@@ -166,7 +166,7 @@ windows f = do
(floor (toRational sw*rw)) (floor (toRational sh*rh)) (floor (toRational sw*rw)) (floor (toRational sh*rh))
io $ restackWindows d (flt ++ io $ restackWindows d (flt ++
maybe [] (\s@(W.Stack f _ _) -> f : delete f (W.integrate s)) tiled) maybe [] (\s@(W.Stack foc _ _) -> foc : delete foc (W.integrate s)) tiled)
-- return the visible windows for this workspace: -- return the visible windows for this workspace:
return (map fst rs ++ flt) return (map fst rs ++ flt)

View File

@@ -15,7 +15,7 @@ module StackSet (
StackSet(..), Workspace(..), Screen(..), StackOrNot, Stack(..), RationalRect(..), StackSet(..), Workspace(..), Screen(..), StackOrNot, Stack(..), RationalRect(..),
-- * Construction -- * Construction
-- $construction -- $construction
new, view, new, view,
-- * Xinerama operations -- * Xinerama operations
-- $xinerama -- $xinerama
lookupWorkspace, lookupWorkspace,
@@ -105,11 +105,6 @@ import qualified Data.Map as M (Map,insert,delete,empty)
-- 'delete'. -- 'delete'.
-- --
import Prelude hiding (filter)
import Data.Maybe (listToMaybe)
import qualified Data.List as L (delete,find,genericSplitAt,filter)
import qualified Data.Map as M (Map,insert,delete,empty)
-- | -- |
-- API changes from xmonad 0.1: -- API changes from xmonad 0.1:
-- StackSet constructor arguments changed. StackSet workspace window screen -- StackSet constructor arguments changed. StackSet workspace window screen