Files
xmonad-contrib/XMonad/Prompt/Email.hs
daniel db37e18098 generalize IO actions to MonadIO m => m actions
This should not cause any working configs to stop working, because IO is an instance of MonadIO, and because complete configs will pin down the type of the call to IO.  Note that XMonad.Config.Arossato is not a complete config, and so it needed some tweaks; with a main function, this should not be a problem.
2009-11-14 02:36:16 +00:00

64 lines
2.1 KiB
Haskell

-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Prompt.Email
-- 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.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 defaultXPConfig 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
-- "XMonad.Doc.Extending#Editing_key_bindings".
-- | 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 addrs) ?+ \to ->
inputPrompt c "Subject" ?+ \subj ->
inputPrompt c "Body" ?+ \body ->
runProcessWithInput "mail" ["-s", subj, to] (body ++ "\n")
>> return ()