[Add lamdabot hints
Neil Mitchell **20051214123048] {
addfile ./src/Web/Lambdabot.hs
hunk ./src/Web/Lambdabot.hs 1
+
+module Web.Lambdabot(query) where
+
+import List
+import Char
+
+query :: String -> IO (Maybe String)
+query x = do d <- readDatabase
+ return $ case filter ((==) (prepSearch x) . fst) d of
+ (x:xs) -> Just $ formatRes (snd x)
+ [] -> Nothing
+
+
+prepSearch = map toLower . reverse . dropWhile isSpace . reverse . dropWhile isSpace
+
+formatRes = unwords . map linky . words
+
+linky x | "http://" `isPrefixOf` x = "" ++ x ++ ""
+ | otherwise = x
+
+
+readDatabase :: IO [(String, String)]
+readDatabase = do x <- readFile "res/lambdabot.txt"
+ return $ f (lines x)
+ where
+ f (key:val:xs) = (key,val) : f xs
+ f _ = []
+
hunk ./src/Web/Main.hs 21
+import Web.Lambdabot
hunk ./src/Web/Main.hs 116
- Just x -> putLine $ "
" ++ showTags x ++ "
"
+ 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 ++ "
"
}