Commit 7cdf92d2 authored by Nicolas Pouillard's avatar Nicolas Pouillard

WIP

parent 82a95f5d
...@@ -332,7 +332,8 @@ loadedNgramsTableSpec = Thermite.simpleSpec performAction render ...@@ -332,7 +332,8 @@ loadedNgramsTableSpec = Thermite.simpleSpec performAction render
render dispatch { path: path@({searchQuery, scoreType, params, termListFilter} /\ setPath) render dispatch { path: path@({searchQuery, scoreType, params, termListFilter} /\ setPath)
, versioned: Versioned { data: initTable } , versioned: Versioned { data: initTable }
, tabNgramType } , tabNgramType }
state@{ ngramsParent, ngramsChildren, ngramsLocalPatch state@{ ngramsParent, ngramsChildren
, ngramsLocalPatch, ngramsStagePatch, ngramsValidPatch
, ngramsSelection, ngramsSelectAll } , ngramsSelection, ngramsSelectAll }
_reactChildren = _reactChildren =
[ autoUpdateElt { duration: 3000, effect: dispatch Synchronize } [ autoUpdateElt { duration: 3000, effect: dispatch Synchronize }
...@@ -394,9 +395,15 @@ loadedNgramsTableSpec = Thermite.simpleSpec performAction render ...@@ -394,9 +395,15 @@ loadedNgramsTableSpec = Thermite.simpleSpec performAction render
-- ^ unless they are scheduled to be removed. -- ^ unless they are scheduled to be removed.
|| tablePatchHasNgrams ngramsLocalPatch ngrams || tablePatchHasNgrams ngramsLocalPatch ngrams
-- ^ unless they are being processed at the moment. -- ^ unless they are being processed at the moment.
|| tablePatchHasNgrams ngramsStagePatch ngrams
-- ^ unless they are being processed at the moment.
|| tablePatchHasNgrams ngramsValidPatch ngrams
-- ^ unless they are part of our local patches.
convertRow (Tuple ngrams ngramsElement) = convertRow (Tuple ngrams ngramsElement) =
{ row: R2.buff <$> renderNgramsItem { ngramsTable, ngrams, { row: R2.buff <$> renderNgramsItem { ngramsTable, ngrams,
ngramsLocalPatch, ngramsLocalPatch,
ngramsStagePatch,
ngramsValidPatch,
ngramsParent, ngramsElement, ngramsParent, ngramsElement,
ngramsSelection, dispatch } ngramsSelection, dispatch }
, delete: false , delete: false
......
...@@ -616,7 +616,7 @@ postNewNgrams newNgrams mayList {nodeId, listIds, tabType, session} = ...@@ -616,7 +616,7 @@ postNewNgrams newNgrams mayList {nodeId, listIds, tabType, session} =
when (not (A.null newNgrams)) $ do when (not (A.null newNgrams)) $ do
(_ :: Array Unit) <- post session p newNgrams (_ :: Array Unit) <- post session p newNgrams
pure unit pure unit
where p = PutNgrams tabType (head listIds) mayList (Just nodeId) where p = PostNgrams tabType (head listIds) mayList (Just nodeId)
postNewElems :: forall s. NewElems -> CoreParams s -> Aff Unit postNewElems :: forall s. NewElems -> CoreParams s -> Aff Unit
postNewElems newElems params = void $ traverseWithIndex postNewElem newElems postNewElems newElems params = void $ traverseWithIndex postNewElem newElems
...@@ -630,7 +630,7 @@ addNewNgram ngrams list = ...@@ -630,7 +630,7 @@ addNewNgram ngrams list =
putNgramsPatches :: forall s. CoreParams s -> VersionedNgramsPatches -> Aff VersionedNgramsPatches putNgramsPatches :: forall s. CoreParams s -> VersionedNgramsPatches -> Aff VersionedNgramsPatches
putNgramsPatches {session, nodeId, listIds, tabType} = put session putNgrams putNgramsPatches {session, nodeId, listIds, tabType} = put session putNgrams
where putNgrams = PutNgrams tabType (head listIds) Nothing (Just nodeId) where putNgrams = PutNgrams tabType (unsafePartial $ head listIds) (Just nodeId)
syncPatches :: forall p s. CoreParams p -> CoreState s -> StateCoTransformer (CoreState s) Unit syncPatches :: forall p s. CoreParams p -> CoreState s -> StateCoTransformer (CoreState s) Unit
syncPatches props { ngramsLocalPatch: ngramsLocalPatch@{ngramsNewElems, ngramsPatches} syncPatches props { ngramsLocalPatch: ngramsLocalPatch@{ngramsNewElems, ngramsPatches}
......
...@@ -9,7 +9,9 @@ import Data.Generic.Rep (class Generic) ...@@ -9,7 +9,9 @@ import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Eq (genericEq) import Data.Generic.Rep.Eq (genericEq)
import Data.Maybe (Maybe(..), maybe) import Data.Maybe (Maybe(..), maybe)
import Gargantext.Routes as R import Gargantext.Routes as R
import Gargantext.Types (ApiVersion, Limit, NodePath, NodeType(..), Offset, TabType(..), TermSize(..), nodePath, nodeTypePath, showTabType') import Gargantext.Types (ApiVersion, Limit, NodePath, NodeType(..), Offset,
TabType(..), TermSize(..), nodePath, nodeTypePath, showTabType', ListId,
TermList)
import Prelude (class Eq, class Show, identity, show, ($), (<>), bind, pure, (<<<), (==)) import Prelude (class Eq, class Show, identity, show, ($), (<>), bind, pure, (<<<), (==))
-- | A means of generating a url to visit, a destination -- | A means of generating a url to visit, a destination
...@@ -124,8 +126,8 @@ sessionPath (R.GetNgrams opts i) = ...@@ -124,8 +126,8 @@ sessionPath (R.GetNgrams opts i) =
<> offsetUrl opts.offset <> offsetUrl opts.offset
<> limitUrl opts.limit <> limitUrl opts.limit
<> orderByUrl opts.orderBy <> orderByUrl opts.orderBy
<> foldMap (\x -> "&list=" <> show x) opts.listIds <> foldMap listUrl opts.listIds
<> foldMap (\x -> "&listType=" <> show x) opts.termListFilter <> foldMap listTypeUrl opts.termListFilter
<> foldMap termSizeFilter opts.termSizeFilter <> foldMap termSizeFilter opts.termSizeFilter
<> "&scoreType=" <> show opts.scoreType <> "&scoreType=" <> show opts.scoreType
<> search opts.searchQuery <> search opts.searchQuery
...@@ -138,12 +140,17 @@ sessionPath (R.GetNgrams opts i) = ...@@ -138,12 +140,17 @@ sessionPath (R.GetNgrams opts i) =
search s = "&search=" <> s search s = "&search=" <> s
sessionPath (R.ListDocument lId dId) = sessionPath (R.ListDocument lId dId) =
sessionPath $ R.NodeAPI NodeList lId ("document/" <> (show $ maybe 0 identity dId)) sessionPath $ R.NodeAPI NodeList lId ("document/" <> (show $ maybe 0 identity dId))
sessionPath (R.PutNgrams t listId termList i) = sessionPath (R.PutNgrams t listId i) =
sessionPath $ R.NodeAPI Node i sessionPath $ R.NodeAPI Node i
$ "ngrams?ngramsType=" $ "ngrams?ngramsType="
<> showTabType' t <> showTabType' t
<> maybe "" (\x -> "&list=" <> show x) listId <> listUrl listId
<> foldMap (\x -> "&listType=" <> show x) termList sessionPath (R.PostNgrams t listId termList i) =
sessionPath $ R.NodeAPI Node i
$ "ngrams?ngramsType="
<> showTabType' t
<> listUrl listId
<> foldMap listTypeUrl termList
sessionPath (R.NodeAPI nt i p) = nodeTypePath nt sessionPath (R.NodeAPI nt i p) = nodeTypePath nt
<> (maybe "" (\i' -> "/" <> show i') i) <> (maybe "" (\i' -> "/" <> show i') i)
<> (if p == "" then "" else "/" <> p) <> (if p == "" then "" else "/" <> p)
...@@ -193,6 +200,12 @@ orderUrl = maybe "" (\x -> "&order=" <> show x) ...@@ -193,6 +200,12 @@ orderUrl = maybe "" (\x -> "&order=" <> show x)
orderByUrl :: forall a. Show a => Maybe a -> String orderByUrl :: forall a. Show a => Maybe a -> String
orderByUrl = maybe "" (\x -> "&orderBy=" <> show x) orderByUrl = maybe "" (\x -> "&orderBy=" <> show x)
listUrl :: ListId -> String
listUrl l = "&list=" <> show l
listTypeUrl :: TermList -> String
listTypeUrl l = "&listType=" <> show l
-- nodeTypePath :: NodeType -> Path -- nodeTypePath :: NodeType -> Path
-- nodeTypePath = NodeAPI -- nodeTypePath = NodeAPI
......
...@@ -28,8 +28,8 @@ data SessionRoute ...@@ -28,8 +28,8 @@ data SessionRoute
= Tab TabType (Maybe Id) = Tab TabType (Maybe Id)
| Children NodeType Offset Limit (Maybe OrderBy) (Maybe Id) | Children NodeType Offset Limit (Maybe OrderBy) (Maybe Id)
| GetNgrams NgramsGetOpts (Maybe Id) | GetNgrams NgramsGetOpts (Maybe Id)
| PutNgrams TabType (Maybe ListId) (Maybe TermList) (Maybe Id) | PutNgrams TabType ListId (Maybe Id)
-- ^ This name is not good. In particular this URL is used both in PUT and POST. | PostNgrams TabType ListId (Maybe TermList) (Maybe Id)
| NodeAPI NodeType (Maybe Id) String | NodeAPI NodeType (Maybe Id) String
| ListDocument (Maybe ListId) (Maybe Id) | ListDocument (Maybe ListId) (Maybe Id)
| Search SearchOpts (Maybe Id) | Search SearchOpts (Maybe Id)
......
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