Commit 09db4e19 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[FIX] GraphTerm -> MapTerm

parent 83807ead
...@@ -38,7 +38,7 @@ annotationMenuCpt :: R.Component Props ...@@ -38,7 +38,7 @@ annotationMenuCpt :: R.Component Props
annotationMenuCpt = R.hooksComponent "Annotation.Menu" cpt annotationMenuCpt = R.hooksComponent "Annotation.Menu" cpt
where where
cpt props _ = pure $ R.fragment $ children props cpt props _ = pure $ R.fragment $ children props
children props = A.mapMaybe (addToList props) [ GraphTerm, CandidateTerm, StopTerm ] children props = A.mapMaybe (addToList props) [ MapTerm, CandidateTerm, StopTerm ]
-- | Given the TermList to render the item for zand the Maybe TermList the item may belong to, possibly render the menuItem -- | Given the TermList to render the item for zand the Maybe TermList the item may belong to, possibly render the menuItem
addToList :: Record Props -> TermList -> Maybe R.Element addToList :: Record Props -> TermList -> Maybe R.Element
......
...@@ -3,11 +3,11 @@ module Gargantext.Components.Annotation.Utils where ...@@ -3,11 +3,11 @@ module Gargantext.Components.Annotation.Utils where
import Gargantext.Types ( TermList(..) ) import Gargantext.Types ( TermList(..) )
termClass :: TermList -> String termClass :: TermList -> String
termClass GraphTerm = "graph-term" termClass MapTerm = "graph-term"
termClass StopTerm = "stop-term" termClass StopTerm = "stop-term"
termClass CandidateTerm = "candidate-term" termClass CandidateTerm = "candidate-term"
termBootstrapClass :: TermList -> String termBootstrapClass :: TermList -> String
termBootstrapClass GraphTerm = "success" termBootstrapClass MapTerm = "success"
termBootstrapClass StopTerm = "danger" termBootstrapClass StopTerm = "danger"
termBootstrapClass CandidateTerm = "warning" termBootstrapClass CandidateTerm = "warning"
...@@ -25,7 +25,7 @@ mergeNode p@{dispatch, subTreeParams, id, nodeType, session} = do ...@@ -25,7 +25,7 @@ mergeNode p@{dispatch, subTreeParams, id, nodeType, session} = do
<- R.useState' Nothing <- R.useState' Nothing
merge <- R.useState' false merge <- R.useState' false
options <- R.useState' (Set.singleton GT.GraphTerm) options <- R.useState' (Set.singleton GT.MapTerm)
let button = case subTreeOutParams of let button = case subTreeOutParams of
Nothing -> H.div {} [] Nothing -> H.div {} []
...@@ -41,7 +41,7 @@ mergeNode p@{dispatch, subTreeParams, id, nodeType, session} = do ...@@ -41,7 +41,7 @@ mergeNode p@{dispatch, subTreeParams, id, nodeType, session} = do
, session , session
} }
, H.div {} [ H.text "Merge which list?" , H.div {} [ H.text "Merge which list?"
, checkboxes [GT.GraphTerm, GT.CandidateTerm, GT.StopTerm] options , checkboxes [GT.MapTerm, GT.CandidateTerm, GT.StopTerm] options
] ]
, H.div {className: "checkbox"} [checkbox merge, H.text "Merge data?"] , H.div {className: "checkbox"} [checkbox merge, H.text "Merge data?"]
] button ] button
......
...@@ -187,7 +187,7 @@ deleteNode termList session (GET.MetaData metaData) node = NTC.putNgramsPatches ...@@ -187,7 +187,7 @@ deleteNode termList session (GET.MetaData metaData) node = NTC.putNgramsPatches
np :: NTC.NgramsPatches np :: NTC.NgramsPatches
np = NTC.singletonPatchMap term $ NTC.NgramsPatch { patch_children: mempty, patch_list } np = NTC.singletonPatchMap term $ NTC.NgramsPatch { patch_children: mempty, patch_list }
patch_list :: NTC.Replace TermList patch_list :: NTC.Replace TermList
patch_list = NTC.Replace { new: termList, old: GraphTerm } patch_list = NTC.Replace { new: termList, old: MapTerm }
query :: Frontends -> GET.MetaData -> Session -> SigmaxT.NodesMap -> R.State SigmaxT.NodeIds -> R.Element query :: Frontends -> GET.MetaData -> Session -> SigmaxT.NodesMap -> R.State SigmaxT.NodeIds -> R.Element
......
...@@ -256,7 +256,7 @@ tableContainerCpt { dispatch ...@@ -256,7 +256,7 @@ tableContainerCpt { dispatch
selectButtons true = selectButtons true =
H.div {} [ H.div {} [
H.button { className: "btn btn-primary" H.button { className: "btn btn-primary"
, on: { click: const $ setSelection GraphTerm } , on: { click: const $ setSelection MapTerm }
} [ H.text "Map" ] } [ H.text "Map" ]
, H.button { className: "btn btn-primary" , H.button { className: "btn btn-primary"
, on: { click: const $ setSelection StopTerm } , on: { click: const $ setSelection StopTerm }
......
...@@ -183,7 +183,7 @@ renderNgramsItemCpt = R.hooksComponent "G.C.NT.renderNgramsItem" cpt ...@@ -183,7 +183,7 @@ renderNgramsItemCpt = R.hooksComponent "G.C.NT.renderNgramsItem" cpt
, ngramsTable } _ = , ngramsTable } _ =
pure $ Tbl.makeRow [ pure $ Tbl.makeRow [
selected selected
, checkbox T.GraphTerm , checkbox T.MapTerm
, checkbox T.StopTerm , checkbox T.StopTerm
, if ngramsParent == Nothing , if ngramsParent == Nothing
then renderNgramsTree { ngramsTable, ngrams, ngramsStyle, ngramsClick, ngramsEdit } then renderNgramsTree { ngramsTable, ngrams, ngramsStyle, ngramsClick, ngramsEdit }
...@@ -232,7 +232,7 @@ renderNgramsItemCpt = R.hooksComponent "G.C.NT.renderNgramsItem" cpt ...@@ -232,7 +232,7 @@ renderNgramsItemCpt = R.hooksComponent "G.C.NT.renderNgramsItem" cpt
termStyle :: T.TermList -> Number -> DOM.Props termStyle :: T.TermList -> Number -> DOM.Props
termStyle T.GraphTerm opacity = DOM.style { color: "green", opacity } termStyle T.MapTerm opacity = DOM.style { color: "green", opacity }
termStyle T.StopTerm opacity = DOM.style { color: "red", opacity termStyle T.StopTerm opacity = DOM.style { color: "red", opacity
, textDecoration: "line-through" } , textDecoration: "line-through" }
termStyle T.CandidateTerm opacity = DOM.style { color: "black", opacity } termStyle T.CandidateTerm opacity = DOM.style { color: "black", opacity }
...@@ -250,6 +250,6 @@ tablePatchHasNgrams ngramsTablePatch ngrams = ...@@ -250,6 +250,6 @@ tablePatchHasNgrams ngramsTablePatch ngrams =
nextTermList :: T.TermList -> T.TermList nextTermList :: T.TermList -> T.TermList
nextTermList T.GraphTerm = T.StopTerm nextTermList T.MapTerm = T.StopTerm
nextTermList T.StopTerm = T.CandidateTerm nextTermList T.StopTerm = T.CandidateTerm
nextTermList T.CandidateTerm = T.GraphTerm nextTermList T.CandidateTerm = T.MapTerm
...@@ -133,7 +133,7 @@ initialPageParams session nodeId listIds tabType = ...@@ -133,7 +133,7 @@ initialPageParams session nodeId listIds tabType =
, params , params
, tabType , tabType
, termSizeFilter: Nothing , termSizeFilter: Nothing
, termListFilter: Just GraphTerm , termListFilter: Just MapTerm
, searchQuery: "" , searchQuery: ""
, scoreType: Occurrences , scoreType: Occurrences
, session , session
......
...@@ -86,7 +86,7 @@ scatterOptions metrics' = Options ...@@ -86,7 +86,7 @@ scatterOptions metrics' = Options
color = color =
case k of case k of
StopTerm -> red StopTerm -> red
GraphTerm -> green MapTerm -> green
CandidateTerm -> grey CandidateTerm -> grey
toSerie color' (Metric {label,x,y}) = toSerie color' (Metric {label,x,y}) =
dataSerie { name: label, itemStyle: itemStyle {color: color'} dataSerie { name: label, itemStyle: itemStyle {color: color'}
......
...@@ -58,7 +58,7 @@ type Loaded = HistoMetrics ...@@ -58,7 +58,7 @@ type Loaded = HistoMetrics
chartOptionsBar :: HistoMetrics -> Options chartOptionsBar :: HistoMetrics -> Options
chartOptionsBar (HistoMetrics { dates: dates', count: count'}) = Options chartOptionsBar (HistoMetrics { dates: dates', count: count'}) = Options
{ mainTitle : "Bar" { mainTitle : "Bar"
, subTitle : "Count of GraphTerm" , subTitle : "Count of MapTerm"
, xAxis : xAxis' $ map (\t -> joinWith " " $ map (take 3) $ A.take 3 $ filter (\s -> length s > 3) $ split (Pattern " ") t) dates' , xAxis : xAxis' $ map (\t -> joinWith " " $ map (take 3) $ A.take 3 $ filter (\s -> length s > 3) $ split (Pattern " ") t) dates'
, yAxis : yAxis' { position: "left", show: true, min:0} , yAxis : yAxis' { position: "left", show: true, min:0}
, series : [seriesBarD1 {name: "Number of publication / year"} $ map (\n -> dataSerie {name: "", itemStyle: itemStyle {color:blue}, value: n }) count'] , series : [seriesBarD1 {name: "Number of publication / year"} $ map (\n -> dataSerie {name: "", itemStyle: itemStyle {color:blue}, value: n }) count']
...@@ -69,7 +69,7 @@ chartOptionsBar (HistoMetrics { dates: dates', count: count'}) = Options ...@@ -69,7 +69,7 @@ chartOptionsBar (HistoMetrics { dates: dates', count: count'}) = Options
chartOptionsPie :: HistoMetrics -> Options chartOptionsPie :: HistoMetrics -> Options
chartOptionsPie (HistoMetrics { dates: dates', count: count'}) = Options chartOptionsPie (HistoMetrics { dates: dates', count: count'}) = Options
{ mainTitle : "Pie" { mainTitle : "Pie"
, subTitle : "Distribution by GraphTerm" , subTitle : "Distribution by MapTerm"
, xAxis : xAxis' [] , xAxis : xAxis' []
, yAxis : yAxis' { position: "", show: false, min:0} , yAxis : yAxis' { position: "", show: false, min:0}
, series : [seriesPieD1 {name: "Data"} $ map (\(Tuple n v) -> dataSerie {name: n, value:v}) $ zip dates' count'] , series : [seriesPieD1 {name: "Data"} $ map (\(Tuple n v) -> dataSerie {name: n, value:v}) $ zip dates' count']
......
...@@ -120,7 +120,7 @@ sessionPath (R.NodeAPI Phylo pId p) = "phyloscape?nodeId=" <> (show $ fromMaybe ...@@ -120,7 +120,7 @@ sessionPath (R.NodeAPI Phylo pId p) = "phyloscape?nodeId=" <> (show $ fromMaybe
sessionPath (R.RecomputeNgrams nt nId lId) = "node/" <> (show nId) <> "/ngrams/recompute?list=" <> (show lId) <> "&ngramsType=" <> (show nt) sessionPath (R.RecomputeNgrams nt nId lId) = "node/" <> (show nId) <> "/ngrams/recompute?list=" <> (show lId) <> "&ngramsType=" <> (show nt)
sessionPath (R.RecomputeListChart ChartBar nt nId lId) = "node/" <> (show nId) <> "/pie?list=" <> (show lId) <> "&ngramsType=" <> (show nt) sessionPath (R.RecomputeListChart ChartBar nt nId lId) = "node/" <> (show nId) <> "/pie?list=" <> (show lId) <> "&ngramsType=" <> (show nt)
sessionPath (R.RecomputeListChart ChartPie nt nId lId) = "node/" <> (show nId) <> "/pie?list=" <> (show lId) <> "&ngramsType=" <> (show nt) sessionPath (R.RecomputeListChart ChartPie nt nId lId) = "node/" <> (show nId) <> "/pie?list=" <> (show lId) <> "&ngramsType=" <> (show nt)
sessionPath (R.RecomputeListChart ChartTree nt nId lId) = "node/" <> (show nId) <> "/tree?list=" <> (show lId) <> "&ngramsType=" <> (show nt) <> "&listType=GraphTerm" sessionPath (R.RecomputeListChart ChartTree nt nId lId) = "node/" <> (show nId) <> "/tree?list=" <> (show lId) <> "&ngramsType=" <> (show nt) <> "&listType=MapTerm"
sessionPath (R.RecomputeListChart Histo nt nId lId) = "node/" <> (show nId) <> "/chart?list=" <> (show lId) <> "&ngramsType=" <> (show nt) sessionPath (R.RecomputeListChart Histo nt nId lId) = "node/" <> (show nId) <> "/chart?list=" <> (show lId) <> "&ngramsType=" <> (show nt)
sessionPath (R.RecomputeListChart Scatter nt nId lId) = "node/" <> (show nId) <> "/metrics?list=" <> (show lId) <> "&ngramsType=" <> (show nt) sessionPath (R.RecomputeListChart Scatter nt nId lId) = "node/" <> (show nId) <> "/metrics?list=" <> (show lId) <> "&ngramsType=" <> (show nt)
sessionPath (R.RecomputeListChart _ nt nId lId) = "node/" <> (show nId) <> "/recompute-chart?list=" <> (show lId) <> "&ngramsType=" <> (show nt) sessionPath (R.RecomputeListChart _ nt nId lId) = "node/" <> (show nId) <> "/recompute-chart?list=" <> (show lId) <> "&ngramsType=" <> (show nt)
...@@ -190,7 +190,7 @@ sessionPath (R.Chart {chartType, listId, limit, tabType} i) = ...@@ -190,7 +190,7 @@ sessionPath (R.Chart {chartType, listId, limit, tabType} i) =
sessionPath $ R.NodeAPI Corpus i sessionPath $ R.NodeAPI Corpus i
$ show chartType $ show chartType
<> "?ngramsType=" <> showTabType' tabType <> "?ngramsType=" <> showTabType' tabType
<> "&listType=GraphTerm" -- <> show listId <> "&listType=MapTerm" -- <> show listId
<> "&listId=" <> show listId <> "&listId=" <> show listId
where where
limitPath = case limit of limitPath = case limit of
......
...@@ -56,14 +56,14 @@ termSizes = [ { desc: "All types", mval: Nothing } ...@@ -56,14 +56,14 @@ termSizes = [ { desc: "All types", mval: Nothing }
, { desc: "Multi-word terms", mval: Just MultiTerm } , { desc: "Multi-word terms", mval: Just MultiTerm }
] ]
data TermList = GraphTerm | StopTerm | CandidateTerm data TermList = MapTerm | StopTerm | CandidateTerm
-- TODO use generic JSON instance -- TODO use generic JSON instance
derive instance eqTermList :: Eq TermList derive instance eqTermList :: Eq TermList
derive instance ordTermList :: Ord TermList derive instance ordTermList :: Ord TermList
instance encodeJsonTermList :: EncodeJson TermList where instance encodeJsonTermList :: EncodeJson TermList where
encodeJson GraphTerm = encodeJson "GraphTerm" encodeJson MapTerm = encodeJson "MapTerm"
encodeJson StopTerm = encodeJson "StopTerm" encodeJson StopTerm = encodeJson "StopTerm"
encodeJson CandidateTerm = encodeJson "CandidateTerm" encodeJson CandidateTerm = encodeJson "CandidateTerm"
...@@ -71,7 +71,7 @@ instance decodeJsonTermList :: DecodeJson TermList where ...@@ -71,7 +71,7 @@ instance decodeJsonTermList :: DecodeJson TermList where
decodeJson json = do decodeJson json = do
s <- decodeJson json s <- decodeJson json
case s of case s of
"GraphTerm" -> pure GraphTerm "MapTerm" -> pure MapTerm
"StopTerm" -> pure StopTerm "StopTerm" -> pure StopTerm
"CandidateTerm" -> pure CandidateTerm "CandidateTerm" -> pure CandidateTerm
_ -> Left "Unexpected list name" _ -> Left "Unexpected list name"
...@@ -79,31 +79,31 @@ instance decodeJsonTermList :: DecodeJson TermList where ...@@ -79,31 +79,31 @@ instance decodeJsonTermList :: DecodeJson TermList where
type ListTypeId = Int type ListTypeId = Int
listTypeId :: TermList -> ListTypeId listTypeId :: TermList -> ListTypeId
listTypeId GraphTerm = 1 listTypeId MapTerm = 1
listTypeId StopTerm = 2 listTypeId StopTerm = 2
listTypeId CandidateTerm = 3 listTypeId CandidateTerm = 3
instance showTermList :: Show TermList where instance showTermList :: Show TermList where
show GraphTerm = "GraphTerm" show MapTerm = "MapTerm"
show StopTerm = "StopTerm" show StopTerm = "StopTerm"
show CandidateTerm = "CandidateTerm" show CandidateTerm = "CandidateTerm"
-- TODO: Can we replace the show instance above with this? -- TODO: Can we replace the show instance above with this?
termListName :: TermList -> String termListName :: TermList -> String
termListName GraphTerm = "Map List" termListName MapTerm = "Map List"
termListName StopTerm = "Stop List" termListName StopTerm = "Stop List"
termListName CandidateTerm = "Candidate List" termListName CandidateTerm = "Candidate List"
instance readTermList :: Read TermList where instance readTermList :: Read TermList where
read :: String -> Maybe TermList read :: String -> Maybe TermList
read "GraphTerm" = Just GraphTerm read "MapTerm" = Just MapTerm
read "StopTerm" = Just StopTerm read "StopTerm" = Just StopTerm
read "CandidateTerm" = Just CandidateTerm read "CandidateTerm" = Just CandidateTerm
read _ = Nothing read _ = Nothing
termLists :: Array { desc :: String, mval :: Maybe TermList } termLists :: Array { desc :: String, mval :: Maybe TermList }
termLists = [ { desc: "All terms", mval: Nothing } termLists = [ { desc: "All terms", mval: Nothing }
, { desc: "Map terms", mval: Just GraphTerm } , { desc: "Map terms", mval: Just MapTerm }
, { desc: "Stop terms", mval: Just StopTerm } , { desc: "Stop terms", mval: Just StopTerm }
, { desc: "Candidate terms", mval: Just CandidateTerm } , { desc: "Candidate terms", mval: Just CandidateTerm }
] ]
......
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