Commit 7b75bfed authored by Mael NICOLAS's avatar Mael NICOLAS

type cleared, need to refactor functions.

Made client take doc as a parameter so we can know precisely what compose it
parent cc773005
...@@ -3,6 +3,7 @@ ...@@ -3,6 +3,7 @@
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE NoMonomorphismRestriction#-}
module HAL.Client where module HAL.Client where
...@@ -11,6 +12,7 @@ import GHC.Generics ...@@ -11,6 +12,7 @@ import GHC.Generics
import Servant.API import Servant.API
import Servant.Client hiding (Response) import Servant.Client hiding (Response)
import Data.Text import Data.Text
import Data.Map import Data.Map
import Data.Aeson import Data.Aeson
import qualified Data.ByteString.Lazy as BSL import qualified Data.ByteString.Lazy as BSL
...@@ -18,9 +20,9 @@ import qualified Codec.Binary.UTF8.String as UTF ...@@ -18,9 +20,9 @@ import qualified Codec.Binary.UTF8.String as UTF
import Control.Lens as L (makeLenses) import Control.Lens as L (makeLenses)
type HALAPI = Search :<|> Structure type HALAPI doc = (Search doc) :<|> (Structure doc)
type Search = "search" type Search doc = "search"
-- fl determine which fields will be returned it can be a list of fields or * -- fl determine which fields will be returned it can be a list of fields or *
:> QueryParams "fl" Text :> QueryParams "fl" Text
-- TODO: type this monster -- TODO: type this monster
...@@ -32,13 +34,13 @@ type Search = "search" ...@@ -32,13 +34,13 @@ type Search = "search"
:> QueryParam "start" Int :> QueryParam "start" Int
-- use rows to make the request only return the x number of result -- use rows to make the request only return the x number of result
:> QueryParam "rows" Int :> QueryParam "rows" Int
:> Get '[JSON] Response :> Get '[JSON] (Response doc)
type Structure = "ref" :> "structure" type Structure doc = "ref" :> "structure"
:> QueryParam "fq" Text :> QueryParam "fq" Text
:> QueryParam "fl" Text :> QueryParam "fl" Text
:> QueryParam "rows" Int :> QueryParam "rows" Int
:> Get '[JSON] Response :> Get '[JSON] (Response doc)
-- Get's argument type -- Get's argument type
...@@ -54,51 +56,54 @@ asc = Just . Asc ...@@ -54,51 +56,54 @@ asc = Just . Asc
desc :: Text -> Maybe SortField desc :: Text -> Maybe SortField
desc = Just . Desc desc = Just . Desc
newtype Doc = Doc (Map Text Value) -- newtype Doc = Doc (Map Text Value)
deriving (Generic) -- deriving (Generic)
--
instance Eq Doc where --instance Eq Doc where
(==) (Doc doc) (Doc doc') = (doc ! "docid") == (doc' ! "docid") -- (==) (Doc doc) (Doc doc') = (doc ! "docid") == (doc' ! "docid")
--
instance Show Doc where --instance Show Doc where
show (Doc o) = (UTF.decode $ BSL.unpack $ encode $ o ! "label_s") -- show (Doc o) = (UTF.decode $ BSL.unpack $ encode $ o ! "label_s")
<> "(" -- <> "("
<> (show . encode $ o ! "docid") -- <> (show . encode $ o ! "docid")
<> ")" -- <> ")"
--
instance FromJSON Doc --instance FromJSON Doc
instance ToJSON Doc --instance ToJSON Doc
-- Response type -- Response type
data Response = Response data Response doc = Response
{ {
_numFound :: Integer, _numFound :: Integer,
_start :: Int, _start :: Int,
_docs :: [Doc] _docs :: [doc]
} deriving (Show, Generic) } deriving (Show, Generic)
L.makeLenses ''Response L.makeLenses ''Response
instance FromJSON Response where instance FromJSON doc => FromJSON (Response doc) where
parseJSON (Object o) = Response <$> parseJSON (Object o) = Response <$>
((o .: "response") >>= (.: "numFound")) ((o .: "response") >>= (.: "numFound"))
<*> ((o .: "response") >>= (.: "start")) <*> ((o .: "response") >>= (.: "start"))
<*> ((o .: "response") >>= (.: "docs")) <*> ((o .: "response") >>= (.: "docs"))
halAPI :: Proxy HALAPI halAPI :: Proxy (HALAPI doc)
halAPI = Proxy halAPI = Proxy
structure :: Maybe Text -- fq structure :: FromJSON doc =>
Maybe Text -- fq
-> Maybe Text -> Maybe Text
-> Maybe Int -- rows -> Maybe Int -- rows
-> ClientM Response -> ClientM (Response doc)
-- search should always have at least `docid` and `label_s` in his fl params -- search should always have at least `docid` and `label_s` in his fl params
search :: [Text] -- fl search :: FromJSON doc =>
[Text] -- fl
-> [Text] -- fq -> [Text] -- fq
-> Maybe SortField -- sort -> Maybe SortField -- sort
-> Maybe Int -- start -> Maybe Int -- start
-> Maybe Int -- rows -> Maybe Int -- rows
-> ClientM Response -> ClientM (Response doc)
(search :<|> structure) = client halAPI (search :<|> structure) = client halAPI
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