Files
xmonad-contrib/XMonad/Prompt/Email.hs
Tony Zorman 3d65a6bf72 Refer to the tutorial instead of X.D.Extending more often
Essentially, whenever the tutorial actually has decent material on the
subject matter.  The replacement is roughly done as follows:

  - logHook → tutorial
  - keybindings → tutorial, as this is thoroughly covered
  - manageHook → tutorial + X.D.Extending, as the manageHook stuff the
    tutorial talks about is a little bit of an afterthought.
  - X.D.Extending (on its own) → tutorial + X.D.Extending
  - layoutHook → tutorial + X.D.Extending, as the tutorial, while
    talking about layouts, doesn't necessarily have a huge focus there.
  - mouse bindings → leave this alone, as the tutorial does not at all
    talk about them.
2022-10-21 09:17:43 +02:00

65 lines
2.2 KiB
Haskell

-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Prompt.Email
-- Description : A prompt for sending quick, one-line emails, via GNU \'mail\'.
-- Copyright : (c) 2007 Brent Yorgey
-- License : BSD-style (see LICENSE)
--
-- Maintainer : <byorgey@gmail.com>
-- Stability : stable
-- Portability : unportable
--
-- A prompt for sending quick, one-line emails, via the standard GNU
-- \'mail\' utility (which must be in your $PATH). This module is
-- intended mostly as an example of using "XMonad.Prompt.Input" to
-- build an action requiring user input.
--
-----------------------------------------------------------------------------
module XMonad.Prompt.Email (
-- * Usage
-- $usage
emailPrompt
) where
import XMonad.Core
import XMonad.Util.Run
import XMonad.Prelude (void)
import XMonad.Prompt
import XMonad.Prompt.Input
-- $usage
--
-- You can use this module by importing it, along with
-- "XMonad.Prompt", into your ~\/.xmonad\/xmonad.hs file:
--
-- > import XMonad.Prompt
-- > import XMonad.Prompt.Email
--
-- and adding an appropriate keybinding, for example:
--
-- > , ((modm .|. controlMask, xK_e), emailPrompt def addresses)
--
-- where @addresses@ is a list of email addresses that should
-- autocomplete, for example:
--
-- > addresses = ["me@me.com", "mr@big.com", "tom.jones@foo.bar"]
--
-- You can still send email to any address, but sending to these
-- addresses will be faster since you only have to type a few
-- characters and then hit \'tab\'.
--
-- For detailed instructions on editing your key bindings, see
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial>.
-- | Prompt the user for a recipient, subject, and body, and send an
-- email via the GNU \'mail\' utility. The second argument is a list
-- of addresses for autocompletion.
emailPrompt :: XPConfig -> [String] -> X ()
emailPrompt c addrs =
inputPromptWithCompl c "To" (mkComplFunFromList c addrs) ?+ \to ->
inputPrompt c "Subject" ?+ \subj ->
inputPrompt c "Body" ?+ \body ->
void (runProcessWithInput "mail" ["-s", subj, to] (body ++ "\n"))