xmonad-contrib-0.17.0.9: Community-maintained extensions for xmonad
Copyright(C) 2007 Spencer Janssen Andrea Rossato glasser@mit.edu
2022 Tony Zorman
LicenseBSD-style (see LICENSE)
MaintainerTony Zorman <soliditsallgood@mailbox.org>
Stabilityunstable
Portabilityunportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

XMonad.Util.Run

Description

This module provides several commands to run an external process. Additionally, it provides an abstraction—particularly geared towards programs like terminals or Emacs—to specify these processes from XMonad in a compositional way.

Originally, this module was composed of functions formerly defined in XMonad.Util.Dmenu (by Spencer Janssen), XMonad.Util.Dzen (by glasser@mit.edu) and XMonad.Util.RunInXTerm (by Andrea Rossato).

Synopsis

Usage

You can use this module by importing it in your xmonad.hs

import XMonad.Util.Run

It then all depends on what you want to do:

runProcessWithInput :: MonadIO m => FilePath -> [String] -> String -> m String Source #

Returns the output.

runProcessWithInputAndWait :: MonadIO m => FilePath -> [String] -> String -> Int -> m () Source #

Wait is in μ (microseconds)

safeSpawn :: MonadIO m => FilePath -> [String] -> m () Source #

safeSpawn bypasses spawn, because spawn passes strings to /bin/sh to be interpreted as shell commands. This is often what one wants, but in many cases the passed string will contain shell metacharacters which one does not want interpreted as such (URLs particularly often have shell metacharacters like '&' in them). In this case, it is more useful to specify a file or program to be run and a string to give it as an argument so as to bypass the shell and be certain the program will receive the string as you typed it.

Examples:

, ((modm, xK_Print), unsafeSpawn "import -window root $HOME/xwd-$(date +%s)$$.png")
, ((modm, xK_d    ), safeSpawn "firefox" [])

Note that the unsafeSpawn example must be unsafe and not safe because it makes use of shell interpretation by relying on $HOME and interpolation, whereas the safeSpawn example can be safe because Firefox doesn't need any arguments if it is just being started.

safeSpawnProg :: MonadIO m => FilePath -> m () Source #

Simplified safeSpawn; only takes a program (and no arguments):

, ((modm, xK_d    ), safeSpawnProg "firefox")

unsafeSpawn :: MonadIO m => String -> m () Source #

An alias for spawn; the name emphasizes that one is calling out to a Turing-complete interpreter which may do things one dislikes; for details, see safeSpawn.

runInTerm :: String -> String -> X () Source #

Open a terminal emulator. The terminal emulator is specified in the default configuration as xterm by default. It is then asked to pass the shell a command with certain options. This is unsafe in the sense of unsafeSpawn

safeRunInTerm :: String -> String -> X () Source #

Run a given program in the preferred terminal emulator; see runInTerm. This makes use of safeSpawn.

seconds :: Rational -> Int Source #

Multiplies by ONE MILLION, for functions that take microseconds.

Use like:

(5.5 `seconds`)

