Commit 6ad8d99d authored by Alexandre Delanoë's avatar Alexandre Delanoë

Merge branch 'dev' into testing

parents c979e19b 7f7ac4ad
Pipeline #4032 failed with stage
dist/images/logo.png

19.8 KB | W: | H:

dist/images/logo.png

17.1 KB | W: | H:

dist/images/logo.png
dist/images/logo.png
dist/images/logo.png
dist/images/logo.png
  • 2-up
  • Swipe
  • Onion skin
{
"name": "Gargantext",
"version": "0.0.6.9.9.3.3",
"version": "0.0.6.9.9.5",
"scripts": {
"generate-purs-packages-nix": "./nix/generate-purs-packages.nix",
"generate-psc-packages-nix": "./nix/generate-packages-json.bash",
......
......@@ -33,6 +33,7 @@ to generate this file without the comments in this block.
, "dom-simple"
, "effect"
, "either"
, "enums"
, "exceptions"
, "ffi-simple"
, "foldable-traversable"
......
......@@ -13,18 +13,18 @@ module Gargantext.Components.Annotation.Field where
import Gargantext.Prelude
import DOM.Simple.Event as DE
import Data.Array as A
import Data.List (List(..), (:))
import Data.Maybe (Maybe(..), maybe)
import Data.String.Common (joinWith)
import Data.Tuple (Tuple(..), snd)
import Data.Tuple.Nested ((/\))
import DOM.Simple.Event as DE
import Effect (Effect)
import Gargantext.Components.Annotation.Menu (annotationMenu, AnnotationMenu)
import Gargantext.Components.Annotation.Types (MenuType(..), ModeType(..), termClass)
import Gargantext.Core.NgramsTable.Functions (findNgramTermList, highlightNgrams, normNgram)
import Gargantext.Core.NgramsTable.Types (NgramsTable, NgramsTerm)
import Gargantext.Core.NgramsTable.Types (NgramsTable, NgramsTerm(..))
import Gargantext.Types (CTabNgramType(..), TermList)
import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Selection as Sel
......@@ -35,7 +35,7 @@ import Record as Record
import Toestand as T
here :: R2.Here
here = R2.here "Gargantext.Components.Annotation.AnnotatedField"
here = R2.here "Gargantext.Components.Annotation.Field"
-- @NOTE #386: add parameter "type" ("Authors", "Terms")
type Props =
......@@ -52,7 +52,6 @@ type MouseEvent = E.SyntheticEvent DE.MouseEvent
annotatedField :: R2.Leaf Props
annotatedField = R2.leaf annotatedFieldCpt
annotatedFieldCpt :: R.Component Props
annotatedFieldCpt = here.component "annotatedField" cpt where
cpt props _ = do
......@@ -71,7 +70,6 @@ type InnerProps =
annotatedFieldInner :: R2.Leaf InnerProps
annotatedFieldInner = R2.leaf annotatedFieldInnerCpt
annotatedFieldInnerCpt :: R.Component InnerProps
annotatedFieldInnerCpt = here.component "annotatedFieldInner" cpt where
cpt { menuRef
......@@ -159,14 +157,14 @@ onAnnotationSelect
s <- Sel.getSelection
case s of
Just sel -> do
case Sel.selectionToString sel of
"" -> hideMenu { menuRef, redrawMenu }
case (normNgram CTabTerms $ Sel.selectionToString sel) of
NormNgramsTerm "" -> hideMenu { menuRef, redrawMenu }
sel' -> do
showMenu { event
, getList: findNgramTermList ngrams
, menuRef
, menuType: NewNgram
, ngram: normNgram CTabTerms sel'
, ngram: sel' -- normNgram CTabTerms sel'
, redrawMenu
, setTermList }
Nothing -> hideMenu { menuRef, redrawMenu }
......@@ -241,7 +239,6 @@ type RunProps =
annotateRun :: R2.Leaf RunProps
annotateRun = R2.leaf annotatedRunCpt
annotatedRunCpt :: R.Component RunProps
annotatedRunCpt = here.component "annotatedRun" cpt where
cpt { list, onSelect, text } _ = pure $ case list of
......
......@@ -36,7 +36,6 @@ type AnnotationMenu =
annotationMenu :: R2.Leaf Props
annotationMenu = R2.leaf annotationMenuCpt
annotationMenuCpt :: R.Component Props
annotationMenuCpt = here.component "main" cpt where
cpt { menuRef } _ = do
......
......@@ -4,6 +4,7 @@ module Gargantext.Components.Category where
import Gargantext.Prelude
import Data.Array as A
import Data.Enum (fromEnum)
import Data.Generic.Rep (class Generic)
import Data.Map as Map
import Data.Maybe (Maybe(..), fromMaybe)
......@@ -12,8 +13,8 @@ import Effect.Aff (launchAff_)
import Effect.Class (liftEffect)
import Gargantext.Components.Bootstrap as B
import Gargantext.Components.Bootstrap.Types (Variant(..))
import Gargantext.Components.Category.Types (Category(..), Star(..), cat2score, categories, clickAgain, decodeStar, star2score, stars)
import Gargantext.Components.DocsTable.Types (DocumentsView(..), LocalCategories, LocalUserScore)
import Gargantext.Components.Category.Types (Category(..), Star(..), cat2score, cat2star, categories, categoryNextState, decodeCategory, stars)
import Gargantext.Components.DocsTable.Types (DocumentsView(..), LocalCategories)
import Gargantext.Components.GraphQL.Context (NodeContext)
import Gargantext.Components.GraphQL.Endpoints (getNodeContext, updateNodeContextCategory)
import Gargantext.Config.REST (AffRESTError, RESTError(..))
......@@ -36,9 +37,9 @@ type RatingProps =
( chartReload :: T2.ReloadS
, nodeId :: NodeID
, row :: DocumentsView
, score :: Star
, score :: Category
, session :: Session
, setLocalCategories :: R.Setter LocalUserScore
-- , setLocalCategories :: R.Setter LocalCategories
)
rating :: R2.Component RatingProps
......@@ -50,11 +51,11 @@ ratingCpt = here.component "rating" cpt where
, row: DocumentsView r
, score
, session
, setLocalCategories
-- , setLocalCategories
} _ = do
pure $ renderRatingSimple { docId: r._id
, corpusId: nodeId
, category: star2score score
, category: score
, session } []
-- -- | Behaviors
......@@ -86,14 +87,17 @@ ratingCpt = here.component "rating" cpt where
-- , className: ratingClassName score s
-- }
ratingIcon Star_0 Star_0 = "recycle"
ratingIcon :: Category -> Star -> String
ratingIcon Trash Star_0 = "recycle"
ratingIcon _ Star_0 = "trash"
ratingIcon c s = star2score c < star2score s ? "star-o" $ "star"
ratingIcon c s = fromEnum (cat2star c) < fromEnum s ? "star-o" $ "star"
ratingVariant :: Star -> Star -> Variant
ratingVariant Star_0 Star_0 = Dark
ratingVariant _ Star_0 = Dark
ratingVariant _ _ = Dark
ratingClassName :: Star -> Star -> String
ratingClassName Star_0 Star_0 = "rating-group__action"
ratingClassName _ Star_0 = "rating-group__action"
ratingClassName _ _ = "rating-group__star"
......@@ -118,9 +122,11 @@ ratingSimpleLoaderCpt = here.component "ratingSimpleLoader" cpt where
useLoader { errorHandler
, loader: loadDocumentContext session
, path: { docId, corpusId }
, render: \{ nc_category } -> renderRatingSimple { docId
, render: \{ nc_category } -> do
let category = fromMaybe UnRead $ decodeCategory <$> nc_category
renderRatingSimple { docId
, corpusId
, category: fromMaybe 0 nc_category
, category
, session } [] }
where
errorHandler err = do
......@@ -139,7 +145,7 @@ loadDocumentContext session { docId, corpusId } = getNodeContext session docId c
type RenderRatingSimpleProps =
( docId :: NodeID
, corpusId :: NodeID
, category :: Int
, category :: Category
, session :: Session )
renderRatingSimple :: R2.Component RenderRatingSimpleProps
......@@ -151,17 +157,17 @@ renderRatingSimpleCpt = here.component "renderRatingSimple" cpt where
, category
, session
} _ = do
score <- T.useBox $ decodeStar category
categoryS <- T.useBox category
pure $ ratingSimple { docId
, corpusId
, score
, category: categoryS
, session } []
type RatingSimpleProps =
( docId :: NodeID
, corpusId :: NodeID
, score :: T.Box Star
, category :: T.Box Category
, session :: Session )
ratingSimple :: R2.Component RatingSimpleProps
......@@ -170,19 +176,21 @@ ratingSimpleCpt :: R.Component RatingSimpleProps
ratingSimpleCpt = here.component "ratingSimple" cpt where
cpt { docId
, corpusId
, score
, category
, session
} _ = do
score' <- T.useLive T.unequal score
category' <- T.useLive T.unequal category
let star' = cat2star category'
let
onClick c _ = do
let c' = score' == c ? clickAgain c $ c
-- let c' = score' == c ? clickAgain c $ c
let c' = categoryNextState category' c
-- setLocalCategories $ Map.insert r._id c'
launchAff_ do
_ <- updateNodeContextCategory session docId corpusId $ star2score c'
liftEffect $ T.write_ c' score
_ <- updateNodeContextCategory session docId corpusId $ cat2score c'
liftEffect $ T.write_ c' category
pure unit
pure $
......@@ -190,17 +198,17 @@ ratingSimpleCpt = here.component "ratingSimple" cpt where
{ className: "rating-group" } $
stars <#> \s ->
B.iconButton
{ name: ratingIcon score' s
{ name: ratingIcon category' s
, callback: onClick s
, overlay: false
, variant: ratingVariant score' s
, className: ratingClassName score' s
, variant: ratingVariant star' s
, className: ratingClassName star' s
}
newtype RatingQuery =
RatingQuery { nodeIds :: Array Int
, rating :: Star
, rating :: Category
}
derive instance Generic RatingQuery _
instance JSON.WriteForeign RatingQuery where
......@@ -267,6 +275,9 @@ icon cat b = btn b $ "fa fa-" <> (color $ size b $ icon' cat b)
icon' Favorite false = "heart-o"
icon' Favorite true = "heart"
icon' ToCite false = "quote-left-o"
icon' ToCite true = "quote-left"
size :: Boolean -> String -> String
size true s = s <> " btn-lg"
size false s = s <> " btn-sm"
......
module Gargantext.Components.Category.Types where
import Data.Generic.Rep (class Generic)
import Data.Bounded.Generic (genericTop, genericBottom)
import Data.Enum (class Enum, class BoundedEnum, succ, pred, fromEnum, toEnumWithDefaults)
import Data.Enum.Generic (genericPred, genericSucc, genericCardinality, genericFromEnum, genericToEnum)
import Data.Eq.Generic (genericEq)
import Data.Generic.Rep (class Generic)
import Data.Maybe (fromMaybe)
import Data.Ord.Generic (genericCompare)
import Data.Show.Generic (genericShow)
import Simple.JSON as JSON
import Gargantext.Prelude
------------------------------------------------------------------------
data Star = Star_0 | Star_1 | Star_2 | Star_3 | Star_4
stars :: Array Star
stars = [Star_0, Star_1, Star_2, Star_3, Star_4]
derive instance Generic Star _
instance Show Star where show = genericShow
instance Eq Star where eq = genericEq
instance JSON.ReadForeign Star where
readImpl f = do
inst <- JSON.readImpl f
pure $ decodeStar inst
instance JSON.WriteForeign Star where writeImpl = JSON.writeImpl <<< star2score
decodeStar :: Int -> Star
decodeStar 0 = Star_0
decodeStar 1 = Star_1
decodeStar 2 = Star_2
decodeStar 3 = Star_3
decodeStar 4 = Star_4
decodeStar _ = Star_4
star2score :: Star -> Int
star2score Star_0 = 0
star2score Star_1 = 1
star2score Star_2 = 2
star2score Star_3 = 3
star2score Star_4 = 4
clickAgain :: Star -> Star
clickAgain Star_0 = Star_1
clickAgain s = decodeStar (star2score s - 1)
------------------------------------------------------------------------
data Category = Trash | UnRead | Checked | Topic | Favorite
data Category = Trash | UnRead | Checked | Topic | Favorite | ToCite
{-
- `UnRead` is assigned initially for new docs
- After reading a doc, `Checked` should be assigned automatically
- Both `Trash` and `UnRead` map to 0 stars in the doc list
-}
categories :: Array Category
categories = [Trash, UnRead, Checked, Topic, Favorite]
categories = [Trash, UnRead, Checked, Topic, Favorite, ToCite]
derive instance Generic Category _
instance Ord Category where compare = genericCompare
instance Enum Category where
pred = genericPred
succ = genericSucc
instance Bounded Category where
bottom = genericBottom
top = genericTop
instance BoundedEnum Category where
cardinality = genericCardinality
fromEnum = genericFromEnum
toEnum = genericToEnum
instance Show Category where show = genericShow
instance Eq Category where eq = genericEq
instance JSON.ReadForeign Category where
......@@ -58,26 +43,79 @@ instance JSON.ReadForeign Category where
pure $ decodeCategory inst
instance JSON.WriteForeign Category where writeImpl = JSON.writeImpl <<< cat2score
catSucc :: Category -> Category
catSucc c = fromMaybe ToCite $ succ c
catPred :: Category -> Category
catPred c = fromMaybe Trash $ pred c
clickAgain :: Category -> Category
clickAgain _ = UnRead
-- | `categoryNextState :: current -> clicked -> new State`
categoryNextState :: Category -> Star -> Category
categoryNextState Trash Star_0 = UnRead
categoryNextState _ Star_0 = Trash
categoryNextState current clicked =
if (cat2star current) == clicked then
clickAgain current
else
star2catSimple clicked
favCategory :: Category -> Category
favCategory Favorite = Topic
favCategory _ = Favorite
trashCategory :: Category -> Category
trashCategory _ = Trash
-- TODO: ?
--trashCategory Trash = UnRead
trashCategory = const Trash
decodeCategory :: Int -> Category
decodeCategory 0 = Trash
decodeCategory 1 = UnRead
decodeCategory 2 = Checked
decodeCategory 3 = Topic
decodeCategory 4 = Favorite
decodeCategory _ = UnRead
decodeCategory = toEnumWithDefaults UnRead UnRead
cat2score :: Category -> Int
cat2score Trash = 0
cat2score UnRead = 1
cat2score Checked = 2
cat2score Topic = 3
cat2score Favorite = 4
cat2score = fromEnum
------------------------------------------------------------------------
-- | This is just a helper to visualize categories.
data Star = Star_0 | Star_1 | Star_2 | Star_3 | Star_4
stars :: Array Star
stars = [Star_0, Star_1, Star_2, Star_3, Star_4]
derive instance Generic Star _
instance Show Star where show = genericShow
instance Eq Star where eq = genericEq
instance Ord Star where compare = genericCompare
instance Enum Star where
pred = genericPred
succ = genericSucc
instance Bounded Star where
bottom = genericBottom
top = genericTop
instance BoundedEnum Star where
cardinality = genericCardinality
fromEnum = genericFromEnum
toEnum = genericToEnum
cat2star :: Category -> Star
cat2star Trash = Star_0
cat2star UnRead = Star_0
cat2star Checked = Star_1
cat2star Topic = Star_2
cat2star Favorite = Star_3
cat2star ToCite = Star_4
-- | This is a "reverse" of `cat2star`
star2catSimple :: Star -> Category
star2catSimple Star_0 = UnRead
star2catSimple Star_1 = Checked
star2catSimple Star_2 = Topic
star2catSimple Star_3 = Favorite
star2catSimple Star_4 = ToCite
markCategoryChecked :: Category -> Category
markCategoryChecked UnRead = Checked
markCategoryChecked s = s
......@@ -26,10 +26,11 @@ import Effect.Timer (setTimeout)
import Gargantext.Components.App.Store (Boxes)
import Gargantext.Components.Bootstrap as B
import Gargantext.Components.Bootstrap.Types (ComponentStatus(..), ModalSizing(..), Variant(..))
import Gargantext.Components.Category (rating)
import Gargantext.Components.Category.Types (Star(..))
import Gargantext.Components.Category (rating, ratingSimple)
import Gargantext.Components.Category.Types (Category(..), Star(..), cat2score, markCategoryChecked)
import Gargantext.Components.DocsTable.DocumentFormCreation as DFC
import Gargantext.Components.DocsTable.Types (DocumentsView(..), Hyperdata(..), LocalUserScore, Query, Response(..), Year, sampleData, showSource)
import Gargantext.Components.DocsTable.Types (DocumentsView(..), Hyperdata(..), LocalCategories, Query, Response(..), Year, sampleData, showSource)
import Gargantext.Components.GraphQL.Endpoints (updateNodeContextCategory)
import Gargantext.Components.Nodes.Lists.Types as NT
import Gargantext.Components.Nodes.Texts.Types as TextsT
import Gargantext.Components.Reload (textsReloadContext)
......@@ -450,7 +451,7 @@ pageLayoutCpt = here.component "pageLayout" cpt where
, spinnerClass: Nothing
}
NT.CacheOff -> do
localCategories <- T.useBox (Map.empty :: LocalUserScore)
localCategories <- T.useBox (Map.empty :: LocalCategories)
paramsS <- T.useBox params
paramsS' <- T.useLive T.unequal paramsS
let loader p = do
......@@ -501,7 +502,7 @@ pagePaintCpt = here.component "pagePaintCpt" cpt
cpt { documents, layout, params } _ = do
params' <- T.useLive T.unequal params
localCategories <- T.useBox (Map.empty :: LocalUserScore)
localCategories <- T.useBox (Map.empty :: LocalCategories)
pure $ pagePaintRaw { documents: A.fromFoldable (filteredRows params')
, layout
, localCategories
......@@ -522,7 +523,7 @@ pagePaintCpt = here.component "pagePaintCpt" cpt
type PagePaintRawProps =
( documents :: Array DocumentsView
, layout :: Record PageLayoutProps
, localCategories :: T.Box LocalUserScore
, localCategories :: T.Box LocalCategories
, params :: T.Box TT.Params
)
......@@ -557,27 +558,97 @@ pagePaintRawCpt = here.component "pagePaintRaw" cpt where
{ colNames
, container: TT.defaultContainer
, params
, rows: rows reload chartReload localCategories' mCurrentDocId'
, rows: rows { boxes
, reload
, chartReload
, frontends
, listId
, localCategories: localCategories'
, mCorpusId
, mCurrentDocId
, nodeId
, session
, sidePanel }
, syncResetButton : [ H.div {} [] ]
, totalRecords
, wrapColElts
}
where
colNames = TT.ColumnName <$> [ "Show", "Tag", "Date", "Title", "Source", "Score" ]
wrapColElts = const identity
rows { boxes
, chartReload
, frontends
, listId
, localCategories
, mCorpusId
, mCurrentDocId
, nodeId
, reload
, session
, sidePanel } =
(\documentsView -> { row: tableRow { boxes
, chartReload
, documentsView
, frontends
, listId
, localCategories
, mCorpusId
, mCurrentDocId
, nodeId
, session
, sidePanel } []
, delete: true } ) <$> A.toUnfoldable documents
trashClassName :: Category -> Boolean -> String
trashClassName Trash _ = "page-paint-row page-paint-row--trash"
trashClassName _ true = "page-paint-row page-paint-row--active"
trashClassName _ false = ""
type TableRowProps =
( boxes :: Boxes
, chartReload :: T2.ReloadS
, documentsView :: DocumentsView
, frontends :: Frontends
, listId :: Int
, localCategories :: LocalCategories
, mCorpusId :: Maybe Int
, mCurrentDocId :: T.Box (Maybe Int)
, nodeId :: Int
, session :: Session
, sidePanel :: T.Box (Maybe (Record TextsT.SidePanel)) )
tableRow :: R2.Component TableRowProps
tableRow = R.createElement tableRowCpt
tableRowCpt :: R.Component TableRowProps
tableRowCpt = here.component "tableRow" cpt where
cpt { boxes
, chartReload
, documentsView: dv@(DocumentsView r@{ _id, category })
, frontends
, listId
, localCategories
, mCorpusId
, mCurrentDocId
, nodeId
, session
, sidePanel } _ = do
mCurrentDocId' <- T.useLive T.unequal mCurrentDocId
let cat :: Category
cat = fromMaybe category (localCategories ^. at _id)
selected = mCurrentDocId' == Just r._id
sid = sessionId session
trashClassName Star_0 _ = "page-paint-row page-paint-row--trash"
trashClassName _ true = "page-paint-row page-paint-row--active"
trashClassName _ false = ""
corpusDocument
| Just cid <- mCorpusId = Routes.CorpusDocument sid cid listId
| otherwise = Routes.Document sid listId
colNames = TT.ColumnName <$> [ "Show", "Tag", "Date", "Title", "Source", "Score" ]
wrapColElts = const identity
rows reload chartReload localCategories' mCurrentDocId' = row <$> A.toUnfoldable documents
where
row dv@(DocumentsView r@{ _id, category }) =
{ row:
TT.makeRow'
{ className: "page-paint-raw " <>
categoryS <- T.useBox cat
categoryS' <- T.useLive T.unequal categoryS
let tClassName = trashClassName categoryS' selected
pure $ TT.makeRow' { className: "page-paint-raw " <>
(selected ?
"page-paint-raw--selected" $
""
......@@ -586,19 +657,24 @@ pagePaintRawCpt = here.component "pagePaintRaw" cpt where
[ -- H.div {} [ H.a { className, style, on: {click: click Favorite} } [] ]
H.div { className: "" }
[ docChooser { boxes
, category: categoryS
, docId: r._id
, listId
, mCorpusId
, nodeId: r._id
, session
, sidePanel } []
]
--, H.div { className: "column-tag flex" } [ caroussel { category: cat, nodeId, row: dv, session, setLocalCategories } [] ]
, H.div { className: "column-tag flex" }
[ rating { chartReload
, nodeId
, row: dv
, score: cat
, setLocalCategories: \lc -> T.modify_ lc localCategories
, session } [] ]
[ ratingSimple { -- chartReload
docId: _id
, category: categoryS
, corpusId: nodeId
-- , row: dv
, session
-- , setLocalCategories: \lc -> T.modify_ lc localCategories
} [] ]
--, H.input { type: "checkbox", defaultValue: checked, on: {click: click Trash} }
-- TODO show date: Year-Month-Day only
, H.div { className: tClassName } [ R2.showText r.date ]
......@@ -618,18 +694,16 @@ pagePaintRawCpt = here.component "pagePaintRaw" cpt where
, H.div { className: tClassName } [ H.text $ showSource r.source ]
, H.div {} [ H.text $ maybe "-" show r.ngramCount ]
]
, delete: true }
where
cat = fromMaybe category (localCategories' ^. at _id)
-- checked = Star_1 == cat
selected = mCurrentDocId' == Just r._id
tClassName = trashClassName cat selected
type DocChooser = (
boxes :: Boxes
, category :: T.Box Category
, docId :: Int
, listId :: ListId
, mCorpusId :: Maybe NodeID
, nodeId :: NodeID
, session :: Session
, sidePanel :: T.Box (Maybe (Record TextsT.SidePanel))
)
......@@ -642,31 +716,23 @@ docChooserCpt = here.component "docChooser" cpt
pure $ H.div {} []
cpt { boxes: { sidePanelState }
, category
, docId
, listId
, mCorpusId: Just corpusId
, nodeId
, session
, sidePanel } _ = do
mCurrentDocId <- T.useFocused
(maybe Nothing _.mCurrentDocId)
(\val -> maybe Nothing (\sp -> Just $ sp { mCurrentDocId = val })) sidePanel
mCurrentDocId' <- T.useLive T.unequal mCurrentDocId
category' <- T.useLive T.unequal category
let selected = mCurrentDocId' == Just nodeId
eyeClass = selected ? "eye" $ "eye-slash"
variant = selected ? Info $ Dark
pure $
H.div
{ className: "doc-chooser" }
[
B.iconButton
{ name: eyeClass
, overlay: false
, variant
, callback: onClick selected
}
]
where
onClick selected _ = do
-- here.log2 "[docChooser] onClick, listId" listId
-- here.log2 "[docChooser] onClick, corpusId" corpusId
......@@ -682,7 +748,24 @@ docChooserCpt = here.component "docChooser" cpt
, mCurrentDocId: Just nodeId
, nodeId: nodeId }) sidePanel
T.write_ Opened sidePanelState
here.log2 "[docChooser] sidePanel opened" sidePanelState
let categoryMarked = markCategoryChecked category'
launchAff_ $ do
_ <- updateNodeContextCategory session docId corpusId $ cat2score categoryMarked
pure unit
T.write_ categoryMarked category
-- here.log2 "[docChooser] sidePanel opened" sidePanelState
pure $
H.div
{ className: "doc-chooser" }
[
B.iconButton
{ name: eyeClass
, overlay: false
, variant
, callback: onClick selected
}
]
newtype SearchQuery = SearchQuery {
......
......@@ -7,14 +7,14 @@ import Data.Generic.Rep (class Generic)
import Data.Map (Map)
import Data.Maybe (Maybe(..), fromMaybe)
import Data.Tuple (Tuple(..))
import Gargantext.Components.Category.Types (Category, Star(..), decodeStar)
import Gargantext.Components.Category.Types (Category(..), Star(..), decodeCategory)
import Simple.JSON as JSON
data Action
= MarkCategory Int Category
type DocumentsViewT =
( category :: Star
( category :: Category
, date :: Int
, ngramCount :: Maybe Int
, score :: Maybe Int
......@@ -66,7 +66,7 @@ type ResponseT =
, title :: String )
newtype Response = Response
{ cid :: Int
, category :: Star
, category :: Category
| ResponseT
}
......@@ -74,7 +74,7 @@ instance JSON.ReadForeign Response where
readImpl f = do
{ category, id, hyperdata, ngramCount, score, title } :: { category :: Int, id :: Int | ResponseT } <- JSON.readImpl f
--pure $ Response { category: decodeCategory category, cid, hyperdata, ngramCount, score, title }
pure $ Response { category: decodeStar category
pure $ Response { category: decodeCategory category
, cid: id
, hyperdata
, ngramCount
......@@ -110,7 +110,7 @@ sampleData' = DocumentsView { _id : 1
, date : 2010
, title : "title"
, source : Just "source"
, category : Star_1
, category : UnRead
, ngramCount : Just 1
, score: Just 1 }
......@@ -121,7 +121,7 @@ sampleData = map (\(Tuple t s) -> DocumentsView { _id : 1
, date : 2017
, title: t
, source: Just s
, category : Star_1
, category : UnRead
, ngramCount : Just 10
, score: Just 1 }) sampleDocuments
......
......@@ -16,7 +16,6 @@ import Gargantext.Components.AutoUpdate (autoUpdate)
import Gargantext.Components.Bootstrap as B
import Gargantext.Components.Bootstrap.Types (ComponentStatus(..), SpinnerTheme(..))
import Gargantext.Components.Category (ratingSimpleLoader)
import Gargantext.Components.Category.Types (decodeStar)
import Gargantext.Components.Document.Types (DocPath, Document(..), LoadedData, initialState)
import Gargantext.Components.NgramsTable.AutoSync (useAutoSync)
import Gargantext.Components.Node (NodePoly(..))
......
......@@ -395,6 +395,7 @@ pageCpt = here.component "page" cpt
wrapColElts = const identity
-- TODO: how to interprete other scores?
gi Trash = "fa fa-star-empty"
gi UnRead = "fa fa-star-empty"
gi _ = "fa fa-star"
documentUrl id { listId, nodeId } =
......
......@@ -3,6 +3,7 @@ module Gargantext.Components.Forest.Tree.Node.Action.Search.SearchField where
import Gargantext.Prelude
import Data.Array as A
import Data.Either (Either(..))
import Data.Maybe (Maybe(..), maybe, fromMaybe)
import Data.Newtype (over)
import Data.Nullable (null)
......@@ -15,8 +16,8 @@ import Effect (Effect)
import Effect.Aff (launchAff_)
import Effect.Class (liftEffect)
import Gargantext.Components.Forest.Tree.Node.Action.Search.Frame (searchIframes)
import Gargantext.Components.Forest.Tree.Node.Action.Search.Types (DataField(..), Database(..), IMT_org(..), Org(..), SearchQuery(..), allOrgs, dataFields, defaultSearchQuery, doc, performSearch, datafield2database, Search)
import Gargantext.Components.GraphQL.Endpoints (getIMTSchools)
import Gargantext.Components.Forest.Tree.Node.Action.Search.Types (DataField(..), Database(..), IMT_org(..), Org(..), SearchQuery(..), allOrgs, dataFields, defaultSearchQuery, doc, performSearch, datafield2database, Search, dbFromInputValue, dbToInputValue)
import Gargantext.Components.GraphQL.Endpoints (getIMTSchools, getNodeCorpus)
import Gargantext.Components.GraphQL.IMT as GQLIMT
import Gargantext.Components.InputWithEnter (inputWithEnter)
import Gargantext.Components.Lang (Lang(..))
......@@ -37,8 +38,8 @@ here :: R2.Here
here = R2.here "Gargantext.Components.Forest.Tree.Node.Action.Search.SearchField"
defaultSearch :: Search
defaultSearch = { databases: Empty
, datafield: Nothing
defaultSearch = { databases : Empty
, datafield : Just (External Empty)
, node_id : Nothing
, lang : Nothing
, term : ""
......@@ -180,28 +181,19 @@ isExternal _ = false
isArxiv :: Maybe DataField -> Boolean
isArxiv (Just
( External
( Just Arxiv
)
)
( External Arxiv )
) = true
isArxiv _ = false
isHAL :: Maybe DataField -> Boolean
isHAL (Just
( External
( Just (HAL _ )
)
)
( External (HAL _ ) )
) = true
isHAL _ = false
isIsTex :: Maybe DataField -> Boolean
isIsTex ( Just
( External
( Just ( IsTex)
)
)
( External ( IsTex ) )
) = true
isIsTex _ = false
......@@ -209,11 +201,8 @@ isIsTex _ = false
isIMT :: Maybe DataField -> Boolean
isIMT ( Just
( External
( Just
( HAL
( Just ( IMT _)
)
)
( Just ( IMT _) )
)
)
) = true
......@@ -222,24 +211,24 @@ isIMT _ = false
isCNRS :: Maybe DataField -> Boolean
isCNRS ( Just
( External
( Just
( HAL
( Just ( CNRS _)
)
)
( Just ( CNRS _) )
)
)
) = true
isCNRS _ = false
isPubmed :: Maybe DataField -> Boolean
isPubmed ( Just
( External ( PubMed _ ) )
) = true
isPubmed _ = false
needsLang :: Maybe DataField -> Boolean
needsLang (Just Gargantext) = true
needsLang (Just Web) = true
needsLang ( Just
( External
( Just (HAL _)
)
)
( External (HAL _) )
) = true
needsLang _ = false
......@@ -247,20 +236,18 @@ needsLang _ = false
isIn :: IMT_org -> Maybe DataField -> Boolean
isIn org ( Just
( External
( Just
( HAL
( Just
( IMT imtOrgs )
)
)
)
)
) = Set.member org imtOrgs
isIn _ _ = false
updateFilter :: IMT_org -> Array IMT_org -> Maybe DataField -> Maybe DataField
updateFilter org allIMTorgs (Just (External (Just (HAL (Just (IMT imtOrgs)))))) =
(Just (External (Just (HAL (Just $ IMT imtOrgs')))))
updateFilter org allIMTorgs (Just (External (HAL (Just (IMT imtOrgs))))) =
Just $ External $ HAL $ Just $ IMT imtOrgs'
where
imtOrgs' = if Set.member org imtOrgs
then
......@@ -272,7 +259,7 @@ updateFilter org allIMTorgs (Just (External (Just (HAL (Just (IMT imtOrgs))))))
then Set.fromFoldable allIMTorgs
else Set.insert org imtOrgs
updateFilter org allIMTorgs _ = (Just (External (Just (HAL (Just (IMT imtOrgs'))))))
updateFilter org allIMTorgs _ = (Just (External (HAL (Just (IMT imtOrgs')))))
where
imtOrgs' = if org == All_IMT
then Set.fromFoldable allIMTorgs
......@@ -346,6 +333,7 @@ dataFieldNavCpt = here.component "dataFieldNav" cpt
type DatabaseInputProps = (
databases :: Array Database
, search :: T.Box Search
, session :: Session
)
databaseInput :: R2.Component DatabaseInputProps
......@@ -354,34 +342,82 @@ databaseInputCpt :: R.Component DatabaseInputProps
databaseInputCpt = here.component "databaseInput" cpt
where
cpt { databases
, search } _ = do
, search
, session } _ = do
search' <- T.useLive T.unequal search
let db = case search'.datafield of
(Just (External (Just x))) -> Just x
(Just (External x)) -> Just x
_ -> Nothing
dbInputValue = fromMaybe "" $ dbToInputValue <$> db
liItem :: Database -> R.Element
liItem db' = H.option { className : "text-primary center"
, value: show db' } [ H.text (show db') ]
, value: dbToInputValue db' } [ H.text (show db') ]
change e = do
let value = read $ R.unsafeEventValue e
T.modify_ (_ { datafield = Just $ External value
, databases = fromMaybe Empty value
let value = dbFromInputValue $ R.unsafeEventValue e
-- TODO Fetch pubmed api key
launchAff_ $ do
updatedValue <- case value of
Just (PubMed _) ->
case search'.node_id of
Just nodeId -> do
eCorpus <- getNodeCorpus session nodeId
case eCorpus of
Left _err -> pure $ PubMed { api_key: Nothing }
Right c -> pure $ PubMed { api_key: c.pubmedAPIKey }
Nothing -> pure $ PubMed { api_key: Nothing }
_ -> pure $ fromMaybe Empty value
liftEffect $ T.modify_ (_ { datafield = Just $ External updatedValue
, databases = updatedValue
}) search
pure $
H.div { className: "form-group" }
[ H.div {className: "text-primary center"} [ H.text "in database" ]
, R2.select { className: "form-control"
, defaultValue: defaultValue search'.datafield
, defaultValue: dbInputValue
, on: { change }
} (liItem <$> databases)
, H.div {className:"center"} [ H.text $ maybe "" doc db ]
]
defaultValue datafield = show $ maybe Empty datafield2database datafield
type PubmedInputProps = (
search :: T.Box Search
, session :: Session
)
pubmedInput :: R2.Component PubmedInputProps
pubmedInput = R.createElement pubmedInputCpt
pubmedInputCpt :: R.Component PubmedInputProps
pubmedInputCpt = here.component "pubmedInput" cpt where
cpt { search, session } _ = do
search' <- T.useLive T.unequal search
case search'.datafield of
Just (External (PubMed p@{ api_key })) ->
-- TODO Fetch current API key
pure $
H.div { className: "form-group" }
[ H.div { className: "text-primary center" } [ H.text "Pubmed API key" ]
, H.input { className: "form-control"
, defaultValue: fromMaybe "" api_key
, on: { blur: modifyPubmedAPIKey search p
, change: modifyPubmedAPIKey search p
, input: modifyPubmedAPIKey search p } } ]
_ -> pure $ H.div {} []
where
modifyPubmedAPIKey search p e = do
let val = R.unsafeEventValue e
let mVal = case val of
"" -> Nothing
s -> Just s
T.modify_ (\s ->
s { datafield = Just (External (PubMed p { api_key = mVal })) }) search
type OrgInputProps =
......@@ -396,7 +432,7 @@ orgInputCpt = here.component "orgInput" cpt
cpt { orgs, search } _ = do
let change e = do
let value = R.unsafeEventValue e
T.modify_ (_ { datafield = Just $ External $ Just $ HAL $ read value }) search
T.modify_ (_ { datafield = Just $ External $ HAL $ read value }) search
pure $ H.div { className: "form-group" }
[ H.div {className: "text-primary center"} [H.text "filter with organization: "]
......@@ -438,13 +474,18 @@ datafieldInputCpt :: R.Component DatafieldInputProps
datafieldInputCpt = here.component "datafieldInput" cpt where
cpt { databases, langs, search, session } _ = do
search' <- T.useLive T.unequal search
datafield <- T.useFocused (_.datafield) (\a b -> b { datafield = a }) search
iframeRef <- R.useRef null
pure $ H.div {}
[ dataFieldNav { search } []
, if isExternal search'.datafield
then databaseInput { databases, search } []
then databaseInput { databases, search, session } []
else H.div {} []
, if isPubmed search'.datafield
then pubmedInput { search, session } []
else H.div {} []
, if isHAL search'.datafield
......@@ -594,23 +635,26 @@ searchQuery selection { datafield: Nothing, term } =
, selection = selection }) defaultSearchQuery
-- TODO Simplify both HAL Nothing and HAL (Just IMT) cases
searchQuery selection { databases
, datafield: datafield@(Just (External (Just (HAL Nothing))))
, datafield: datafield@(Just (External (HAL Nothing)))
, lang
, term
, node_id
, years } = over SearchQuery (_ { databases = databases
, years } =
over SearchQuery (_ { databases = databases
, datafield = datafield
, lang = lang
, node_id = node_id
, query = queryHAL term Nothing lang years
, selection = selection
}) defaultSearchQuery
searchQuery selection { databases
, datafield: datafield@(Just (External (Just (HAL (Just (IMT imtOrgs))))))
, datafield: datafield@(Just (External (HAL (Just (IMT imtOrgs)))))
, lang
, term
, node_id
, years } = over SearchQuery (_ { databases = databases
, years } =
over SearchQuery (_ { databases = databases
, datafield = datafield
, lang = lang
, node_id = node_id
......
......@@ -8,7 +8,6 @@ import Data.Maybe (Maybe(..), fromMaybe, maybe)
import Data.Newtype (class Newtype)
import Data.Set (Set)
import Data.Set as Set
import Data.String as String
import Data.Tuple (Tuple)
import Data.Tuple.Nested ((/\))
import Gargantext.Components.GraphQL.IMT as GQLIMT
......@@ -34,10 +33,7 @@ type Search = { databases :: Database
isIsTex_Advanced :: Maybe DataField -> Boolean
isIsTex_Advanced ( Just
( External
( Just ( IsTex_Advanced)
)
)
( External ( IsTex_Advanced) )
) = true
isIsTex_Advanced _ = false
......@@ -51,13 +47,13 @@ class Doc a where
dataFields :: Array DataField
dataFields = [ {- Gargantext
, -} External Nothing
, -} External Empty
, Web
-- , Files
]
data DataField = Gargantext
| External (Maybe Database)
| External Database
| Web
| Files
......@@ -74,9 +70,9 @@ instance Doc DataField where
doc Files = "Zip files with formats.."
derive instance Eq DataField
instance JSON.WriteForeign DataField where
writeImpl (External (Just db)) = JSON.writeImpl $ "External " <> show db
writeImpl Web = JSON.writeImpl $ "Web"
writeImpl f = JSON.writeImpl $ show f
writeImpl (External db) = JSON.writeImpl { tag: "External"
, contents: JSON.writeImpl db }
writeImpl f = JSON.writeImpl $ JSON.writeImpl { tag: show f }
----------------------------------------
data DataOriginApi = InternalOrigin { api :: Database }
......@@ -91,23 +87,23 @@ instance JSON.WriteForeign DataOriginApi where
writeImpl (ExternalOrigin { api }) = JSON.writeImpl { api }
datafield2dataOriginApi :: DataField -> DataOriginApi
datafield2dataOriginApi (External (Just a)) = ExternalOrigin { api : a }
datafield2dataOriginApi (External a) = ExternalOrigin { api : a }
datafield2dataOriginApi _ = InternalOrigin { api : IsTex } -- TODO fixme
------------------------------------------------------------------------
-- | Database search specifications
datafield2database :: DataField -> Database
datafield2database (External (Just x)) = x
datafield2database (External x) = x
datafield2database _ = Empty
allDatabases :: Array Database
allDatabases = [ Empty
, PubMed
, Arxiv
, PubMed { api_key: Nothing }
-- , Arxiv
, HAL Nothing
, IsTex
, IsTex_Advanced
-- , IsTex_Advanced
-- , Isidore
--, Web
--, News
......@@ -116,7 +112,7 @@ allDatabases = [ Empty
data Database = All_Databases
| Empty
| PubMed
| PubMed { api_key :: Maybe String }
| Arxiv
| HAL (Maybe Org)
| IsTex
......@@ -127,7 +123,7 @@ data Database = All_Databases
derive instance Generic Database _
instance Show Database where
show All_Databases = "All Databases"
show PubMed = "PubMed"
show (PubMed _) = "PubMed"
show Arxiv = "Arxiv"
show (HAL _) = "HAL"
show IsTex = "IsTex"
......@@ -139,7 +135,7 @@ instance Show Database where
instance Doc Database where
doc All_Databases = "All databases"
doc PubMed = "All Medical publications"
doc (PubMed _) = "All Medical publications"
doc Arxiv = "Arxiv"
doc (HAL _) = "All open science (archives ouvertes)"
doc IsTex = "All Elsevier enriched by CNRS/INIST"
......@@ -149,22 +145,46 @@ instance Doc Database where
-- doc News = "Web filtered by News"
-- doc SocialNetworks = "Web filtered by MicroBlogs"
instance Read Database where
read :: String -> Maybe Database
read "All Databases" = Just All_Databases
read "PubMed" = Just PubMed
read "Arxiv" = Just Arxiv
read "HAL" = Just $ HAL Nothing
read "Isidore" = Just Isidore
read "IsTex" = Just IsTex
read "IsTex_Advanced" = Just IsTex_Advanced
-- read "Web" = Just Web
-- read "News" = Just News
-- read "Social Networks" = Just SocialNetworks
read _ = Nothing
-- instance Read Database where
-- read :: String -> Maybe Database
-- read "All Databases" = Just All_Databases
-- read "PubMed" = Just PubMed
-- read "Arxiv" = Just Arxiv
-- read "HAL" = Just $ HAL Nothing
-- read "Isidore" = Just Isidore
-- read "IsTex" = Just IsTex
-- read "IsTex_Advanced" = Just IsTex_Advanced
-- -- read "Web" = Just Web
-- -- read "News" = Just News
-- -- read "Social Networks" = Just SocialNetworks
-- read _ = Nothing
dbToInputValue :: Database -> String
dbToInputValue All_Databases = "all_databases"
dbToInputValue (PubMed _) = "pubmed"
dbToInputValue Arxiv = "arxiv"
dbToInputValue (HAL _) = "hal"
dbToInputValue IsTex = "istex"
dbToInputValue IsTex_Advanced = "istex_advanced"
dbToInputValue Isidore = "isidore"
dbToInputValue Empty = "empty"
dbFromInputValue :: String -> Maybe Database
dbFromInputValue "all_databases" = Just All_Databases
dbFromInputValue "pubmed" = Just (PubMed { api_key: Nothing})
dbFromInputValue "arxiv" = Just Arxiv
dbFromInputValue "hal" = Just (HAL Nothing)
dbFromInputValue "istex" = Just IsTex
dbFromInputValue "istex_advanced" = Just IsTex_Advanced
dbFromInputValue "isidore" = Just Isidore
dbFromInputValue "empty" = Just Empty
dbFromInputValue _ = Nothing
derive instance Eq Database
instance JSON.WriteForeign Database where writeImpl = JSON.writeImpl <<< show
instance JSON.WriteForeign Database where
writeImpl (PubMed { api_key }) = JSON.writeImpl { tag: "PubMed"
, _api_key: api_key }
writeImpl f = JSON.writeImpl { tag: show f }
------------------------------------------------------------------------
-- | Organization specifications
......@@ -243,6 +263,7 @@ newtype SearchQuery = SearchQuery
, node_id :: Maybe Int
, offset :: Maybe Int
, order :: Maybe SearchOrder
, pubmedAPIKey :: Maybe String
, selection :: ListSelection.Selection
}
derive instance Generic SearchQuery _
......@@ -260,13 +281,14 @@ instance GT.ToQuery SearchQuery where
pair k = maybe [] $ \v ->
[ QP.keyFromString k /\ Just (QP.valueFromString $ show v) ]
instance JSON.WriteForeign SearchQuery where
writeImpl (SearchQuery { databases, datafield, lang, node_id, query, selection }) =
writeImpl (SearchQuery { databases, datafield, lang, node_id, pubmedAPIKey, query, selection }) =
JSON.writeImpl { query: query -- String.replace (String.Pattern "\"") (String.Replacement "\\\"") query
, databases
, datafield
, lang: maybe "EN" show lang
, node_id: fromMaybe 0 node_id
, flowListWith: selection
, pubmedAPIKey
}
defaultSearchQuery :: SearchQuery
......@@ -280,6 +302,7 @@ defaultSearchQuery = SearchQuery
, node_id : Nothing
, offset : Nothing
, order : Nothing
, pubmedAPIKey : Nothing
, selection : ListSelection.NoList -- MyListsFirst
}
......
......@@ -156,6 +156,7 @@ uploadFileViewWithLangsCpt = here.component "uploadFileViewWithLangs" cpt
[ formChoiceSafe { items: [ CSV
, CSV_HAL
, WOS
, JSON
-- , Iramuteq
]
, default: CSV
......@@ -585,7 +586,7 @@ uploadFile { contents, fileFormat, lang, fileType, id, nodeType, mName, selectio
, Tuple "_wjf_name" mName
]
csvBodyParams = [ Tuple "_wtf_data" (Just contents)
, Tuple "_wtf_filetype" (Just $ show NodeList)
, Tuple "_wtf_filetype" (Just $ show fileType)
, Tuple "_wtf_fileformat" (Just $ show fileFormat)
, Tuple "_wf_lang" (Just $ show lang)
, Tuple "_wtf_name" mName
......
......@@ -14,7 +14,7 @@ import Gargantext.Components.GraphQL.Contact (AnnuaireContact)
import Gargantext.Components.GraphQL.Context as GQLCTX
import Gargantext.Components.GraphQL.IMT as GQLIMT
import Gargantext.Components.GraphQL.NLP as GQLNLP
import Gargantext.Components.GraphQL.Node (Node)
import Gargantext.Components.GraphQL.Node as GQLNode
import Gargantext.Components.GraphQL.Tree (TreeFirstLevel)
import Gargantext.Components.GraphQL.User (User, UserInfo, UserInfoM)
import Gargantext.Components.GraphQL.Team (Team, TeamDeleteM)
......@@ -78,8 +78,9 @@ type Schema
, contexts_for_ngrams :: { corpus_id :: Int, ngrams_terms :: Array String } ==> Array GQLCTX.Context
, imt_schools :: {} ==> Array GQLIMT.School
, languages :: {} ==> Array GQLNLP.Language
, node_parent :: { node_id :: Int, parent_type :: String } ==> Array Node -- TODO: parent_type :: NodeType
, nodes :: { node_id :: Int } ==> Array Node
, node_parent :: { node_id :: Int, parent_type :: String } ==> Array GQLNode.Node -- TODO: parent_type :: NodeType
, nodes :: { node_id :: Int } ==> Array GQLNode.Node
, nodes_corpus :: { corpus_id :: Int } ==> Array GQLNode.Corpus
, user_infos :: { user_id :: Int } ==> Array UserInfo
, users :: { user_id :: Int } ==> Array User
, team :: { team_node_id :: Int } ==> Team
......
......@@ -14,7 +14,7 @@ import Gargantext.Components.GraphQL.Contact (AnnuaireContact, annuaireContactQu
import Gargantext.Components.GraphQL.Context as GQLCTX
import Gargantext.Components.GraphQL.IMT as GQLIMT
import Gargantext.Components.GraphQL.NLP as GQLNLP
import Gargantext.Components.GraphQL.Node (Node, nodeParentQuery, nodesQuery)
import Gargantext.Components.GraphQL.Node (Corpus, Node, nodeParentQuery, nodesQuery, nodesCorpusQuery)
import Gargantext.Components.GraphQL.Team (Team, teamQuery)
import Gargantext.Components.GraphQL.Tree (TreeFirstLevel, treeFirstLevelQuery)
import Gargantext.Components.GraphQL.User (UserInfo, userInfoQuery)
......@@ -46,6 +46,15 @@ getNode session nodeId = do
Nothing -> Left (CustomError $ "node with id" <> show nodeId <>" not found")
Just node -> Right node
getNodeCorpus :: Session -> Int -> AffRESTError Corpus
getNodeCorpus session corpusId = do
{ nodes_corpus } <- queryGql session "get nodes corpus" $
nodesCorpusQuery `withVars` { id: corpusId }
liftEffect $ here.log2 "[getNodesCorpus] nodes_corpus" nodes_corpus
pure $ case A.head nodes_corpus of
Nothing -> Left (CustomError $ "corpus with id" <> show corpusId <>" not found")
Just corpus -> Right corpus
getNodeParent :: Session -> Int -> NodeType -> Aff (Array Node)
getNodeParent session nodeId parentType = do
{ node_parent } <- queryGql session "get node parent" $
......
......@@ -2,18 +2,35 @@ module Gargantext.Components.GraphQL.Node where
import Gargantext.Prelude
import Data.Maybe (Maybe)
import GraphQL.Client.Args (Args, (=>>))
import GraphQL.Client.Variable (Var(..))
import Gargantext.Utils.GraphQL as GGQL
import Type.Proxy (Proxy(..))
type Corpus
= { id :: Int
, name :: String
, parent_id :: Int
, pubmedAPIKey :: Maybe String
, type_id :: Int }
type Node
= { id :: Int
, name :: String
, parent_id :: Int
, type_id :: Int }
type NodesCorpusQuery =
{ nodes_corpus :: Args
{ corpus_id :: Var "id" Int }
{ id :: Unit
, name :: Unit
, parent_id :: Unit
, pubmedAPIKey :: Unit
, type_id :: Unit } }
type NodesQuery =
{ nodes :: Args
{ node_id :: Var "id" Int }
......@@ -27,6 +44,11 @@ nodesQuery = { nodes: { node_id: Var :: _ "id" Int } =>>
GGQL.getFieldsStandard (Proxy :: _ Node)
}
nodesCorpusQuery :: NodesCorpusQuery
nodesCorpusQuery = { nodes_corpus: { corpus_id: Var :: _ "id" Int } =>>
GGQL.getFieldsStandard (Proxy :: _ Corpus)
}
nodeParentQuery = { node_parent: { node_id: Var :: _ "id" Int
, parent_type: Var :: _ "parent_type" String } =>> -- TODO parent_type :: NodeType
GGQL.getFieldsStandard (Proxy :: _ Node)
......
......@@ -13,6 +13,7 @@ import Gargantext.Prelude
import Data.Array as A
import Data.Array as Array
import Data.Either (Either(..))
import Data.Foldable (any)
import Data.FunctorWithIndex (mapWithIndex)
import Data.Lens (to, view, (.~), (^.), (^?))
import Data.Lens.At (at)
......@@ -47,7 +48,7 @@ import Gargantext.Components.Table.Types (Params, orderByToGTOrderBy)
import Gargantext.Components.Table.Types as TT
import Gargantext.Config.REST (AffRESTError, RESTError, logRESTError)
import Gargantext.Core.NgramsTable.Functions (addNewNgramA, applyNgramsPatches, chartsAfterSync, commitPatch, convOrderBy, coreDispatch, filterTermSize, ngramsRepoElementToNgramsElement, normNgram, patchSetFromMap, singletonNgramsTablePatch, tablePatchHasNgrams, toVersioned)
import Gargantext.Core.NgramsTable.Types (Action(..), CoreAction(..), State, Dispatch, NgramsActionRef, NgramsClick, NgramsElement(..), NgramsPatch(..), NgramsTable, NgramsTablePatch(..), NgramsTerm(..), PageParams, PatchMap(..), Versioned(..), VersionedNgramsTable, VersionedWithCountNgramsTable, _NgramsElement, _NgramsRepoElement, _NgramsTable, _children, _list, _ngrams, _ngrams_repo_elements, _ngrams_scores, _occurrences, _root, applyPatchSet, ngramsTermText, replace)
import Gargantext.Core.NgramsTable.Types (Action(..), CoreAction(..), State, Dispatch, NgramsActionRef, NgramsClick, NgramsElement(..), NgramsPatch(..), NgramsRepoElement(..), NgramsTable, NgramsTablePatch(..), NgramsTerm(..), PageParams, PatchMap(..), Versioned(..), VersionedNgramsTable, VersionedWithCountNgramsTable, _NgramsElement, _NgramsRepoElement, _NgramsTable, _children, _list, _ngrams, _ngrams_repo_elements, _ngrams_scores, _occurrences, _root, applyPatchSet, ngramsTermText, replace)
import Gargantext.Hooks.Loader (useLoaderBox)
import Gargantext.Routes (SessionRoute(..)) as Routes
import Gargantext.Sessions (Session, get)
......@@ -525,7 +526,11 @@ loadedNgramsTableBodyCpt = here.component "loadedNgramsTableBody" cpt where
exactMatches :: Boolean
exactMatches = not $ Seq.null $ Seq.filter fltr nres
where
fltr (Tuple ng _) = queryExactMatchesLabel searchQuery (ngramsTermText ng)
-- | Match either ngrams term or its children with the
-- | `queryExactMatchesLabel` function.
fltr :: Tuple NgramsTerm NgramsRepoElement -> Boolean
fltr (Tuple ng (NgramsRepoElement { children })) =
any (queryExactMatchesLabel searchQuery) $ (Set.map ngramsTermText $ Set.insert ng children)
rowsFilter :: NgramsElement -> Maybe NgramsElement
rowsFilter ngramsElement =
if displayRow { ngramsElement
......
......@@ -177,7 +177,7 @@ divDropdownLeftCpt = here.component "divDropdownLeft" cpt
]
, -----------------------------------------------------------
[ LiNav { title : "Chat"
, href : "https://chat.iscpif.fr/channel/gargantext"
, href : "https://webchat.oftc.net/?channels=#gargantext"
, icon : "fa fa-rocket"
, text : "Chat"
}
......
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