aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Actions/Search.hs
diff options
context:
space:
mode:
authorgwern0 <gwern0@gmail.com>2008-04-01 03:39:47 +0200
committergwern0 <gwern0@gmail.com>2008-04-01 03:39:47 +0200
commite6c215cbecc6c4c4f86d8d18884e55d82d3eb1ce (patch)
treeaad4054d9f384aeddf93efcd4a02a6bf51db38c0 /XMonad/Actions/Search.hs
parent6e52f21443139d5e7766222a744a5faca075fc47 (diff)
downloadXMonadContrib-e6c215cbecc6c4c4f86d8d18884e55d82d3eb1ce.tar.gz
XMonadContrib-e6c215cbecc6c4c4f86d8d18884e55d82d3eb1ce.tar.xz
XMonadContrib-e6c215cbecc6c4c4f86d8d18884e55d82d3eb1ce.zip
Search.hs: remove an argument from selectSearch and promptSearch
The new getBrowser function allows us to mv the old selectSearch and promptSearch aside as too-general functions, and replace them with new versions, which employ getBrowser to supply one more argument. This allows us to replace the tedious 'selectSearch google "firefox"; selectSearch yahoo "firefox"...' with shorter 'selectSearch google' and so on. One less argument. Also, update the docs. darcs-hash:20080401013947-f7719-866c590c5d7c109718ed54fcdee0313550bbef40.gz
Diffstat (limited to 'XMonad/Actions/Search.hs')
-rw-r--r--XMonad/Actions/Search.hs100
1 files changed, 57 insertions, 43 deletions
diff --git a/XMonad/Actions/Search.hs b/XMonad/Actions/Search.hs
index 3f67e09..8e9387e 100644
--- a/XMonad/Actions/Search.hs
+++ b/XMonad/Actions/Search.hs
@@ -12,33 +12,35 @@
Additional sites welcomed.
-}
-module XMonad.Actions.Search ( -- * Usage
- -- $usage
- search,
- simpleEngine,
- promptSearch,
- selectSearch,
-
- amazon,
- google,
- hoogle,
- imdb,
- maps,
- mathworld,
- scholar,
- wayback,
- wikipedia
-
- -- * Use case: searching with a submap
- -- $tip
+module XMonad.Actions.Search ( -- * Usage
+ -- $usage
+ search,
+ simpleEngine,
+ promptSearch,
+ promptSearchBrowser,
+ selectSearch,
+ selectSearchBrowser,
+
+ amazon,
+ google,
+ hoogle,
+ imdb,
+ maps,
+ mathworld,
+ scholar,
+ wayback,
+ wikipedia
+
+ -- * Use case: searching with a submap
+ -- $tip
) where
import Data.Char (chr, ord, isAlpha, isMark, isDigit)
import Numeric (showIntAtBase)
-import XMonad (X(), MonadIO)
+import XMonad (X(), MonadIO, liftIO)
import XMonad.Prompt (XPrompt(showXPrompt), mkXPrompt, XPConfig())
-import XMonad.Prompt.Shell (getShellCompl)
+import XMonad.Prompt.Shell (getBrowser, getShellCompl)
import XMonad.Util.Run (safeSpawn)
import XMonad.Util.XSelection (getSelection)
@@ -84,8 +86,7 @@ import XMonad.Util.XSelection (getSelection)
* 'wikipedia' -- basic Wikipedia search.
-Feel free to add more!
--}
+Feel free to add more! -}
{- $tip
@@ -108,9 +109,9 @@ Then add the following to your key bindings:
> ...
>
> searchEngineMap method = M.fromList $
-> [ ((0, xK_g), method \"firefox\" S.google)
-> , ((0, xK_h), method \"firefox\" S.hoogle)
-> , ((0, xK_w), method \"firefox\" S.wikipedia)
+> [ ((0, xK_g), method S.google)
+> , ((0, xK_h), method S.hoogle)
+> , ((0, xK_w), method S.wikipedia)
> ]
Make sure to set firefox to open new pages in a new window instead of
@@ -125,17 +126,16 @@ If you select something in whatever application and hit /mod-shift-s/ +
/g/\//h/\//w/ it will search the selected string with the specified
engine.
-Happy searching!
--}
+Happy searching! -}
--- A customized prompt.
+-- | A customized prompt indicating we are searching, and not anything else.
data Search = Search
instance XPrompt Search where
showXPrompt Search = "Search: "
-- | Escape the search string so search engines understand it.
-- Note that everything is escaped; we could be smarter and use 'isAllowedInURI'
--- but then that'd be hard enough to copy-and-paste we'd need to depend on 'network'.
+-- but then that'd be hard enough to copy-and-paste we'd need to depend on @network@.
escape :: String -> String
escape = escapeURIString (\c -> isAlpha c || isDigit c || isMark c)
where -- Copied from Network.URI.
@@ -162,9 +162,9 @@ type Browser = FilePath
type Query = String
type SearchEngine = String -> String
-{- | Given a browser, a search engine, and a search term, perform the
- requested search in the browser. -}
-search :: MonadIO m => Browser -> SearchEngine -> Query -> m ()
+-- | Given a browser, a search engine, and a search term, perform the
+-- requested search in the browser.
+search :: Browser -> SearchEngine -> Query -> X ()
search browser site query = safeSpawn browser $ site query
{- | Given a base URL, create the SearchEngine that escapes the query and
@@ -191,25 +191,39 @@ maps = simpleEngine "http://maps.google.com/maps?q="
mathworld = simpleEngine "http://mathworld.wolfram.com/search/?query="
scholar = simpleEngine "http://scholar.google.com/scholar?q="
wikipedia = simpleEngine "https://secure.wikimedia.org/wikipedia/en/wiki/Special:Search?go=Go&search="
-wayback = simpleEngine "http://web.archive.org/"
{- This doesn't seem to work, but nevertheless, it seems to be the official
method at <http://web.archive.org/collections/web/advanced.html> to get the
latest backup. -}
+wayback = simpleEngine "http://web.archive.org/"
+
+{- | Like 'search', but for use with the output from a Prompt; it grabs the
+ Prompt's result, passes it to a given searchEngine and opens it in a given
+ browser. -}
+promptSearchBrowser :: XPConfig -> Browser -> SearchEngine -> X ()
+promptSearchBrowser config browser engine = mkXPrompt Search config (getShellCompl []) $ search browser engine
{- | Like 'search', but in this case, the string is not specified but grabbed
from the user's response to a prompt. Example:
- > , ((modm, xK_g), promptSearch greenXPConfig "firefox" google)
+> , ((modm, xK_g), promptSearch greenXPConfig google)
--}
-promptSearch :: XPConfig -> Browser -> SearchEngine -> X ()
-promptSearch config browser site = mkXPrompt Search config (getShellCompl []) $ search browser site
+ This specializes "promptSearchBrowser" by supplying the browser argument as
+ supplied by 'getBrowser' from "XMonad.Prompt.Shell". -}
+promptSearch :: XPConfig -> SearchEngine -> X ()
+promptSearch config engine = liftIO getBrowser >>= \ browser -> promptSearchBrowser config browser engine
+
+-- | Like 'search', but for use with the X selection; it grabs the selection,
+-- passes it to a given searchEngine and opens it in a given browser.
+-- selectSearchBrowser :: Browser -> SearchEngine -> IO ()
+selectSearchBrowser :: Browser -> SearchEngine -> X ()
+selectSearchBrowser browser searchengine = search browser searchengine =<< getSelection
{- | Like 'search', but for use with the X selection; it grabs the selection,
- passes it to a given searchEngine and opens it in the given browser. Example:
+ passes it to a given searchEngine and opens it in the default browser . Example:
-> , ((modm .|. shiftMask, xK_g), selectSearch "firefox" google)
+> , ((modm .|. shiftMask, xK_g), selectSearch google)
--}
-selectSearch :: MonadIO m => Browser -> SearchEngine -> m ()
-selectSearch browser searchEngine = search browser searchEngine =<< getSelection
+ This specializes "selectSearchBrowser" by supplying the browser argument as
+ supplied by 'getBrowser' from "XMonad.Prompt.Shell". -}
+selectSearch :: SearchEngine -> X ()
+selectSearch engine = liftIO getBrowser >>= \browser -> selectSearchBrowser browser engine \ No newline at end of file