In GHC 7 and later, you must either enable the PostfixOperators extension (by adding

{-# LANGUAGE PostfixOperators #-}

to the top of your file) or use seconds in prefix form:

seconds 5.5

spawnPipe :: MonadIO m => String -> m Handle Source #

Launch an external application through the system shell and return a Handle to its standard input. Note that the Handle is a text Handle using the current locale encoding.

spawnPipeWithUtf8Encoding :: MonadIO m => String -> m Handle Source #

Same as spawnPipe, but forces the UTF-8 encoding regardless of locale.

spawnPipeWithNoEncoding :: MonadIO m => String -> m Handle Source #

Same as spawnPipe, but forces the char8 encoding, so unicode strings need encodeString. Should never be needed, but some X functions return already encoded Strings, so it may possibly be useful for someone.

Compositionally Spawning Processes

To use the provided EDSL, you must first add the spawnExternalProcess combinator to your xmonad configuration, like so:

main = xmonad $ … $ spawnExternalProcess def $ … $ def

See ProcessConfig for a list of all default configuration options, in case you'd like to change them—especially if you want to make use of the Emacs integration.

After that, the real fun begins! The format for spawning these processes is always the same: a call to proc, its argument being a bunch of function calls, separated by the pipe operator (>->). You can just bind the resulting function to a key; no additional plumbing required. For example, using XMonad.Util.EZConfig syntax and with terminal = "alacritty" in you XMonad configuration, spawning a ghci session with a special class name, "calculator", would look like

("M-y", proc $ inTerm >-> setXClass "calculator" >-> execute "ghci")

which would translate, more or less, to /usr/bin/sh -c "alacritty --class calculator -e ghci". The usefulness of this notation becomes apparent with more complicated examples:

proc $ inEmacs
   >-> withEmacsLibs [OwnFile "mailboxes"]
   >-> execute (elispFun "notmuch")
   >-> setFrameName "mail"

This is equivalent to spawning

emacs -l /home/slot/.config/emacs/lisp/mailboxes.el
      -e '(notmuch)'
      -F '(quote (name . "mail"))'

Notice how we did not have to specify the whole path to mailboxes.el, since we had set the correct emacsLispDir upon starting xmonad. This becomes especially relevant when running Emacs in batch mode, where one has to include [M,Non-GNU]ELPA packages in the call, whose exact names may change at any time. Then the following

do url <- getSelection  -- from XMonad.Util.XSelection
   proc $ inEmacs
      >-> withEmacsLibs [ElpaLib "dash", ElpaLib "s", OwnFile "arXiv-citation"]
      >-> asBatch
      >-> execute (elispFun $ "arXiv-citation" <> asString url)

becomes

emacs -L /home/slot/.config/emacs/elpa/dash-20220417.2250
      -L /home/slot/.config/emacs/elpa/s-20210616.619
      -l /home/slot/.config/emacs/lisp/arXiv-citation.el
      --batch
      -e '(arXiv-citation "<url-in-the-primary-selection>")'

which would be quite bothersome to type indeed!

Configuration and Running

data ProcessConfig Source #

Additional information that might be useful when spawning external programs.

Constructors

ProcessConfig 

Fields

  • editor :: !String

    Default editor. Defaults to "emacsclient -c -a ''".

  • emacsLispDir :: !FilePath

    Directory for your custom Emacs lisp files. Probably user-emacs-directory or user-emacs-directory/lisp. Defaults to "~/.config/emacs/lisp/"

  • emacsElpaDir :: !FilePath

    Directory for all packages from [M,Non-GNU]ELPA; probably user-emacs-directory/elpa. Defaults to "~/.config/emacs/elpa".

  • emacs :: !String

    Standalone Emacs executable; this should not be emacsclient since, for example, the client does not support --batch mode. Defaults to "emacs".

Instances

Instances details
Default ProcessConfig Source # 
Instance details

Defined in XMonad.Util.Run

Methods

def :: ProcessConfig #

type Input = ShowS Source #

Convenient type alias.

spawnExternalProcess :: ProcessConfig -> XConfig l -> XConfig l Source #

Given a ProcessConfig, remember it for spawning external processes later on.

proc :: X Input -> X () Source #

Spawn a completed input.

getInput :: X Input -> X String Source #

Get the completed input string.

Programs

termInDir :: X Input Source #

Spawn the terminal in some directory; it must support the --working-directory option.

inProgram :: String -> X Input Source #

Use the given program.

General Combinators

(>->) :: X Input -> X Input -> X Input infixr 3 Source #

Combine inputs together.

(>-$) :: X Input -> X String -> X Input infixr 3 Source #

Combine an input with an ordinary string.

inWorkingDir :: X Input Source #

Spawn thing in the current working directory. thing must support a --working-directory option.

execute :: String -> X Input Source #

Execute the argument. Current thing must support a -e option. For programs such as Emacs, eval may be the safer option; while emacsclient supports -e, the emacs executable itself does not.

eval :: String -> X Input Source #

Eval(uate) the argument. Current thing must support a --eval option.

setXClass :: String -> X Input Source #

Set the appropriate X class for a window. This will more often than not actually be the instance name.

asString :: String -> String Source #

Treat an argument as a string; i.e., wrap it with quotes.

>>> asString "string"
" \"string\" "

Emacs Integration

data EmacsLib Source #

An Emacs library.

Constructors

OwnFile !String

A file from emacsLispDir.

ElpaLib !String

A directory in emacsElpaDir.

Special !String

Special files; these will not be looked up somewhere, but forwarded verbatim (as a path).

setFrameName :: String -> X Input Source #

Set a frame name for the emacsclient.

Note that this uses the -F option to set the frame parameters alist, which the emacs executable does not support.

withEmacsLibs :: [EmacsLib] -> X Input Source #

Load some Emacs libraries. This is useful when executing scripts in batch mode.

elispFun :: String -> String Source #

Transform the given input into an elisp function; i.e., surround it with parentheses.

>>> elispFun "arxiv-citation URL"
" '( arxiv-citation URL )' "

asBatch :: X Input Source #

Tell Emacs to enable batch-mode.

require :: String -> String Source #

Require a package.

>>> require "arxiv-citation"
"(require (quote arxiv-citation))"

progn :: [String] -> String Source #

Wrap the given commands in a progn and also escape it by wrapping it inside single quotes. The given commands need not be wrapped in parentheses, this will be done by the function. For example:

>>> progn [require "this-lib", "function-from-this-lib arg", "(other-function arg2)"]
" '( progn (require (quote this-lib)) (function-from-this-lib arg) (other-function arg2) )' "

quote :: String -> String Source #

Quote a symbol.

>>> quote "new-process"
"(quote new-process)"

Re-exports

hPutStr :: Handle -> String -> IO () #

Computation hPutStr hdl s writes the string s to the file or channel managed by hdl.

This operation may fail with:

hPutStrLn :: Handle -> String -> IO () #

The same as hPutStr, but adds a newline character.