summaryrefslogtreecommitdiffstats
path: root/src/XMonad/Local/Actions.hs
blob: aca23af4cdeff9dbf61cc685dcf4387e92272c7e (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
{-# LANGUAGE DoAndIfThenElse #-}
{-# LANGUAGE UnicodeSyntax   #-}

module XMonad.Local.Actions where

import           Control.Monad
import           Data.Maybe
import           System.Posix.Directory
import           System.Posix.Env
import           System.Posix.Signals         (Signal, signalProcess)

import           XMonad
import qualified XMonad.Actions.TopicSpace    as TS
import qualified XMonad.Util.Paste            as Paste
import qualified XMonad.Util.WindowProperties as WP

-- local modules **************************************************************
import qualified XMonad.Local.Config          as Local
import qualified XMonad.Local.Prompt          as Local
import qualified XMonad.Local.Util            as Local

-- launch applications ********************************************************
spawnExplorer ∷ X ()
spawnExplorer = do
    cwd <- liftIO getWorkingDirectory
    pth <- liftIO $ getEnvDefault "HOME" cwd
    spawnExplorerIn pth

spawnExplorerIn ∷ String → X ()
spawnExplorerIn dir = spawn $ Local.explorer ++ " --no-desktop --browser " ++ dir

spawnShell ∷ Maybe String → X()
spawnShell = spawnShellIn ""

spawnShellIn ∷ TS.Dir → Maybe String → X()
spawnShellIn dir command = do
    t <- asks (terminal . config)
    spawn $ cmd' t
  where
    run (Just c) = " " ++ c
    run Nothing  = ""

    cmd' t | dir == "" = t ++ run command
           | otherwise = "cd " ++ dir ++ " && " ++ t ++ run command

spawnTmux ∷ String → X()
spawnTmux project = spawnShell $ Just ("tmux -c 'tmuxinator " ++ project ++ "'")

killWindowPID ∷ Signal → Window → X()
killWindowPID s w = do
    pid <- WP.getProp32s "_NET_WM_PID" w
    when (isJust pid) (liftIO $ mapM_ (signalProcess s . fromIntegral) (fromJust pid))

signalCurrentWindow ∷ Signal → X()
signalCurrentWindow s = withFocused (killWindowPID s)

mateRun ∷ X ()
mateRun = withDisplay $ \dpy -> do
    rw <- asks theRoot
    mate_panel <- getAtom "_MATE_PANEL_ACTION"
    panel_run  <- getAtom "_MATE_PANEL_ACTION_RUN_DIALOG"

    io $ allocaXEvent $ \e -> do
        setEventType e clientMessage
        setClientMessageEvent e rw mate_panel 32 panel_run 0
        sendEvent dpy rw False structureNotifyMask e
        sync dpy False

clipboardManager ∷ String
clipboardManager = "/usr/bin/clipit"

getClipboardText ∷ X (Maybe String)
getClipboardText = catchX
    (Local.runProcessAndLogError clipboardManager ["-c"] "")
    (io $ return Nothing)

saveTextToClipboard ∷ String → X ()
saveTextToClipboard text = catchX
    (void (Local.runProcessAndLogError clipboardManager [] text))
    (io $ return ())

getAndPasteDigraph ∷ X ()
getAndPasteDigraph = do
    dg <- Local.digraphPrompt
    case dg of
        Just text@(_:_) -> do
            saveTextToClipboard text
            Paste.pasteChar controlMask 'V'
        _               -> io $ return ()

-- | Turn the current entry in clipboard into plain text and paste it to the
-- current window using Ctrl+v shortcut.
pastePlainTextFromClipboard ∷ X ()
pastePlainTextFromClipboard = do
    t <- getClipboardText
    case t of
        Just text@(_:_) -> do
            saveTextToClipboard text
            Paste.pasteChar controlMask 'V'
        _               -> io $ return ()