Commit f95b71d2 authored by Thomas Peiselt's avatar Thomas Peiselt

Use hoogle v5.

Hoogle v5 uses a different json representation for the data, requires a
new URL and also contains HTML markup inside the json fields.

This commit removes all markup to be able to handle the hoogle responses
using the same structure as with the previous response structure (from
hoogle v4).
parent c3a70079
...@@ -164,6 +164,7 @@ Test-Suite hspec ...@@ -164,6 +164,7 @@ Test-Suite hspec
IHaskell.Test.Completion IHaskell.Test.Completion
IHaskell.Test.Util IHaskell.Test.Util
IHaskell.Test.Parser IHaskell.Test.Parser
IHaskell.Test.Hoogle
default-language: Haskell2010 default-language: Haskell2010
build-depends: build-depends:
base, base,
...@@ -178,6 +179,7 @@ Test-Suite hspec ...@@ -178,6 +179,7 @@ Test-Suite hspec
directory, directory,
text, text,
shelly, shelly,
raw-strings-qq,
setenv setenv
source-repository head source-repository head
......
{-# LANGUAGE NoImplicitPrelude, FlexibleInstances, OverloadedStrings #-} {-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module IHaskell.Eval.Hoogle ( module IHaskell.Eval.Hoogle (
search, search,
document, document,
render, render,
OutputFormat(..), OutputFormat(..),
HoogleResult, HoogleResult(..),
HoogleResponse(..),
parseResponse,
) where ) where
import IHaskellPrelude
import qualified Data.ByteString.Lazy as LBS
import qualified Data.ByteString.Char8 as CBS import qualified Data.ByteString.Char8 as CBS
import qualified Data.ByteString.Lazy as LBS
import Data.Either (either)
import IHaskellPrelude
import Network.HTTP.Client
import Network.HTTP.Client.TLS
import Data.Aeson import Data.Aeson
import Data.Char (isAlphaNum, isAscii)
import qualified Data.List as List import qualified Data.List as List
import Data.Char (isAscii, isAlphaNum) import qualified Data.Text as T
import Data.Vector (toList)
import Network.HTTP.Client
import Network.HTTP.Client.TLS
import StringUtils (replace, split, strip)
import StringUtils (split, strip, replace) import Debug.Trace
-- | Types of formats to render output to. -- | Types of formats to render output to.
data OutputFormat = Plain -- ^ Render to plain text. data OutputFormat = Plain -- ^ Render to plain text.
...@@ -35,17 +44,19 @@ data HoogleResult = SearchResult HoogleResponse ...@@ -35,17 +44,19 @@ data HoogleResult = SearchResult HoogleResponse
data HoogleResponseList = HoogleResponseList [HoogleResponse] data HoogleResponseList = HoogleResponseList [HoogleResponse]
instance FromJSON HoogleResponseList where instance FromJSON HoogleResponseList where
parseJSON (Object obj) = do parseJSON (Array arr) =
results <- obj .: "results" HoogleResponseList <$> mapM parseJSON (toList arr)
HoogleResponseList <$> mapM parseJSON results
parseJSON _ = fail "Expected object with 'results' field." parseJSON _ = fail "Expected array."
instance FromJSON HoogleResponse where instance FromJSON HoogleResponse where
parseJSON (Object obj) = parseJSON (Object obj) =
HoogleResponse <$> obj .: "location" <*> obj .: "self" <*> obj .: "docs" HoogleResponse
<$> obj .: "url"
<*> (removeMarkup <$> obj .: "item")
<*> obj .: "docs"
parseJSON _ = fail "Expected object with fields: location, self, docs" parseJSON _ = fail "Expected object with fields: url, item, docs"
-- | Query Hoogle for the given string. This searches Hoogle using the internet. It returns either -- | Query Hoogle for the given string. This searches Hoogle using the internet. It returns either
-- an error message or the successful JSON result. -- an error message or the successful JSON result.
...@@ -59,7 +70,7 @@ query str = do ...@@ -59,7 +70,7 @@ query str = do
where where
queryUrl :: String -> String queryUrl :: String -> String
queryUrl = printf "https://www.haskell.org/hoogle/?hoogle=%s&mode=json" queryUrl = printf "http://hoogle.haskell.org/?hoogle=%s&mode=json"
-- | Copied from the HTTP package. -- | Copied from the HTTP package.
urlEncode :: String -> String urlEncode :: String -> String
...@@ -87,12 +98,10 @@ urlEncode (ch:t) ...@@ -87,12 +98,10 @@ urlEncode (ch:t)
-- | Search for a query on Hoogle. Return all search results. -- | Search for a query on Hoogle. Return all search results.
search :: String -> IO [HoogleResult] search :: String -> IO [HoogleResult]
search string = do search string = either ((:[]) . NoResult) parseResponse <$> query string
response <- query string
return $ parseResponse :: String -> [HoogleResult]
case response of parseResponse jsn =
Left err -> [NoResult err]
Right jsn ->
case eitherDecode $ LBS.fromStrict $ CBS.pack jsn of case eitherDecode $ LBS.fromStrict $ CBS.pack jsn of
Left err -> [NoResult err] Left err -> [NoResult err]
Right results -> Right results ->
...@@ -182,7 +191,7 @@ renderSelf string loc ...@@ -182,7 +191,7 @@ renderSelf string loc
packageSub package packageSub package
| otherwise = | otherwise =
let [name, args] = split "::" string let [name, args] = trace string $ split "::" string
package = extractPackageName loc package = extractPackageName loc
modname = extractModuleName loc modname = extractModuleName loc
in span "hoogle-name" in span "hoogle-name"
...@@ -259,3 +268,17 @@ span = printf "<span class='%s'>%s</span>" ...@@ -259,3 +268,17 @@ span = printf "<span class='%s'>%s</span>"
link :: String -> String -> String link :: String -> String -> String
link = printf "<a target='_blank' href='%s'>%s</a>" link = printf "<a target='_blank' href='%s'>%s</a>"
-- | very explicit cleaning of the type signature in the hoogle 5 response,
-- to remove html markup and escaped characters.
removeMarkup :: String -> String
removeMarkup s = T.unpack $ List.foldl (flip ($)) (T.pack s) replaceAll
where replacements :: [ (T.Text, T.Text) ]
replacements = [ ( "<span class=name><0>", "" )
, ( "</0></span>", "" )
, ( "&gt;", ">" )
, ( "&lt;", "<" )
, ( "<b>", "")
, ( "</b>", "")
]
replaceAll = uncurry T.replace <$> replacements
...@@ -7,6 +7,7 @@ import Test.Hspec ...@@ -7,6 +7,7 @@ import Test.Hspec
import IHaskell.Test.Completion (testCompletions) import IHaskell.Test.Completion (testCompletions)
import IHaskell.Test.Parser (testParser) import IHaskell.Test.Parser (testParser)
import IHaskell.Test.Eval (testEval) import IHaskell.Test.Eval (testEval)
import IHaskell.Test.Hoogle (testHoogle)
main :: IO () main :: IO ()
main = main =
...@@ -14,3 +15,4 @@ main = ...@@ -14,3 +15,4 @@ main =
testParser testParser
testEval testEval
testCompletions testCompletions
testHoogle
{-# LANGUAGE QuasiQuotes #-}
module IHaskell.Test.Hoogle ( testHoogle ) where
import Test.Hspec
import Text.RawString.QQ
import IHaskell.Eval.Hoogle
-- import Data.Text (unpack)
-- import qualified Data.Text.IO as T
preludeFmapJson :: String
preludeFmapJson = [r|
[
{
"url": "https://hackage.haskell.org/package/base/docs/Prelude.html#v:fmap",
"module": {
"url": "https://hackage.haskell.org/package/base/docs/Prelude.html",
"name": "Prelude"
},
"package": {
"url": "https://hackage.haskell.org/package/base",
"name": "base"
},
"item": "<span class=name><0>fmap</0></span> :: Functor f =&gt; (a -&gt; b) -&gt; f a -&gt; f b",
"type": "",
"docs": ""
}
]|]
moduleJson :: String
moduleJson = [r|
[
{
"url": "https://hackage.haskell.org/package/universum/docs/Universum-Functor-Fmap.html",
"module": {},
"package": {
"url": "https://hackage.haskell.org/package/universum",
"name": "universum"
},
"item": "<b>module</b> Universum.Functor.<span class=name><0>Fmap</0></span>",
"type": "module",
"docs": "This module contains useful functions to work with <a>Functor</a> type\nclass.\n"
}
]|]
testHoogle :: Spec
testHoogle = describe "Hoogle Search" $ do
describe "fmap search result" $ do
let results = parseResponse preludeFmapJson :: [HoogleResult]
it "should find 1 results" $ do
length results `shouldBe` 1
let (SearchResult (HoogleResponse loc signature _docUrl)) = head results
it "should not contain html markup" $ do
loc `shouldBe` "https://hackage.haskell.org/package/base/docs/Prelude.html#v:fmap"
signature `shouldBe` "fmap :: Functor f => (a -> b) -> f a -> f b"
describe "module result" $ do
let results = parseResponse moduleJson :: [HoogleResult]
let (SearchResult (HoogleResponse _loc signature _docUrl)) = head results
it "should not contain html markup" $ do
signature `shouldBe` "module Universum.Functor.Fmap"
it "should be renderable" $ do
(render Plain $ head results) `shouldStartWith` "module Universum.Functor.Fmap"
(render HTML $ head results) `shouldStartWith` "<span class='hoogle-head'>module</span>"
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment