aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Util/Search.hs
diff options
context:
space:
mode:
authorgwern0 <gwern0@gmail.com>2007-12-15 22:16:38 +0100
committergwern0 <gwern0@gmail.com>2007-12-15 22:16:38 +0100
commit4bbbcd0601ed8ed7cfcfa9b5285e1bd2164a6466 (patch)
treef6a7e34a63b48e78877701df38b8c7cf437357b1 /XMonad/Util/Search.hs
parent0ea6e96512fb5a686454964953a9dfe8f99340a2 (diff)
downloadXMonadContrib-4bbbcd0601ed8ed7cfcfa9b5285e1bd2164a6466.tar.gz
XMonadContrib-4bbbcd0601ed8ed7cfcfa9b5285e1bd2164a6466.tar.xz
XMonadContrib-4bbbcd0601ed8ed7cfcfa9b5285e1bd2164a6466.zip
Util.Search: import escapeURIString, and fall back on the ugly const false hack to avoid copy-pasting even more
darcs-hash:20071215211638-f7719-8d0d1d832a8a4c1f059e043e6beb2d4834bfde8f.gz
Diffstat (limited to 'XMonad/Util/Search.hs')
-rw-r--r--XMonad/Util/Search.hs30
1 files changed, 26 insertions, 4 deletions
diff --git a/XMonad/Util/Search.hs b/XMonad/Util/Search.hs
index b767971..c20ff1f 100644
--- a/XMonad/Util/Search.hs
+++ b/XMonad/Util/Search.hs
@@ -30,6 +30,8 @@ import XMonad.Util.Run (safeSpawn)
import XMonad.Prompt.Shell (getShellCompl)
import XMonad.Prompt (XPrompt(showXPrompt), mkXPrompt, XPConfig())
import XMonad.Util.XSelection (getSelection)
+import Data.Char (chr, ord)
+import Numeric (showIntAtBase)
-- A customized prompt
data Search = Search
@@ -37,11 +39,31 @@ instance XPrompt Search where
showXPrompt Search = "Search: "
-- | Escape the search string so search engines understand it.
--- We could just go (const False) and escape anything that even looks at us
--- funny, but that produces obfuscated search queries. So we merely escape
--- anything that doesn't look unfunny.
+-- 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'.
escape :: String -> String
-escape = id
+escape = escapeURIString (const False)
+ where
+ escapeURIString ::
+ (Char -> Bool) -- ^ a predicate which returns 'False'
+ -- if the character should be escaped
+ -> String -- ^ the string to process
+ -> String -- ^ the resulting URI string
+ escapeURIString p s = concatMap (escapeURIChar p) s
+
+ escapeURIChar :: (Char->Bool) -> Char -> String
+ escapeURIChar p c
+ | p c = [c]
+ | otherwise = '%' : myShowHex (ord c) ""
+ where
+ myShowHex :: Int -> ShowS
+ myShowHex n r = case showIntAtBase 16 (toChrHex) n r of
+ [] -> "00"
+ [c] -> ['0',c]
+ cs -> cs
+ toChrHex d
+ | d < 10 = chr (ord '0' + fromIntegral d)
+ | otherwise = chr (ord 'A' + fromIntegral (d - 10))
-- | Given the base search URL, a browser to use, and the actual query, escape
-- the query, prepend the base URL, and hand it off to the browser.