-----------------------------------------------------------------------------
-- |
-- Module      :  XMonad.Prompt.AppendFile
-- Description :  A prompt for appending a single line of text to a file.
-- Copyright   :  (c) 2007 Brent Yorgey
-- License     :  BSD-style (see LICENSE)
--
-- Maintainer  :  <byorgey@gmail.com>
-- Stability   :  stable
-- Portability :  unportable
--
-- A prompt for appending a single line of text to a file.  Useful for
-- keeping a file of notes, things to remember for later, and so on---
-- using a keybinding, you can write things down just about as quickly
-- as you think of them, so it doesn't have to interrupt whatever else
-- you're doing.
--
-- Who knows, it might be useful for other purposes as well!
--
-----------------------------------------------------------------------------

module XMonad.Prompt.AppendFile (
                                 -- * Usage
                                 -- $usage

                                 appendFilePrompt,
                                 appendFilePrompt',
                                 AppendFile,
                                ) where

import XMonad.Core
import XMonad.Prompt
import XMonad.Prelude (mkAbsolutePath)

import System.IO

-- $usage
--
-- You can use this module by importing it, along with
-- "XMonad.Prompt", into your @xmonad.hs@ file:
--
-- > import XMonad.Prompt
-- > import XMonad.Prompt.AppendFile
--
-- and adding an appropriate keybinding, for example:
--
-- >  , ((modm .|. controlMask, xK_n), appendFilePrompt def "/home/me/NOTES")
--
-- Additional notes can be added via regular Haskell or XMonad functions; for
-- example, to preface notes with the time they were made, one could write a
-- binding like
--
-- > ,  ((modm .|. controlMask, xK_n), do
-- >            spawn ("date>>"++"/home/me/NOTES")
-- >            appendFilePrompt def "/home/me/NOTES"
-- >        )
--
-- (Put the spawn on the line after the prompt to append the time instead.)
--
-- 'appendFilePrompt'' can be used to transform the string input in the prompt
-- before saving into the file. Previous example with date can be rewritten as:
--
-- > ,  ((modm .|. controlMask, xK_n), do
-- >            date <- io $ fmap (formatTime defaultTimeLocale "[%Y-%m-%d %H:%M] ") getZonedTime
-- >            appendFilePrompt' def (date ++) $ "/home/me/NOTES"
-- >        )
--
-- A benefit is that if the prompt is cancelled the date is not output to
-- the file too.
--
-- For detailed instructions on editing your key bindings, see
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial>.

newtype AppendFile = AppendFile FilePath

instance XPrompt AppendFile where
    showXPrompt :: AppendFile -> String
showXPrompt (AppendFile String
fn) = String
"Add to " forall a. [a] -> [a] -> [a]
++ String
fn forall a. [a] -> [a] -> [a]
++ String
": "

-- | Given an XPrompt configuration and a file path, prompt the user
--   for a line of text, and append it to the given file.
appendFilePrompt :: XPConfig -> FilePath -> X ()
appendFilePrompt :: XPConfig -> String -> X ()
appendFilePrompt XPConfig
c = XPConfig -> (String -> String) -> String -> X ()
appendFilePrompt' XPConfig
c forall a. a -> a
id

-- | Given an XPrompt configuration, string transformation function
--   and a file path, prompt the user for a line of text, transform it
--   and append the result to the given file.
appendFilePrompt' :: XPConfig -> (String -> String) -> FilePath -> X ()
appendFilePrompt' :: XPConfig -> (String -> String) -> String -> X ()
appendFilePrompt' XPConfig
c String -> String
trans String
fn = forall p.
XPrompt p =>
p -> XPConfig -> ComplFunction -> (String -> X ()) -> X ()
mkXPrompt (String -> AppendFile
AppendFile String
fn)
                                  XPConfig
c
                                  (forall a b. a -> b -> a
const (forall (m :: * -> *) a. Monad m => a -> m a
return []))
                                  ((String -> String) -> String -> String -> X ()
doAppend String -> String
trans String
fn)

-- | Append a string to a file.
doAppend :: (String -> String) -> FilePath -> String -> X ()
doAppend :: (String -> String) -> String -> String -> X ()
doAppend String -> String
trans String
fn String
s = forall (m :: * -> *). MonadIO m => String -> m String
mkAbsolutePath String
fn forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \String
f -> (forall (m :: * -> *) a. MonadIO m => IO a -> m a
io forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall r. String -> IOMode -> (Handle -> IO r) -> IO r
withFile String
f IOMode
AppendMode forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c. (a -> b -> c) -> b -> a -> c
flip Handle -> String -> IO ()
hPutStrLn forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
trans) String
s