mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-08-01 04:31:52 -07:00
Fix -Wnoncanonical-monoid-instances warnings
This commit is contained in:
@@ -138,13 +138,12 @@ import Graphics.X11.Xlib.Extras (Event(..))
|
||||
-- to make it obay the monoid laws
|
||||
data Opacity = Opacity Rational | OEmpty
|
||||
|
||||
instance Semigroup Opacity where
|
||||
r <> OEmpty = r
|
||||
_ <> r = r
|
||||
|
||||
instance Monoid Opacity where
|
||||
mempty = OEmpty
|
||||
r `mappend` OEmpty = r
|
||||
_ `mappend` r = r
|
||||
|
||||
instance Semigroup Opacity where
|
||||
(<>) = mappend
|
||||
|
||||
-- | A FadeHook is similar to a ManageHook, but records window opacity.
|
||||
type FadeHook = Query Opacity
|
||||
|
@@ -373,7 +373,6 @@ instance Semigroup a => Semigroup (FocusQuery a) where
|
||||
(<>) = liftM2 (<>)
|
||||
instance Monoid a => Monoid (FocusQuery a) where
|
||||
mempty = return mempty
|
||||
mappend = (<>)
|
||||
|
||||
runFocusQuery :: FocusQuery a -> Focus -> Query a
|
||||
runFocusQuery (FocusQuery m) = runReaderT m
|
||||
|
@@ -74,13 +74,12 @@ data Wallpaper = WallpaperFix FilePath -- ^ Single, fixed wallpaper
|
||||
newtype WallpaperList = WallpaperList [(WorkspaceId, Wallpaper)]
|
||||
deriving (Show,Read)
|
||||
|
||||
instance Monoid WallpaperList where
|
||||
mempty = WallpaperList []
|
||||
mappend (WallpaperList w1) (WallpaperList w2) =
|
||||
instance Semigroup WallpaperList where
|
||||
WallpaperList w1 <> WallpaperList w2 =
|
||||
WallpaperList $ M.toList $ M.fromList w2 `M.union` M.fromList w1
|
||||
|
||||
instance Semigroup WallpaperList where
|
||||
(<>) = mappend
|
||||
instance Monoid WallpaperList where
|
||||
mempty = WallpaperList []
|
||||
|
||||
-- | Complete wallpaper configuration passed to the hook
|
||||
data WallpaperConf = WallpaperConf {
|
||||
|
Reference in New Issue
Block a user