aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Actions/Launcher.hs
blob: fc6eeb4f5178260463ad09d514ef91b15e180e0a (plain) (blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
{- |
Module      :  XMonad.Actions.Launcher
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           Data.List            (find, findIndex, isPrefixOf, tails)
import qualified Data.Map             as M
import           Data.Maybe           (fromMaybe, isJust)
import           System.Directory     (doesDirectoryExist)
import           XMonad               hiding (config)
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(defaultXPConfig)
    > import XMonad.Actions.Launcher

    > ((modm .|. controlMask, xK_l), launcherPrompt defaultXPConfig $ 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 'defaultXPConfig', 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 {
  browser              :: String
  , pathToHoogle       :: String
}

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

-- | Uses the command `calc` to compute arithmetic expressions
instance XPrompt CalculatorMode where
  showXPrompt CalcMode = "calc %s> "
  commandToComplete CalcMode = id --send the whole string to `calc`
  completionFunction CalcMode = \s -> if (length s == 0) then return [] else do
    fmap lines $ runProcessWithInput "calc" [s] ""
  modeAction CalcMode _ _ = return () -- do nothing; this might copy the result to the clipboard

-- | Uses the program `hoogle` to search for functions
instance XPrompt HoogleMode where
  showXPrompt _ = "hoogle %s> "
  commandToComplete _ = id
  completionFunction (HMode pathToHoogleBin' _) = \s -> completionFunctionWith pathToHoogleBin' ["--count","8",s]
  -- This action calls hoogle again to find the URL corresponding to the autocompleted item
  modeAction (HMode pathToHoogleBin'' browser') query result = do
    completionsWithLink <- liftIO $ completionFunctionWith pathToHoogleBin'' ["--count","5","--link",query]
    let link = do
          s <- find (isJust . \complStr -> findSeqIndex complStr result) completionsWithLink
          i <- findSeqIndex s "http://"
          return $ drop i s
    case link of
       Just l -> spawn $ browser' ++ " " ++ l
       _      -> 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 xs xss = findIndex (isPrefixOf xss) $ tails 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 cmd args = do fmap lines $ runProcessWithInput cmd args ""

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

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

hoogleMode :: FilePath -> String -> XPMode
hoogleMode pathToHoogleBin browser' = XPT $ HMode pathToHoogleBin browser'
calcMode :: XPMode
calcMode = XPT CalcMode

-- | This function takes a map of extensions and a path file. It uses the map to find the pattern that matches the file path, then the corresponding program (listed in the map) is spawned.
spawnWithActions :: ExtensionActions -> FilePath -> X()
spawnWithActions actions fp = do
  isDirectoryPath <- liftIO $ doesDirectoryExist fp
  let
    takeExtension = \p -> "." ++ (reverse . takeWhile (/= '.') $ reverse p) --it includes the dot
    -- Patterns defined by the user
    extAction = M.lookup (takeExtension fp) actions
    dirAction = if (isDirectoryPath) then M.lookup "/" actions else Nothing -- / represents a directory
    anyFileAction = M.lookup ".*" actions  -- .* represents any file
    action = fromMaybe (spawnNoPatternMessage (takeExtension fp)) $ extAction `orElse1` dirAction `orElse1` anyFileAction
  action fp
     where
       -- | This function is defined in Data.Generics.Aliases (package syb "Scrap your boilerplate"), defined here to avoid dependency
       orElse1 :: Maybe a -> Maybe a -> Maybe a
       x `orElse1` y = case x of
         Just _  -> x
         Nothing -> y
       spawnNoPatternMessage :: String -> String -> X ()
       spawnNoPatternMessage fileExt _ = spawn $ "xmessage No action specified for file extension " ++ fileExt ++ ", add a default action by matching the extension \".*\" in the action map sent to launcherPrompt"

{- 

  -- 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)
-}