[refactoring] use better query strings for Ends.purs

Also, some Routes.purs refactoring
parent baaea6e3
...@@ -3,16 +3,18 @@ module Gargantext.Ends ...@@ -3,16 +3,18 @@ module Gargantext.Ends
-- ( ) -- ( )
where where
import Prelude (class Eq, class Show, show, ($), (/=), (<<<), (<>), (==)) import Data.Array (filter)
import Data.Foldable (foldMap) import Data.Foldable (foldMap)
import Data.Generic.Rep (class Generic) import Data.Generic.Rep (class Generic)
import Data.Eq.Generic (genericEq) import Data.Eq.Generic (genericEq)
import Data.Maybe (Maybe(..), maybe, fromMaybe) import Data.Maybe (Maybe(..), maybe, fromMaybe)
import Data.Newtype (class Newtype) import Data.Newtype (class Newtype)
import Prelude (class Eq, class Show, show, ($), (/=), (<<<), (<>), (==), (<$>))
import Simple.JSON as JSON import Simple.JSON as JSON
import Gargantext.Routes as R import Gargantext.Routes as R
import Gargantext.Types (ApiVersion, ChartType(..), Limit, NodePath, NodeType(..), Offset, TabType(..), TermSize(..), nodePath, nodeTypePath, showTabType', TermList(MapTerm)) import Gargantext.Types (ApiVersion, ChartType(..), Limit, NodePath, NodeType(..), Offset, TabType(..), TermSize(..), nodePath, nodeTypePath, showTabType', TermList(MapTerm))
import Gargantext.Utils.QueryString (joinQueryStrings, mQueryParam, queryParam, queryParamS)
-- | A means of generating a url to visit, a destination -- | A means of generating a url to visit, a destination
class ToUrl conf p where class ToUrl conf p where
...@@ -90,56 +92,86 @@ staticUrl (Frontends {static}) = frontendUrl static ...@@ -90,56 +92,86 @@ staticUrl (Frontends {static}) = frontendUrl static
sessionPath :: R.SessionRoute -> String sessionPath :: R.SessionRoute -> String
sessionPath (R.Tab t i) = sessionPath (R.NodeAPI Node i (showTabType' t)) sessionPath (R.Tab t i) = sessionPath (R.NodeAPI Node i (showTabType' t))
sessionPath (R.Children n o l s i) = sessionPath (R.NodeAPI Node i ("children?type=" <> show n <> offsetUrl o <> limitUrl l <> orderUrl s)) sessionPath (R.Children n o l s i) = sessionPath (R.NodeAPI Node i ("children" <> qs))
sessionPath (R.RecomputeNgrams nt nId lId) = "node/" <> (show nId) <> "/ngrams/recompute?" <> (defaultList lId) <> "&ngramsType=" <> (show nt) where
sessionPath (R.RecomputeListChart ChartBar nt nId lId) = "node/" <> (show nId) <> "/pie?" <> (defaultList lId) <> "&ngramsType=" <> (show nt) qs = joinQueryStrings [ queryParam "type" n
sessionPath (R.RecomputeListChart ChartPie nt nId lId) = "node/" <> (show nId) <> "/pie?" <> (defaultList lId) <> "&ngramsType=" <> (show nt) , queryParam "offset" o
sessionPath (R.RecomputeListChart ChartTree nt nId lId) = "node/" <> (show nId) <> "/tree?" <> (defaultList lId) <> "&ngramsType=" <> (show nt) <> "&listType=" <> show MapTerm , queryParam "limit" l
sessionPath (R.RecomputeListChart Histo nt nId lId) = "node/" <> (show nId) <> "/chart?" <> (defaultList lId) <> "&ngramsType=" <> (show nt) , queryParam "order" s ]
sessionPath (R.RecomputeListChart Scatter nt nId lId) = "node/" <> (show nId) <> "/metrics?" <> (defaultList lId) <> "&ngramsType=" <> (show nt)
sessionPath (R.RecomputeListChart _ nt nId lId) = "node/" <> (show nId) <> "/recompute-chart?" <> (defaultList lId) <> "&ngramsType=" <> (show nt) sessionPath (R.RecomputeNgrams nt nId lId) = "node/" <> (show nId) <> "/ngrams/recompute" <> qs
where
qs = joinQueryStrings [ queryParam "list" lId
, queryParam "ngramsType" nt ]
sessionPath (R.RecomputeListChart ChartBar nt nId lId) = "node/" <> (show nId) <> "/pie" <> qs
where
qs = joinQueryStrings [ queryParam "list" lId
, queryParam "ngramsType" nt ]
sessionPath (R.RecomputeListChart ChartPie nt nId lId) = "node/" <> (show nId) <> "/pie" <> qs
where
qs = joinQueryStrings [ queryParam "list" lId
, queryParam "ngramsType" nt ]
sessionPath (R.RecomputeListChart ChartTree nt nId lId) = "node/" <> (show nId) <> "/tree" <> qs
where
qs = joinQueryStrings [ queryParam "list" lId
, queryParam "ngramsType" nt
, queryParam "listType" MapTerm ]
sessionPath (R.RecomputeListChart Histo nt nId lId) = "node/" <> (show nId) <> "/chart" <> qs
where
qs = joinQueryStrings [ queryParam "list" lId
, queryParam "ngramsType" nt ]
sessionPath (R.RecomputeListChart Scatter nt nId lId) = "node/" <> (show nId) <> "/metrics" <> qs
where
qs = joinQueryStrings [ queryParam "list" lId
, queryParam "ngramsType" nt ]
sessionPath (R.RecomputeListChart _ nt nId lId) = "node/" <> (show nId) <> "/recompute-chart" <> qs
where
qs = joinQueryStrings [ queryParam "list" lId
, queryParam "ngramsType" nt ]
sessionPath (R.GraphAPI gId p) = "graph/" <> (show gId) <> "/" <> p sessionPath (R.GraphAPI gId p) = "graph/" <> (show gId) <> "/" <> p
sessionPath (R.GetNgrams opts i) = sessionPath (R.GetNgrams opts i) =
base opts.tabType base opts.tabType $ "ngrams" <> qs
$ "ngrams?ngramsType=" <> showTabType' opts.tabType
<> limitUrl opts.limit
<> offset opts.offset
<> orderByUrl opts.orderBy
<> foldMap (\x -> if x /= 0 then "&list=" <> show x else "") opts.listIds
<> foldMap (\x -> "&listType=" <> show x) opts.termListFilter
<> foldMap termSizeFilter opts.termSizeFilter
<> search opts.searchQuery
where where
base (TabCorpus _) = sessionPath <<< R.NodeAPI Node i base (TabCorpus _) = sessionPath <<< R.NodeAPI Node i
base _ = sessionPath <<< R.NodeAPI Url_Document i base _ = sessionPath <<< R.NodeAPI Url_Document i
offset Nothing = ""
offset (Just o) = offsetUrl o qs = joinQueryStrings ( [ queryParamS "ngramsType" $ showTabType' opts.tabType
termSizeFilter MonoTerm = "&minTermSize=0&maxTermSize=1" , queryParam "limit" opts.limit
termSizeFilter MultiTerm = "&minTermSize=2" , mQueryParam "orderBy" opts.orderBy
search "" = "" , mQueryParam "offset" opts.offset
search s = "&search=" <> s , mQueryParam "listType" opts.termListFilter ]
<> listIds
<> termSizeFilter opts.termSizeFilter
<> search opts.searchQuery )
listIds = (queryParam "list") <$> filter (_ /= 0) opts.listIds
termSizeFilter Nothing = []
termSizeFilter (Just MonoTerm) = [ queryParam "minTermSize" 0, queryParam "maxTermSize" 1 ]
termSizeFilter (Just MultiTerm) = [ queryParam "minTermSize" 2 ]
search "" = []
search s = [ queryParamS "search" s ]
sessionPath (R.GetNgramsTableAll opts i) = sessionPath (R.GetNgramsTableAll opts i) =
sessionPath $ R.NodeAPI Node i sessionPath $ R.NodeAPI Node i $ "ngrams" <> qs
$ "ngrams?ngramsType=" where
<> showTabType' opts.tabType qs = joinQueryStrings ([ queryParamS "ngramsType" $ showTabType' opts.tabType
<> foldMap (\x -> "&list=" <> show x) opts.listIds , queryParam "limit" 100000 ] <> list)
<> limitUrl 100000 list = (queryParam "list") <$> opts.listIds
sessionPath (R.GetNgramsTableVersion opts i) = sessionPath (R.GetNgramsTableVersion opts i) =
sessionPath $ R.NodeAPI Node i sessionPath $ R.NodeAPI Node i $ "ngrams/version" <> qs
$ "ngrams/version?ngramsType="
<> showTabType' opts.tabType
<> "&list=" <> show opts.listId
-- $ "ngrams/version?" -- $ "ngrams/version?"
-- <> "list=" <> show opts.listId -- <> "list=" <> show opts.listId
where
qs = joinQueryStrings [ queryParamS "ngramsType" $ showTabType' opts.tabType
, queryParam "list" opts.listId ]
sessionPath (R.ListDocument lId dId) = sessionPath (R.ListDocument lId dId) =
sessionPath $ R.NodeAPI NodeList lId ("document/" <> (show $ fromMaybe 0 dId)) sessionPath $ R.NodeAPI NodeList lId ("document/" <> (show $ fromMaybe 0 dId))
sessionPath (R.ListsRoute lId) = "lists/" <> show lId sessionPath (R.ListsRoute lId) = "lists/" <> show lId
sessionPath (R.PutNgrams t listId termList i) = sessionPath (R.PutNgrams t listId termList i) =
sessionPath $ R.NodeAPI Node i sessionPath $ R.NodeAPI Node i $ "ngrams" <> qs
$ "ngrams?ngramsType=" where
<> showTabType' t qs = joinQueryStrings [ queryParamS "ngramsType" $ showTabType' t
<> maybe "" (\x -> "&list=" <> show x) listId , mQueryParam "list" listId
<> foldMap (\x -> "&listType=" <> show x) termList , mQueryParam "listType" termList ]
sessionPath (R.PostNgramsChartsAsync i) = sessionPath (R.PostNgramsChartsAsync i) =
sessionPath $ R.NodeAPI Node i $ "ngrams/async/charts/update" sessionPath $ R.NodeAPI Node i $ "ngrams/async/charts/update"
sessionPath (R.NodeAPI nt i p) = nodeTypePath nt sessionPath (R.NodeAPI nt i p) = nodeTypePath nt
...@@ -148,45 +180,42 @@ sessionPath (R.NodeAPI nt i p) = nodeTypePath nt ...@@ -148,45 +180,42 @@ sessionPath (R.NodeAPI nt i p) = nodeTypePath nt
sessionPath (R.TreeFirstLevel nId p) = nodeTypePath Tree sessionPath (R.TreeFirstLevel nId p) = nodeTypePath Tree
<> (maybe "" (\nId' -> "/" <> show nId') nId) <> "/first-level" <> p <> (maybe "" (\nId' -> "/" <> show nId') nId) <> "/first-level" <> p
sessionPath (R.Search {listId, limit, offset, orderBy} mCorpusId) = sessionPath (R.Search {listId, limit, offset, orderBy} mCorpusId) =
sessionPath $ R.NodeAPI Corpus mCorpusId sessionPath $ R.NodeAPI Corpus mCorpusId $ "search" <> qs
$ "search?list_id=" <> show listId where
<> offsetUrl offset qs = joinQueryStrings [ queryParam "list_id" listId
<> limitUrl limit , queryParam "offset" offset
<> orderUrl orderBy , queryParam "limit" limit
, mQueryParam "orderBy" orderBy ]
-- sessionPath (R.Search {listId, limit, offset, orderBy} (Just corpusId)) = -- sessionPath (R.Search {listId, limit, offset, orderBy} (Just corpusId)) =
-- "search/" <> (show corpusId) <> "/list/" <> (show listId) <> "?" -- "search/" <> (show corpusId) <> "/list/" <> (show listId) <> "?"
-- <> offsetUrl offset -- <> offsetUrl offset
-- <> limitUrl limit -- <> limitUrl limit
-- <> orderUrl orderBy -- <> orderUrl orderBy
sessionPath (R.CorpusMetrics { listId, limit, tabType} i) = sessionPath (R.CorpusMetrics { listId, limit, tabType} i) =
sessionPath $ R.NodeAPI Corpus i sessionPath $ R.NodeAPI Corpus i $ "metrics" <> qs
$ "metrics" where
<> "?ngrams=" <> show listId qs = joinQueryStrings [ queryParam "ngrams" listId
<> "&ngramsType=" <> showTabType' tabType , queryParamS "ngramsType" $ showTabType' tabType
<> maybe "" limitUrl limit , mQueryParam "limit" limit ]
sessionPath (R.CorpusMetricsHash { listId, tabType} i) = sessionPath (R.CorpusMetricsHash { listId, tabType} i) =
sessionPath $ R.NodeAPI Corpus i sessionPath $ R.NodeAPI Corpus i $ "metrics/hash" <> qs
$ "metrics/hash" where
<> "?ngrams=" <> show listId qs = joinQueryStrings [ queryParam "ngrams" listId
<> "&ngramsType=" <> showTabType' tabType , queryParamS "ngramsType" $ showTabType' tabType ]
-- TODO fix this url path -- TODO fix this url path
sessionPath (R.Chart {chartType, limit, listId, tabType} i) = sessionPath (R.Chart {chartType, limit, listId, tabType} i) =
sessionPath $ R.NodeAPI Corpus i sessionPath $ R.NodeAPI Corpus i $ show chartType <> qs
$ show chartType where
<> "?ngramsType=" <> showTabType' tabType qs = joinQueryStrings [ queryParamS "ngramsType" $ showTabType' tabType
<> "&listType=" <> show MapTerm -- listId , queryParam "listType" MapTerm
<> defaultListAddMaybe listId , mQueryParam "list" listId ]
where
limitPath = case limit of
Just li -> "&limit=" <> show li
Nothing -> ""
-- <> maybe "" limitUrl limit -- <> maybe "" limitUrl limit
sessionPath (R.ChartHash { chartType, listId, tabType } i) = sessionPath (R.ChartHash { chartType, listId, tabType } i) =
sessionPath $ R.NodeAPI Corpus i sessionPath $ R.NodeAPI Corpus i $ show chartType <> "/hash" <> qs
$ show chartType where
<> "/hash?ngramsType=" <> showTabType' tabType qs = joinQueryStrings [ queryParamS "ngramsType" $ showTabType' tabType
<> "&listType=" <> show MapTerm -- listId , queryParam "listType" MapTerm
<> defaultListAddMaybe listId , mQueryParam "list" listId ]
-- sessionPath (R.NodeAPI (NodeContact s a i) i) = sessionPath $ "annuaire/" <> show a <> "/contact/" <> show i -- sessionPath (R.NodeAPI (NodeContact s a i) i) = sessionPath $ "annuaire/" <> show a <> "/contact/" <> show i
sessionPath (R.PhyloAPI nId) = "node/" <> show nId <> "/phylo" sessionPath (R.PhyloAPI nId) = "node/" <> show nId <> "/phylo"
sessionPath R.Members = "members" sessionPath R.Members = "members"
......
...@@ -35,34 +35,8 @@ data AppRoute ...@@ -35,34 +35,8 @@ data AppRoute
| UserPage SessionId Int | UserPage SessionId Int
| ForgotPassword (M.Map String String) | ForgotPassword (M.Map String String)
derive instance Eq AppRoute derive instance Eq AppRoute
data SessionRoute
= Tab TabType (Maybe Id)
| Children NodeType Offset Limit (Maybe OrderBy) (Maybe Id)
| GetNgrams NgramsGetOpts (Maybe Id)
| GetNgramsTableAll NgramsGetTableAllOpts (Maybe Id)
| GetNgramsTableVersion { listId :: ListId, tabType :: TabType } (Maybe Id)
| PutNgrams TabType (Maybe ListId) (Maybe TermList) (Maybe Id)
| PostNgramsChartsAsync (Maybe Id)
-- ^ This name is not good. In particular this URL is used both in PUT and POST.
| RecomputeNgrams (TabSubType CTabNgramType) Id ListId
| RecomputeListChart ChartType CTabNgramType Id ListId
| NodeAPI NodeType (Maybe Id) String
| TreeFirstLevel (Maybe Id) String
| GraphAPI Id String
| ListsRoute ListId
| ListDocument (Maybe ListId) (Maybe DocId)
| Search SearchOpts (Maybe Id)
| CorpusMetrics CorpusMetricOpts (Maybe Id)
| CorpusMetricsHash { listId :: ListId, tabType :: TabType } (Maybe Id)
| Chart ChartOpts (Maybe Id)
| ChartHash { chartType :: ChartType, listId :: Maybe ListId, tabType :: TabType } (Maybe Id)
-- | AnnuaireContact AnnuaireId DocId
| PhyloAPI Id
| Members
instance Show AppRoute where instance Show AppRoute where
show Home = "Home" show Home = "Home"
show Login = "Login" show Login = "Login"
...@@ -140,6 +114,32 @@ nodeTypeAppRoute GT.NodeFrameVisio s i = Just $ RouteFrameVisio s i ...@@ -140,6 +114,32 @@ nodeTypeAppRoute GT.NodeFrameVisio s i = Just $ RouteFrameVisio s i
nodeTypeAppRoute _ _ _ = Nothing nodeTypeAppRoute _ _ _ = Nothing
data SessionRoute
= Tab TabType (Maybe Id)
| Children NodeType Offset Limit (Maybe OrderBy) (Maybe Id)
| GetNgrams NgramsGetOpts (Maybe Id)
| GetNgramsTableAll NgramsGetTableAllOpts (Maybe Id)
| GetNgramsTableVersion { listId :: ListId, tabType :: TabType } (Maybe Id)
| PutNgrams TabType (Maybe ListId) (Maybe TermList) (Maybe Id)
| PostNgramsChartsAsync (Maybe Id)
-- ^ This name is not good. In particular this URL is used both in PUT and POST.
| RecomputeNgrams (TabSubType CTabNgramType) Id ListId
| RecomputeListChart ChartType CTabNgramType Id ListId
| NodeAPI NodeType (Maybe Id) String
| TreeFirstLevel (Maybe Id) String
| GraphAPI Id String
| ListsRoute ListId
| ListDocument (Maybe ListId) (Maybe DocId)
| Search SearchOpts (Maybe Id)
| CorpusMetrics CorpusMetricOpts (Maybe Id)
| CorpusMetricsHash { listId :: ListId, tabType :: TabType } (Maybe Id)
| Chart ChartOpts (Maybe Id)
| ChartHash { chartType :: ChartType, listId :: Maybe ListId, tabType :: TabType } (Maybe Id)
-- | AnnuaireContact AnnuaireId DocId
| PhyloAPI Id
| Members
------------------------------------------------------ ------------------------------------------------------
type Tile = type Tile =
......
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