diff --git a/XMonad/Actions/GroupNavigation.hs b/XMonad/Actions/GroupNavigation.hs index 63acc990..37508a08 100644 --- a/XMonad/Actions/GroupNavigation.hs +++ b/XMonad/Actions/GroupNavigation.hs @@ -127,7 +127,7 @@ focusNextMatchOrDo qry act = findM (runQuery qry) -- Returns the list of windows ordered by workspace as specified in -- ~/.xmonad/xmonad.hs orderedWindowList :: Direction -> X (Seq Window) -orderedWindowList History = liftM (\(HistoryDB w ws) -> maybe ws (ws |>) w) XS.get +orderedWindowList History = fmap (\(HistoryDB w ws) -> maybe ws (ws |>) w) XS.get orderedWindowList dir = withWindowSet $ \ss -> do wsids <- asks (Seq.fromList . workspaces . config) let wspcs = orderedWorkspaceList ss wsids diff --git a/XMonad/Actions/RandomBackground.hs b/XMonad/Actions/RandomBackground.hs index c0bbe564..7e9ff593 100644 --- a/XMonad/Actions/RandomBackground.hs +++ b/XMonad/Actions/RandomBackground.hs @@ -55,7 +55,7 @@ randPermutation xs g = swap $ zip (randoms g) xs -- | @randomBg'@ produces a random hex number in the form @'#xxyyzz'@ randomBg' :: (MonadIO m) => RandomColor -> m String -randomBg' (RGB l h) = io $ liftM (toHex . take 3 . randomRs (l,h)) newStdGen +randomBg' (RGB l h) = io $ fmap (toHex . take 3 . randomRs (l,h)) newStdGen randomBg' (HSV s v) = io $ do g <- newStdGen let x = (^(2::Int)) $ fst $ randomR (0,sqrt $ pi / 3) g diff --git a/XMonad/Actions/WorkspaceCursors.hs b/XMonad/Actions/WorkspaceCursors.hs index a89360d7..9a42c99d 100644 --- a/XMonad/Actions/WorkspaceCursors.hs +++ b/XMonad/Actions/WorkspaceCursors.hs @@ -162,7 +162,7 @@ focusDepth (End _) = 0 descend :: Monad m =>(W.Stack (Cursors a) -> m (W.Stack (Cursors a)))-> Int-> Cursors a-> m (Cursors a) descend f 1 (Cons x) = Cons <$> f x -descend f n (Cons x) | n > 1 = liftM Cons $ descend f (pred n) `onFocus` x +descend f n (Cons x) | n > 1 = fmap Cons $ descend f (pred n) `onFocus` x descend _ _ x = return x onFocus :: (Monad m) => (a1 -> m a1) -> W.Stack a1 -> m (W.Stack a1) diff --git a/XMonad/Layout/IndependentScreens.hs b/XMonad/Layout/IndependentScreens.hs index 656cfd1a..d88c7672 100644 --- a/XMonad/Layout/IndependentScreens.hs +++ b/XMonad/Layout/IndependentScreens.hs @@ -121,7 +121,7 @@ onCurrentScreen f vws = screen . current >>= f . flip marshall vws -- > } -- countScreens :: (MonadIO m, Integral i) => m i -countScreens = liftM genericLength . liftIO $ openDisplay "" >>= liftA2 (<*) getScreenInfo closeDisplay +countScreens = fmap genericLength . liftIO $ openDisplay "" >>= liftA2 (<*) getScreenInfo closeDisplay -- | This turns a naive pretty-printer into one that is aware of the -- independent screens. That is, you can write your pretty printer to behave diff --git a/XMonad/Layout/Master.hs b/XMonad/Layout/Master.hs index 9a1e80b1..d51e4049 100644 --- a/XMonad/Layout/Master.hs +++ b/XMonad/Layout/Master.hs @@ -90,7 +90,7 @@ data FixMaster a = FixMaster (AddMaster a) deriving (Show, Read) instance LayoutModifier FixMaster Window where modifyLayout (FixMaster (AddMaster k d f)) = applyMaster True k d f modifierDescription (FixMaster a) = "Fix" ++ modifierDescription a - pureMess (FixMaster a) m = liftM FixMaster (pureMess a m) + pureMess (FixMaster a) m = fmap FixMaster (pureMess a m) fixMastered :: (LayoutClass l a) => Rational -- ^ @delta@, the ratio of the screen to resize by diff --git a/XMonad/Prompt.hs b/XMonad/Prompt.hs index 95c935e1..f8b60525 100644 --- a/XMonad/Prompt.hs +++ b/XMonad/Prompt.hs @@ -1204,7 +1204,7 @@ pasteString = pasteString' id -- | A variant of 'pasteString' which allows modifying the X selection before -- pasting. pasteString' :: (String -> String) -> XP () -pasteString' f = join $ io $ liftM (insertString . f) getSelection +pasteString' f = join $ io $ fmap (insertString . f) getSelection -- | Remove a character at the cursor position deleteString :: Direction1D -> XP () diff --git a/XMonad/Prompt/AppendFile.hs b/XMonad/Prompt/AppendFile.hs index 7da49b8e..da3ca402 100644 --- a/XMonad/Prompt/AppendFile.hs +++ b/XMonad/Prompt/AppendFile.hs @@ -60,7 +60,7 @@ import Control.Exception.Extensible (bracket) -- before saving into the file. Previous example with date can be rewritten as: -- -- > , ((modm .|. controlMask, xK_n), do --- > date <- io $ liftM (formatTime defaultTimeLocale "[%Y-%m-%d %H:%M] ") getZonedTime +-- > date <- io $ fmap (formatTime defaultTimeLocale "[%Y-%m-%d %H:%M] ") getZonedTime -- > appendFilePrompt' def (date ++) $ "/home/me/NOTES" -- > ) -- diff --git a/XMonad/Prompt/DirExec.hs b/XMonad/Prompt/DirExec.hs index 6178679c..9f415198 100644 --- a/XMonad/Prompt/DirExec.hs +++ b/XMonad/Prompt/DirExec.hs @@ -103,5 +103,5 @@ getDirectoryExecutables path = filterM (\x -> let x' = path ++ x in liftA2 (&&) (doesFileExist x') - (liftM executable (getPermissions x')))) + (fmap executable (getPermissions x')))) `E.catch` econst [] diff --git a/XMonad/Prompt/RunOrRaise.hs b/XMonad/Prompt/RunOrRaise.hs index b7d67623..624c6526 100644 --- a/XMonad/Prompt/RunOrRaise.hs +++ b/XMonad/Prompt/RunOrRaise.hs @@ -76,7 +76,7 @@ pidof x = io $ (runProcessWithInput "pidof" [x] [] >>= readIO) `E.catch` econst pid :: Query Int pid = ask >>= (\w -> liftX $ withDisplay $ \d -> getPID d w) where getPID d w = getAtom "_NET_WM_PID" >>= \a -> io $ - liftM getPID' (getWindowProperty32 d a w) + fmap getPID' (getWindowProperty32 d a w) getPID' (Just (x:_)) = fromIntegral x getPID' (Just []) = -1 getPID' (Nothing) = -1 diff --git a/XMonad/Util/Dmenu.hs b/XMonad/Util/Dmenu.hs index 78c49425..ece99bec 100644 --- a/XMonad/Util/Dmenu.hs +++ b/XMonad/Util/Dmenu.hs @@ -58,7 +58,7 @@ menu menuCmd opts = menuArgs menuCmd [] opts -- | Like 'menu' but also takes a list of command line arguments. menuArgs :: MonadIO m => String -> [String] -> [String] -> m String -menuArgs menuCmd args opts = liftM (filter (/='\n')) $ +menuArgs menuCmd args opts = fmap (filter (/='\n')) $ runProcessWithInput menuCmd args (unlines opts) -- | Like 'dmenuMap' but also takes the command to run. diff --git a/XMonad/Util/XSelection.hs b/XMonad/Util/XSelection.hs index f2f3a881..3b52778a 100644 --- a/XMonad/Util/XSelection.hs +++ b/XMonad/Util/XSelection.hs @@ -85,8 +85,8 @@ getSelection = io $ do details on the advantages and disadvantages of using safeSpawn. -} promptSelection, safePromptSelection, unsafePromptSelection :: String -> X () promptSelection = unsafePromptSelection -safePromptSelection app = join $ io $ liftM (safeSpawn app . return) getSelection -unsafePromptSelection app = join $ io $ liftM unsafeSpawn $ fmap (\x -> app ++ " " ++ x) getSelection +safePromptSelection app = join $ io $ fmap (safeSpawn app . return) getSelection +unsafePromptSelection app = join $ io $ fmap unsafeSpawn $ fmap (\x -> app ++ " " ++ x) getSelection {- | A wrapper around 'promptSelection' and its safe variant. They take two parameters, the first is a function that transforms strings, and the second is the application to run. @@ -94,5 +94,5 @@ unsafePromptSelection app = join $ io $ liftM unsafeSpawn $ fmap (\x -> app ++ " One example is to wrap code, such as a command line action copied out of the browser to be run as @"sudo" ++ cmd@ or @"su - -c \""++ cmd ++"\""@. -} transformPromptSelection, transformSafePromptSelection :: (String -> String) -> String -> X () -transformPromptSelection f app = join $ io $ liftM (safeSpawn app . return) (fmap f getSelection) -transformSafePromptSelection f app = join $ io $ liftM unsafeSpawn $ fmap (\x -> app ++ " " ++ x) (fmap f getSelection) +transformPromptSelection f app = join $ io $ fmap (safeSpawn app . return) (fmap f getSelection) +transformSafePromptSelection f app = join $ io $ fmap unsafeSpawn $ fmap (\x -> app ++ " " ++ x) (fmap f getSelection) diff --git a/tests/genMain.hs b/tests/genMain.hs index 129b0102..a64687c5 100644 --- a/tests/genMain.hs +++ b/tests/genMain.hs @@ -56,7 +56,7 @@ genModule imports props = vcat [header,imports', main ] hang (text "let props = ") 8 (brackets $ foldr1 (\x xs -> x <> comma $$ xs) props') $$ - text "(results, passed) <- liftM unzip $ \ + text "(results, passed) <- fmap unzip $ \ \mapM (\\(s,a) -> printf \"%-40s: \" s >> a n) props" $$ text "printf \"Passed %d tests!\\n\" (sum passed)"