{- This file is part of Hoogle, (c) Neil Mitchell 2004-2005 http://www.cs.york.ac.uk/~ndm/hoogle/ This work is licensed under the Creative Commons Attribution-NonCommercial-ShareAlike License. To view a copy of this license, visit http://creativecommons.org/licenses/by-nc-sa/2.0/ or send a letter to Creative Commons, 559 Nathan Abbott Way, Stanford, California 94305, USA. -} {- | The Web interface, expects to be run as a CGI script. This does not require Haskell CGI etc, it just dumps HTML to the console -} module Web.Main where import Hoogle.Hoogle import Hoogle.TextUtil import Web.CGI import Web.Lambdabot import Char import System import List import Maybe import Directory -- | Should the output be sent to the console and a file. -- If true then both, the file is 'debugFile'. -- Useful mainly for debugging. debugOut = False fakeArgs :: IO [(String, String)] fakeArgs = return $ [("q","map"), ("format","sherlock")] -- | The main function main :: IO () main = do args <- if debugOut then fakeArgs else cgiArgs putStr "Content-type: text/html\n\n" appendFile "log.txt" (show args ++ "\n") let input = lookupDef "" "q" args if null input then hoogleBlank else do let p = hoogleParse input case hoogleParseError p of Just x -> showError input x Nothing -> showResults p args lookupDef :: Eq key => val -> key -> [(key, val)] -> val lookupDef def key list = case lookup key list of Nothing -> def Just x -> x lookupDefInt :: Eq key => Int -> key -> [(key, String)] -> Int lookupDefInt def key list = case lookup key list of Nothing -> def Just x -> case reads x of [(x,"")] -> x _ -> def -- | Show the search box hoogleBlank :: IO () hoogleBlank = do debugInit outputFile "front" -- | Replace all occurances of $ with the parameter outputFileParam :: FilePath -> String -> IO () outputFileParam x param = do src <- readFile ("res/" ++ x ++ ".inc") putLine (f src) where f ('$':xs) = param ++ f xs f (x:xs) = x : f xs f [] = [] outputFile :: FilePath -> IO () outputFile x = do src <- readFile ("res/" ++ x ++ ".inc") putLine src showError :: String -> String -> IO () showError input err = do debugInit outputFileParam "prefix" input outputFileParam "error" err outputFileParam "suffix" input -- | Perform a search, dump the results using 'putLine' showResults :: Search -> [(String, String)] -> IO () showResults input args = do res <- hoogleResults "res/hoogle.txt" input let lres = length res search = hoogleSearch input tSearch = showText search useres = take num $ drop start res debugInit outputFileParam "prefix" tSearch putLine $ "
Searched for " ++ showTags search ++ "" ++ (if lres == 0 then "No results found" else f lres) ++ "
" case hoogleSuggest True input of Nothing -> return () Just x -> putLine $ "

Hoogle says: " ++ showTags x ++ "

" lam <- Web.Lambdabot.query (lookupDef "" "q" args) case lam of Nothing -> return () Just x -> putLine $ "

" ++ "Lambdabot says: " ++ x ++ "

" if null res then outputFileParam "noresults" tSearch else putLine $ "" ++ concatMap showResult useres ++ "
" putLine $ g lres putLine $ if format == "sherlock" then sherlock useres else "" outputFileParam "suffix" tSearch where start = lookupDefInt 0 "start" args num = lookupDefInt 25 "num" args format = lookupDef "" "format" args nostart = filter ((/=) "start" . fst) args showPrev len pos = if start <= 0 then "" else " " showNext len pos = if start+num >= len then "" else " " f len = showPrev len "top" ++ "Results " ++ show (start+1) ++ " - " ++ show (min (start+num) len) ++ " of " ++ show len ++ "" ++ showNext len "top" g len = if start == 0 && len <= num then "" else "
" ++ showPrev len "bot" ++ concat (zipWith h [1..10] [0,num..len]) ++ showNext len "bot" ++ "
" h num start2 = " " ++ show num ++ " " sherlock :: [Result] -> String sherlock xs = "\n\n" where f res@(Result modu name typ _ _ _ _) = "" ++ hoodoc res True ++ "" ++ showTags name ++ " " ++ "(" ++ showText modu ++ ")" ++ "\n" showTags :: TagStr -> String showTags (Str x) = x showTags (Tag "b" x) = "" ++ showTags x ++ "" showTags (Tag "u" x) = "" ++ showTags x ++ "" showTags (Tag "a" x) = "" ++ showTags x ++ "" where url = if "http://" `isPrefixOf` txt then txt else "?q=" ++ escape txt txt = showText x showTags (Tag [n] x) | n >= '1' && n <= '6' = "" ++ showTags x ++ "" showTags (Tag n x) = showTags x showTags (Tags xs) = concatMap showTags xs showTagsLimit :: Int -> TagStr -> String showTagsLimit n x = if length s > n then take (n-2) s ++ ".." else s where s = showText x showResult :: Result -> String showResult res@(Result modu name typ _ _ _ _) = "" ++ "" ++ hoodoc res False ++ showTagsLimit 20 modu ++ "" ++ (if null (showTags modu) then "" else ".") ++ "" ++ openA ++ showTags name ++ "" ++ "" ++ openA ++ ":: " ++ showTags typ ++ "" ++ "" ++ "\n" where openA = hoodoc res True hoodoc :: Result -> Bool -> String hoodoc res full = f $ if not full then modu ++ "&mode=module" else if resultMode res == "module" then modu ++ (if null modu then "" else ".") ++ showText (resultName res) ++ "&mode=module" else showText (resultModule res) ++ "&name=" ++ escape (showText (resultName res)) ++ "&mode=" ++ resultMode res where modu = showText (resultModule res) f x = "" -- | The file to output to if 'debugOut' is True debugFile = "temp.htm" -- | Clear the debugging file debugInit = if debugOut then writeFile debugFile "" else return () -- | Write out a line, to console and optional to a debugging file putLine :: String -> IO () putLine x = do putStrLn x if debugOut then appendFile debugFile x else return () -- | Read the hit count, increment it, return the new value. -- Hit count is stored in hits.txt hitCount :: IO Integer hitCount = do x <- readHitCount -- HUGS SCREWS THIS UP WITHOUT `seq` -- this should not be needed, but it is -- (we think) x `seq` writeHitCount (x+1) return (x+1) where hitFile = "hits.txt" readHitCount :: IO Integer readHitCount = do exists <- doesFileExist hitFile if exists then do src <- readFile hitFile return (parseHitCount src) else return 0 writeHitCount :: Integer -> IO () writeHitCount x = writeFile hitFile (show x) parseHitCount = read . head . lines -- | Take a piece of text and escape all the HTML special bits escapeHTML :: String -> String escapeHTML = concatMap f where f :: Char -> String f '<' = "<" f '>' = ">" f '&' = "&" f x = x:[]