{- |
Module      :  XMonad.Actions.Launcher
Description :  A set of prompts for XMonad.
Copyright   :  (C) 2012 Carlos López-Camey
License     :  None; public domain

Maintainer  :  <c.lopez@kmels.net>
Stability   :  unstable

A set of prompts for XMonad
-}

module XMonad.Actions.Launcher(
  -- * Description and use
  -- $description
  defaultLauncherModes
  , ExtensionActions
  , LauncherConfig(..)
  , launcherPrompt
) where

import qualified Data.Map        as M
import           XMonad          hiding (config)
import           XMonad.Prelude
import           XMonad.Prompt
import           XMonad.Util.Run

{- $description
    This module exemplifies usage of `XMonad.Prompt.mkXPromptWithModes`. It includes two modes:

       * Hoogle mode: Search for functions using hoogle, choosing a function leads you to documentation in Haddock.

       * Calc: Uses the program calc to do calculations.

    To test it, modify your local .xmonad:

    > import XMonad.Prompt(def)
    > import XMonad.Actions.Launcher

    > ((modm .|. controlMask, xK_l), launcherPrompt def $ defaultLauncherModes launcherConfig)

    A LauncherConfig contains settings for the default modes, modify them accordingly.

    > launcherConfig = LauncherConfig { pathToHoogle = "/home/YOU/.cabal/bin/hoogle" , browser = "firefox"}

Restart xmonad. Press Ctrl + Your_Modkey + L and the first prompt should pop up.

 If you used the default 'XPConfig', you can change mode with 'xK_grave'. If you are using your own 'XPConfig', define the value for 'changeModeKey'.
 -}

data HoogleMode = HMode FilePath String --path to hoogle and browser
data CalculatorMode = CalcMode

data LauncherConfig = LauncherConfig {
  LauncherConfig -> String
browser        :: String
  , LauncherConfig -> String
pathToHoogle :: String
}

type ExtensionActions = M.Map String (String -> X())

-- | Uses the command `calc` to compute arithmetic expressions
instance XPrompt CalculatorMode where
  showXPrompt :: CalculatorMode -> String
showXPrompt CalculatorMode
CalcMode = String
"calc %s> "
  commandToComplete :: CalculatorMode -> String -> String
commandToComplete CalculatorMode
CalcMode = forall a. a -> a
id --send the whole string to `calc`
  completionFunction :: CalculatorMode -> ComplFunction
completionFunction CalculatorMode
CalcMode String
s = if forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
s then forall (m :: * -> *) a. Monad m => a -> m a
return [] else
    String -> [String]
lines forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *).
MonadIO m =>
String -> [String] -> String -> m String
runProcessWithInput String
"calc" [String
s] String
""
  modeAction :: CalculatorMode -> String -> String -> X ()
modeAction CalculatorMode
CalcMode String
_ String
_ = forall (m :: * -> *) a. Monad m => a -> m a
return () -- do nothing; this might copy the result to the clipboard

-- | Uses the program `hoogle` to search for functions
instance XPrompt HoogleMode where
  showXPrompt :: HoogleMode -> String
showXPrompt HoogleMode
_ = String
"hoogle %s> "
  commandToComplete :: HoogleMode -> String -> String
commandToComplete HoogleMode
_ = forall a. a -> a
id
  completionFunction :: HoogleMode -> ComplFunction
completionFunction (HMode String
pathToHoogleBin' String
_) String
s = String -> [String] -> IO [String]
completionFunctionWith String
pathToHoogleBin' [String
"--count",String
"8",String
s]
  -- This action calls hoogle again to find the URL corresponding to the autocompleted item
  modeAction :: HoogleMode -> String -> String -> X ()
