aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Prompt/RunOrRaise.hs
diff options
context:
space:
mode:
authorsean.escriva <sean.escriva@gmail.com>2009-09-28 22:44:43 +0200
committersean.escriva <sean.escriva@gmail.com>2009-09-28 22:44:43 +0200
commitc11a6e9d11b994cc23aa096ff85c31c7a881283b (patch)
tree4de75600dd9412ed6a5f9ece873cbc0e7dcdf478 /XMonad/Prompt/RunOrRaise.hs
parenta343d09be11a512c48611b2abbb9d270ff71e75e (diff)
downloadXMonadContrib-c11a6e9d11b994cc23aa096ff85c31c7a881283b.tar.gz
XMonadContrib-c11a6e9d11b994cc23aa096ff85c31c7a881283b.tar.xz
XMonadContrib-c11a6e9d11b994cc23aa096ff85c31c7a881283b.zip
minor hlint cleanup of Prompt and XMonad.Prompt.* sub-modules
Ignore-this: 25e71f59bdcc5bf94c2d6f476833216b darcs-hash:20090928204443-29414-d1844586f2955c8b76d971b20d6e2b6c1ea91d4d.gz
Diffstat (limited to 'XMonad/Prompt/RunOrRaise.hs')
-rw-r--r--XMonad/Prompt/RunOrRaise.hs12
1 files changed, 6 insertions, 6 deletions
diff --git a/XMonad/Prompt/RunOrRaise.hs b/XMonad/Prompt/RunOrRaise.hs
index 3fffe74..bfe68b8 100644
--- a/XMonad/Prompt/RunOrRaise.hs
+++ b/XMonad/Prompt/RunOrRaise.hs
@@ -25,7 +25,7 @@ import XMonad.Prompt.Shell
import XMonad.Actions.WindowGo (runOrRaise)
import XMonad.Util.Run (runProcessWithInput)
-import Control.Monad (liftM2)
+import Control.Monad (liftM, liftM2)
import Data.Maybe
import System.Directory (doesDirectoryExist, doesFileExist, executable, getPermissions)
@@ -47,15 +47,15 @@ instance XPrompt RunOrRaisePrompt where
showXPrompt RRP = "Run or Raise: "
runOrRaisePrompt :: XPConfig -> X ()
-runOrRaisePrompt c = do cmds <- io $ getCommands
+runOrRaisePrompt c = do cmds <- io getCommands
mkXPrompt RRP c (getShellCompl cmds) open
open :: String -> X ()
-open path = (io $ isNormalFile path) >>= \b ->
+open path = io (isNormalFile path) >>= \b ->
if b
then spawn $ "xdg-open \"" ++ path ++ "\""
else uncurry runOrRaise . getTarget $ path
where
- isNormalFile f = exists f >>= \e -> if e then (notExecutable f) else return False
+ isNormalFile f = exists f >>= \e -> if e then notExecutable f else return False
exists f = fmap or $ sequence [doesFileExist f,doesDirectoryExist f]
notExecutable = fmap (not . executable) . getPermissions
getTarget x = (x,isApp x)
@@ -66,12 +66,12 @@ isApp "thunderbird" = className =? "Thunderbird-bin" <||> className =? "Thunderb
isApp x = liftM2 (==) pid $ pidof x
pidof :: String -> Query Int
-pidof x = io $ (runProcessWithInput "pidof" [x] [] >>= readIO) `catch` (\_ -> return $ 0)
+pidof x = io $ (runProcessWithInput "pidof" [x] [] >>= readIO) `catch` (\_ -> return 0)
pid :: Query Int
pid = ask >>= (\w -> liftX $ withDisplay $ \d -> getPID d w)
where getPID d w = getAtom "_NET_WM_PID" >>= \a -> io $
- getWindowProperty32 d a w >>= return . getPID'
+ liftM getPID' (getWindowProperty32 d a w)
getPID' (Just (x:_)) = fromIntegral x
getPID' (Just []) = -1
getPID' (Nothing) = -1