Commit 9d2cb1ee authored by Nicolas Pouillard's avatar Nicolas Pouillard

WIP

parent 3e4ae118
......@@ -89,28 +89,30 @@ import Gargantext.Sessions (Session, get, put, post)
import Gargantext.Types (OrderBy(..), CTabNgramType(..), TabType, TermList(..), TermSize)
import Gargantext.Utils.KarpRabin (indicesOfAny)
-- TODO the name is misleading
data NodeId = NodeId { corpusId :: Int
, documentId :: Maybe Int
}
type CoreParams s =
{ nodeId :: NodeId
type CoreParams nodeId extra =
{ nodeId :: nodeId
-- ^ This node can be a corpus or contact.
, listIds :: Array Int
, tabType :: TabType
, session :: Session
| s
| extra
}
type PageParams =
type PageParams nodeId =
CoreParams
nodeId
( params :: T.Params
, searchQuery :: String
, termListFilter :: Maybe TermList -- Nothing means all
, termSizeFilter :: Maybe TermSize -- Nothing means all
)
initialPageParams :: Session -> Int -> Array Int -> TabType -> PageParams
initialPageParams :: forall nodeId. Session -> nodeId -> Array Int -> TabType -> PageParams nodeId
initialPageParams session nodeId listIds tabType =
{ nodeId
, listIds
......@@ -564,14 +566,14 @@ type CoreState s =
| s
}
postNewNgrams :: forall s. Array NgramsTerm -> Maybe TermList -> CoreParams s -> Aff Unit
postNewNgrams :: forall n s. Array NgramsTerm -> Maybe TermList -> CoreParams n s -> Aff Unit
postNewNgrams newNgrams mayList {nodeId, listIds, tabType, session} =
when (not (A.null newNgrams)) $ do
(_ :: Array Unit) <- post session p newNgrams
pure unit
where p = PutNgrams tabType (head listIds) mayList (Just nodeId)
postNewElems :: forall s. NewElems -> CoreParams s -> Aff Unit
postNewElems :: forall n s. NewElems -> CoreParams n s -> Aff Unit
postNewElems newElems params = void $ traverseWithIndex postNewElem newElems
where
postNewElem ngrams list = postNewNgrams [ngrams] (Just list) params
......@@ -580,11 +582,12 @@ addNewNgram :: CTabNgramType -> NgramsTerm -> TermList -> NgramsTablePatch
addNewNgram ntype ngrams list = { ngramsPatches: mempty
, ngramsNewElems: Map.singleton (normNgram ntype ngrams) list }
putNgramsPatches :: forall s. CoreParams s -> Versioned NgramsPatches -> Aff (Versioned NgramsPatches)
-- TODO putNgramsPatches :: forall s. CoreParams Int s -> Versioned NgramsPatches -> Aff (Versioned NgramsPatches)
putNgramsPatches :: forall n s. CoreParams n s -> Versioned NgramsPatches -> Aff (Versioned NgramsPatches)
putNgramsPatches {session, nodeId, listIds, tabType} = put session putNgrams
where putNgrams = PutNgrams tabType (head listIds) Nothing (Just nodeId)
commitPatch :: forall p s. CoreParams p
commitPatch :: forall n p s. CoreParams n p
-> Versioned NgramsTablePatch -> StateCoTransformer (CoreState s) Unit
commitPatch props (Versioned {version, data: tablePatch@{ngramsPatches, ngramsNewElems}}) = do
let pt = Versioned { version, data: ngramsPatches }
......@@ -596,7 +599,7 @@ commitPatch props (Versioned {version, data: tablePatch@{ngramsPatches, ngramsNe
}
-- TODO: check that pt.version == s.ngramsTablePatch.version
loadNgramsTable :: PageParams -> Aff VersionedNgramsTable
loadNgramsTable :: PageParams NodeId -> Aff VersionedNgramsTable
loadNgramsTable
{ nodeId, listIds, termListFilter, termSizeFilter, session
, searchQuery, tabType, params: {offset, limit, orderBy}}
......@@ -604,9 +607,9 @@ loadNgramsTable
where
NodeId {corpusId, documentId} = nodeId
query = GetNgrams { tabType, offset, limit, listIds
, orderBy: convOrderBy <$> orderBy
, termListFilter, termSizeFilter
, searchQuery } (Just corpusId) documentId
, orderBy: convOrderBy <$> orderBy
, termListFilter, termSizeFilter
, searchQuery } (Just corpusId) documentId
convOrderBy :: T.OrderByDirection T.ColumnName -> OrderBy
convOrderBy (T.ASC (T.ColumnName "Score (Occurrences)")) = ScoreAsc
......
......@@ -369,14 +369,14 @@ documentLayoutCpt = R.hooksComponent "G.P.Corpus.Document.documentLayout" cpt
------------------------------------------------------------------------
loadDocument :: Session -> Maybe Int -> Int -> Aff NodeDocument
loadDocument session corpusId nodeId =
get session $ SessionCorpusDocument corpusId (Just nodeId)
get session $ CorpusDocumentAPI corpusId (Just nodeId)
loadData :: DocPath -> Aff LoadedData
loadData {session, nodeId, corpusId, listIds, tabType} = do
document <- loadDocument session corpusId nodeId
ngramsTable <- loadNgramsTable
{ session
, NodeId corpusId (Just nodeId)
-- , NodeId corpusId (Just nodeId)
, listIds
, params: { offset : 0, limit : 100, orderBy: Nothing}
, tabType
......
......@@ -14,6 +14,12 @@ import Gargantext.Types
( ApiVersion, Limit, NodePath, NodeType(..), Offset, TabType(..)
, TermSize(..), nodePath, nodeTypePath, showTabType')
joinUrl :: String -> String -> String
joinUrl p "" = p
joinUrl p q = p <> "/" <> q
infixr 5 joinUrl as </>
-- | A means of generating a url to visit, a destination
class ToUrl conf p where
toUrl :: conf -> p -> String
......@@ -33,7 +39,7 @@ backend version prePath baseUrl name = Backend { name, version, prePath, baseUrl
-- | Creates a backend url from a backend and the path as a string
backendUrl :: Backend -> String -> String
backendUrl (Backend b) path = b.baseUrl <> b.prePath <> show b.version <> "/" <> path
backendUrl (Backend b) path = b.baseUrl <> b.prePath <> show b.version </> path
derive instance genericBackend :: Generic Backend _
......@@ -117,7 +123,7 @@ sessionPath :: R.SessionRoute -> String
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.NodeAPI Phylo pId p) = "phyloscape?nodeId=" <> (show $ maybe 0 identity pId) <> p
sessionPath (R.GetNgrams opts c i) =
sessionPath (R.GetNgrams opts) =
base opts.tabType
$ "ngrams?ngramsType="
<> showTabType' opts.tabType
......@@ -129,24 +135,26 @@ sessionPath (R.GetNgrams opts c i) =
<> foldMap termSizeFilter opts.termSizeFilter
<> search opts.searchQuery
where
base :: TabType -> String
base (TabCorpus _) = sessionPath <<< R.NodeAPI Node c
base _ = sessionPath <<< (R.SessionCorpusDocument c i)
base :: TabType -> String -> String
base (TabCorpus _) = case opts.nodeId of
-- Just _ -> error
Nothing -> sessionPath <<< R.NodeAPI Node opts.corpusId
base _ = sessionPath <<< R.CorpusDocumentAPI opts.corpusId opts.nodeId
termSizeFilter MonoTerm = "&minTermSize=0&maxTermSize=1"
termSizeFilter MultiTerm = "&minTermSize=2"
search "" = ""
search s = "&search=" <> s
sessionPath (R.SessionCorpusDocument cId dId) =
sessionPath $ R.NodeAPI Corpus cId ("document/" <> (show $ maybe 0 identity dId))
sessionPath (R.PutNgrams t listId termList i) =
sessionPath (R.CorpusDocumentAPI cId dId p) =
sessionPath $ R.NodeAPI Corpus cId $ "document" </> show (maybe 0 identity dId) </> p
sessionPath (R.PutNgrams {tabType, listId, termList, nodeId, corpusId}) =
sessionPath $ R.NodeAPI Node i
$ "ngrams?ngramsType="
<> showTabType' t
<> showTabType' tabType
<> maybe "" (\x -> "&list=" <> show x) listId
<> foldMap (\x -> "&listType=" <> show x) termList
sessionPath (R.NodeAPI nt i p) = nodeTypePath nt
<> (maybe "" (\i' -> "/" <> show i') i)
<> (if p == "" then "" else "/" <> p)
</> maybe "" show i
</> p
sessionPath (R.Search {listId,limit,offset,orderBy} i) =
sessionPath $ R.NodeAPI Corpus i
$ "search?list_id=" <> show listId
......
......@@ -2,7 +2,7 @@ module Gargantext.Routes where
import Prelude
import Data.Maybe (Maybe)
import Gargantext.Types (ChartOpts, CorpusMetricOpts, Id, Limit, ListId, NgramsGetOpts, NodeType, Offset, OrderBy, SearchOpts, SessionId, TabType, TermList)
import Gargantext.Types (ChartOpts, CorpusMetricOpts, Id, Limit, ListId, NgramsGetParams, NgramsPutParams, NodeType, Offset, OrderBy, SearchOpts, SessionId, TabType, TermList)
data AppRoute
= Home
......@@ -19,14 +19,15 @@ data AppRoute
| UserPage SessionId Int
| ContactPage SessionId Int
-- TODO renaming suggestion RouteAPI?
data SessionRoute
= Tab TabType (Maybe Id)
| Children NodeType Offset Limit (Maybe OrderBy) (Maybe Id)
| GetNgrams NgramsGetOpts (Maybe Id) (Maybe Id)
| PutNgrams TabType (Maybe ListId) (Maybe TermList) (Maybe Id)
| GetNgrams NgramsGetParams
| PutNgrams NgramsPutParams
-- ^ This name is not good. In particular this URL is used both in PUT and POST.
| NodeAPI NodeType (Maybe Id) String
| SessionCorpusDocument (Maybe Id) (Maybe Id)
| CorpusDocumentAPI (Maybe Id) (Maybe Id) String
| Search SearchOpts (Maybe Id)
| CorpusMetrics CorpusMetricOpts (Maybe Id)
| Chart ChartOpts (Maybe Id)
......
......@@ -267,7 +267,7 @@ nodeTypePath Team = "team"
type ListId = Int
type NgramsGetOpts =
type NgramsGetParams =
{ tabType :: TabType
, offset :: Offset
, limit :: Limit
......@@ -276,6 +276,16 @@ type NgramsGetOpts =
, termListFilter :: Maybe TermList
, termSizeFilter :: Maybe TermSize
, searchQuery :: String
, corpusId :: Maybe Id
, nodeId :: Maybe Id
}
type NgramsPutParams =
{ tabType :: TabType
, listId :: Maybe ListId
, termList :: Maybe TermList
, corpusId :: Maybe Id
, nodeId :: Maybe Id
}
type SearchOpts =
......
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