modeAction (HMode String
pathToHoogleBin'' String
browser') String
query String
result = do
    [String]
completionsWithLink <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ String -> [String] -> IO [String]
completionFunctionWith String
pathToHoogleBin'' [String
"--count",String
"5",String
"--link",String
query]
    let link :: Maybe String
link = do
          String
s <- forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (forall a. Maybe a -> Bool
isJust forall b c a. (b -> c) -> (a -> b) -> a -> c
. \String
complStr -> forall a. Eq a => [a] -> [a] -> Maybe Int
findSeqIndex String
complStr String
result) [String]
completionsWithLink
          Int
i <- forall a. Eq a => [a] -> [a] -> Maybe Int
findSeqIndex String
s String
"http://"
          forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. Int -> [a] -> [a]
drop Int
i String
s
    case Maybe String
link of
       Just String
l -> forall (m :: * -> *). MonadIO m => String -> m ()
spawn forall a b. (a -> b) -> a -> b
$ String
browser' forall a. [a] -> [a] -> [a]
++ String
" " forall a. [a] -> [a] -> [a]
++ String
l
       Maybe String
_      -> forall (m :: * -> *) a. Monad m => a -> m a
return ()
    where
      -- | Receives a sublist and a list. It returns the index where the sublist appears in the list.
      findSeqIndex :: (Eq a) => [a] -> [a] -> Maybe Int
      findSeqIndex :: forall a. Eq a => [a] -> [a] -> Maybe Int
findSeqIndex [a]
xs [a]
xss = forall a. (a -> Bool) -> [a] -> Maybe Int
findIndex (forall a. Eq a => [a] -> [a] -> Bool
isPrefixOf [a]
xss) forall a b. (a -> b) -> a -> b
$ forall a. [a] -> [[a]]
tails [a]
xs

-- | Creates an autocompletion function for a programm given the program's name and a list of args to send to the command.
completionFunctionWith :: String -> [String] -> IO [String]
completionFunctionWith :: String -> [String] -> IO [String]
completionFunctionWith String
cmd [String]
args = String -> [String]
lines forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *).
MonadIO m =>
String -> [String] -> String -> m String
runProcessWithInput String
cmd [String]
args String
""

-- | Creates a prompt with the given modes
launcherPrompt :: XPConfig -> [XPMode] -> X()
launcherPrompt :: XPConfig -> [XPMode] -> X ()
launcherPrompt XPConfig
config [XPMode]
modes = [XPMode] -> XPConfig -> X ()
mkXPromptWithModes [XPMode]
modes XPConfig
config

-- | Create a list of modes based on :
-- a list of extensions mapped to actions
-- the path to hoogle
defaultLauncherModes :: LauncherConfig -> [XPMode]
defaultLauncherModes :: LauncherConfig -> [XPMode]
defaultLauncherModes LauncherConfig
cnf = let
  ph :: String
ph           = LauncherConfig -> String
pathToHoogle LauncherConfig
cnf
  in [ String -> String -> XPMode
hoogleMode String
ph forall a b. (a -> b) -> a -> b
$ LauncherConfig -> String
browser LauncherConfig
cnf
     , XPMode
calcMode]

hoogleMode :: FilePath -> String -> XPMode
hoogleMode :: String -> String -> XPMode
hoogleMode String
pathToHoogleBin String
browser' = forall p. XPrompt p => p -> XPMode
XPT forall a b. (a -> b) -> a -> b
$ String -> String -> HoogleMode
HMode String
pathToHoogleBin String
browser'
calcMode :: XPMode
calcMode :: XPMode
calcMode = forall p. XPrompt p => p -> XPMode
XPT CalculatorMode
CalcMode

{-

  -- ideas for XMonad.Prompt running on mode XPMultipleModes
     * Switch to mode by name of the prompt, 1. ':' at an empty(?) buffer, 2. autocomplete name in buffer should happen, 3. switch to mode with enter (cancel switch with C-g)

     * Support for actions of type String -> X a

  -- ideas for this module

     * Hoogle mode: add a setting in the action to either go to documentation or to the source code (needs hoogle change?)

     * Hoogle mode: add setting to query hoogle at haskell.org instead (with &mode=json)
-}