Skip to content
Projects
Groups
Snippets
Help
Loading...
Help
Submit feedback
Contribute to GitLab
Sign in
Toggle navigation
P
purescript-gargantext
Project
Project
Details
Activity
Releases
Cycle Analytics
Repository
Repository
Files
Commits
Branches
Tags
Contributors
Graph
Compare
Charts
Issues
0
Issues
0
List
Board
Labels
Milestones
Merge Requests
0
Merge Requests
0
CI / CD
CI / CD
Pipelines
Jobs
Schedules
Charts
Wiki
Wiki
Snippets
Snippets
Members
Members
Collapse sidebar
Close sidebar
Activity
Graph
Charts
Create a new issue
Jobs
Commits
Issue Boards
Open sidebar
Grégoire Locqueville
purescript-gargantext
Commits
c9d48a87
Verified
Commit
c9d48a87
authored
May 15, 2023
by
Przemyslaw Kaminski
Browse files
Options
Browse Files
Download
Email Patches
Plain Diff
[doc table] fixes to stars (add 1 more state, refactor)
parent
d720b1a6
Changes
7
Hide whitespace changes
Inline
Side-by-side
Showing
7 changed files
with
268 additions
and
154 deletions
+268
-154
spago.dhall
spago.dhall
+1
-0
Category.purs
src/Gargantext/Components/Category.purs
+36
-25
Types.purs
src/Gargantext/Components/Category/Types.purs
+87
-53
DocsTable.purs
src/Gargantext/Components/DocsTable.purs
+136
-68
Types.purs
src/Gargantext/Components/DocsTable/Types.purs
+7
-7
Layout.purs
src/Gargantext/Components/Document/Layout.purs
+0
-1
FacetsTable.purs
src/Gargantext/Components/FacetsTable.purs
+1
-0
No files found.
spago.dhall
View file @
c9d48a87
...
@@ -33,6 +33,7 @@ to generate this file without the comments in this block.
...
@@ -33,6 +33,7 @@ to generate this file without the comments in this block.
, "dom-simple"
, "dom-simple"
, "effect"
, "effect"
, "either"
, "either"
, "enums"
, "exceptions"
, "exceptions"
, "ffi-simple"
, "ffi-simple"
, "foldable-traversable"
, "foldable-traversable"
...
...
src/Gargantext/Components/Category.purs
View file @
c9d48a87
...
@@ -4,6 +4,7 @@ module Gargantext.Components.Category where
...
@@ -4,6 +4,7 @@ module Gargantext.Components.Category where
import Gargantext.Prelude
import Gargantext.Prelude
import Data.Array as A
import Data.Array as A
import Data.Enum (fromEnum)
import Data.Generic.Rep (class Generic)
import Data.Generic.Rep (class Generic)
import Data.Map as Map
import Data.Map as Map
import Data.Maybe (Maybe(..), fromMaybe)
import Data.Maybe (Maybe(..), fromMaybe)
...
@@ -12,8 +13,8 @@ import Effect.Aff (launchAff_)
...
@@ -12,8 +13,8 @@ import Effect.Aff (launchAff_)
import Effect.Class (liftEffect)
import Effect.Class (liftEffect)
import Gargantext.Components.Bootstrap as B
import Gargantext.Components.Bootstrap as B
import Gargantext.Components.Bootstrap.Types (Variant(..))
import Gargantext.Components.Bootstrap.Types (Variant(..))
import Gargantext.Components.Category.Types (Category(..), Star(..), cat2score, cat
egories, clickAgain, decodeStar, star2score
, stars)
import Gargantext.Components.Category.Types (Category(..), Star(..), cat2score, cat
2star, categories, categoryNextState, decodeCategory
, stars)
import Gargantext.Components.DocsTable.Types (DocumentsView(..), LocalCategories
, LocalUserScore
)
import Gargantext.Components.DocsTable.Types (DocumentsView(..), LocalCategories)
import Gargantext.Components.GraphQL.Context (NodeContext)
import Gargantext.Components.GraphQL.Context (NodeContext)
import Gargantext.Components.GraphQL.Endpoints (getNodeContext, updateNodeContextCategory)
import Gargantext.Components.GraphQL.Endpoints (getNodeContext, updateNodeContextCategory)
import Gargantext.Config.REST (AffRESTError, RESTError(..))
import Gargantext.Config.REST (AffRESTError, RESTError(..))
...
@@ -36,9 +37,9 @@ type RatingProps =
...
@@ -36,9 +37,9 @@ type RatingProps =
( chartReload :: T2.ReloadS
( chartReload :: T2.ReloadS
, nodeId :: NodeID
, nodeId :: NodeID
, row :: DocumentsView
, row :: DocumentsView
, score ::
Star
, score ::
Category
, session :: Session
, session :: Session
, setLocalCategories :: R.Setter LocalUserScore
-- , setLocalCategories :: R.Setter LocalCategories
)
)
rating :: R2.Component RatingProps
rating :: R2.Component RatingProps
...
@@ -50,11 +51,11 @@ ratingCpt = here.component "rating" cpt where
...
@@ -50,11 +51,11 @@ ratingCpt = here.component "rating" cpt where
, row: DocumentsView r
, row: DocumentsView r
, score
, score
, session
, session
, setLocalCategories
--
, setLocalCategories
} _ = do
} _ = do
pure $ renderRatingSimple { docId: r._id
pure $ renderRatingSimple { docId: r._id
, corpusId: nodeId
, corpusId: nodeId
, category: s
tar2score s
core
, category: score
, session } []
, session } []
-- -- | Behaviors
-- -- | Behaviors
...
@@ -86,14 +87,17 @@ ratingCpt = here.component "rating" cpt where
...
@@ -86,14 +87,17 @@ ratingCpt = here.component "rating" cpt where
-- , className: ratingClassName score s
-- , className: ratingClassName score s
-- }
-- }
ratingIcon Star_0 Star_0 = "recycle"
ratingIcon :: Category -> Star -> String
ratingIcon Trash Star_0 = "recycle"
ratingIcon _ Star_0 = "trash"
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 Star_0 = Dark
ratingVariant _ Star_0 = Dark
ratingVariant _ Star_0 = Dark
ratingVariant _ _ = Dark
ratingVariant _ _ = Dark
ratingClassName :: Star -> Star -> String
ratingClassName Star_0 Star_0 = "rating-group__action"
ratingClassName Star_0 Star_0 = "rating-group__action"
ratingClassName _ Star_0 = "rating-group__action"
ratingClassName _ Star_0 = "rating-group__action"
ratingClassName _ _ = "rating-group__star"
ratingClassName _ _ = "rating-group__star"
...
@@ -118,10 +122,12 @@ ratingSimpleLoaderCpt = here.component "ratingSimpleLoader" cpt where
...
@@ -118,10 +122,12 @@ ratingSimpleLoaderCpt = here.component "ratingSimpleLoader" cpt where
useLoader { errorHandler
useLoader { errorHandler
, loader: loadDocumentContext session
, loader: loadDocumentContext session
, path: { docId, corpusId }
, path: { docId, corpusId }
, render: \{ nc_category } -> renderRatingSimple { docId
, render: \{ nc_category } -> do
, corpusId
let category = fromMaybe UnRead $ decodeCategory <$> nc_category
, category: fromMaybe 0 nc_category
renderRatingSimple { docId
, session } [] }
, corpusId
, category
, session } [] }
where
where
errorHandler err = do
errorHandler err = do
here.warn2 "[pageLayout] RESTError" err
here.warn2 "[pageLayout] RESTError" err
...
@@ -139,7 +145,7 @@ loadDocumentContext session { docId, corpusId } = getNodeContext session docId c
...
@@ -139,7 +145,7 @@ loadDocumentContext session { docId, corpusId } = getNodeContext session docId c
type RenderRatingSimpleProps =
type RenderRatingSimpleProps =
( docId :: NodeID
( docId :: NodeID
, corpusId :: NodeID
, corpusId :: NodeID
, category ::
Int
, category ::
Category
, session :: Session )
, session :: Session )
renderRatingSimple :: R2.Component RenderRatingSimpleProps
renderRatingSimple :: R2.Component RenderRatingSimpleProps
...
@@ -151,17 +157,17 @@ renderRatingSimpleCpt = here.component "renderRatingSimple" cpt where
...
@@ -151,17 +157,17 @@ renderRatingSimpleCpt = here.component "renderRatingSimple" cpt where
, category
, category
, session
, session
} _ = do
} _ = do
score <- T.useBox $ decodeStar
category
categoryS <- T.useBox
category
pure $ ratingSimple { docId
pure $ ratingSimple { docId
, corpusId
, corpusId
,
score
,
category: categoryS
, session } []
, session } []
type RatingSimpleProps =
type RatingSimpleProps =
( docId :: NodeID
( docId :: NodeID
, corpusId :: NodeID
, corpusId :: NodeID
,
score :: T.Box Star
,
category :: T.Box Category
, session :: Session )
, session :: Session )
ratingSimple :: R2.Component RatingSimpleProps
ratingSimple :: R2.Component RatingSimpleProps
...
@@ -170,19 +176,21 @@ ratingSimpleCpt :: R.Component RatingSimpleProps
...
@@ -170,19 +176,21 @@ ratingSimpleCpt :: R.Component RatingSimpleProps
ratingSimpleCpt = here.component "ratingSimple" cpt where
ratingSimpleCpt = here.component "ratingSimple" cpt where
cpt { docId
cpt { docId
, corpusId
, corpusId
,
score
,
category
, session
, session
} _ = do
} _ = do
score' <- T.useLive T.unequal score
category' <- T.useLive T.unequal category
let star' = cat2star category'
let
let
onClick c _ = do
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'
-- setLocalCategories $ Map.insert r._id c'
launchAff_ do
launchAff_ do
_ <- updateNodeContextCategory session docId corpusId $
star
2score c'
_ <- updateNodeContextCategory session docId corpusId $
cat
2score c'
liftEffect $ T.write_ c'
score
liftEffect $ T.write_ c'
category
pure unit
pure unit
pure $
pure $
...
@@ -190,17 +198,17 @@ ratingSimpleCpt = here.component "ratingSimple" cpt where
...
@@ -190,17 +198,17 @@ ratingSimpleCpt = here.component "ratingSimple" cpt where
{ className: "rating-group" } $
{ className: "rating-group" } $
stars <#> \s ->
stars <#> \s ->
B.iconButton
B.iconButton
{ name: ratingIcon
score
' s
{ name: ratingIcon
category
' s
, callback: onClick s
, callback: onClick s
, overlay: false
, overlay: false
, variant: ratingVariant s
core
' s
, variant: ratingVariant s
tar
' s
, className: ratingClassName s
core
' s
, className: ratingClassName s
tar
' s
}
}
newtype RatingQuery =
newtype RatingQuery =
RatingQuery { nodeIds :: Array Int
RatingQuery { nodeIds :: Array Int
, rating ::
Star
, rating ::
Category
}
}
derive instance Generic RatingQuery _
derive instance Generic RatingQuery _
instance JSON.WriteForeign RatingQuery where
instance JSON.WriteForeign RatingQuery where
...
@@ -267,6 +275,9 @@ icon cat b = btn b $ "fa fa-" <> (color $ size b $ icon' cat b)
...
@@ -267,6 +275,9 @@ icon cat b = btn b $ "fa fa-" <> (color $ size b $ icon' cat b)
icon' Favorite false = "heart-o"
icon' Favorite false = "heart-o"
icon' Favorite true = "heart"
icon' Favorite true = "heart"
icon' ToCite false = "quote-left-o"
icon' ToCite true = "quote-left"
size :: Boolean -> String -> String
size :: Boolean -> String -> String
size true s = s <> " btn-lg"
size true s = s <> " btn-lg"
size false s = s <> " btn-sm"
size false s = s <> " btn-sm"
...
...
src/Gargantext/Components/Category/Types.purs
View file @
c9d48a87
module Gargantext.Components.Category.Types where
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.Eq.Generic (genericEq)
import Data.Generic.Rep (class Generic)
import Data.Maybe (fromMaybe)
import Data.Ord.Generic (genericCompare)
import Data.Show.Generic (genericShow)
import Data.Show.Generic (genericShow)
import Simple.JSON as JSON
import Simple.JSON as JSON
import Gargantext.Prelude
import Gargantext.Prelude
------------------------------------------------------------------------
------------------------------------------------------------------------
data Star = Star_0 | Star_1 | Star_2 | Star_3 | Star_4
data Category = Trash | UnRead | Checked | Topic | Favorite | ToCite
{-
stars :: Array Star
- `UnRead` is assigned initially for new docs
stars = [Star_0, Star_1, Star_2, Star_3, Star_4]
- After reading a doc, `Checked` should be assigned automatically
- Both `Trash` and `UnRead` map to 0 stars in the doc list
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
categories :: Array Category
categories :: Array Category
categories = [Trash, UnRead, Checked, Topic, Favorite]
categories = [Trash, UnRead, Checked, Topic, Favorite
, ToCite
]
derive instance Generic Category _
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 Show Category where show = genericShow
instance Eq Category where eq = genericEq
instance Eq Category where eq = genericEq
instance JSON.ReadForeign Category where
instance JSON.ReadForeign Category where
...
@@ -58,26 +43,75 @@ instance JSON.ReadForeign Category where
...
@@ -58,26 +43,75 @@ instance JSON.ReadForeign Category where
pure $ decodeCategory inst
pure $ decodeCategory inst
instance JSON.WriteForeign Category where writeImpl = JSON.writeImpl <<< cat2score
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 :: Category -> Category
favCategory Favorite = Topic
favCategory Favorite = Topic
favCategory _ = Favorite
favCategory _ = Favorite
trashCategory :: Category -> Category
trashCategory :: Category -> Category
trashCategory _ = Trash
trashCategory = const Trash
-- TODO: ?
--trashCategory Trash = UnRead
decodeCategory :: Int -> Category
decodeCategory :: Int -> Category
decodeCategory 0 = Trash
decodeCategory = toEnumWithDefaults UnRead UnRead
decodeCategory 1 = UnRead
decodeCategory 2 = Checked
decodeCategory 3 = Topic
decodeCategory 4 = Favorite
decodeCategory _ = UnRead
cat2score :: Category -> Int
cat2score :: Category -> Int
cat2score Trash = 0
cat2score = fromEnum
cat2score UnRead = 1
cat2score Checked = 2
------------------------------------------------------------------------
cat2score Topic = 3
-- | This is just a helper to visualize categories.
cat2score Favorite = 4
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
src/Gargantext/Components/DocsTable.purs
View file @
c9d48a87
...
@@ -26,10 +26,10 @@ import Effect.Timer (setTimeout)
...
@@ -26,10 +26,10 @@ import Effect.Timer (setTimeout)
import Gargantext.Components.App.Store (Boxes)
import Gargantext.Components.App.Store (Boxes)
import Gargantext.Components.Bootstrap as B
import Gargantext.Components.Bootstrap as B
import Gargantext.Components.Bootstrap.Types (ComponentStatus(..), ModalSizing(..), Variant(..))
import Gargantext.Components.Bootstrap.Types (ComponentStatus(..), ModalSizing(..), Variant(..))
import Gargantext.Components.Category (rating)
import Gargantext.Components.Category (rating
, ratingSimple
)
import Gargantext.Components.Category.Types (Star(..))
import Gargantext.Components.Category.Types (
Category(..),
Star(..))
import Gargantext.Components.DocsTable.DocumentFormCreation as DFC
import Gargantext.Components.DocsTable.DocumentFormCreation as DFC
import Gargantext.Components.DocsTable.Types (DocumentsView(..), Hyperdata(..), Local
UserScore
, Query, Response(..), Year, sampleData, showSource)
import Gargantext.Components.DocsTable.Types (DocumentsView(..), Hyperdata(..), Local
Categories
, Query, Response(..), Year, sampleData, showSource)
import Gargantext.Components.Nodes.Lists.Types as NT
import Gargantext.Components.Nodes.Lists.Types as NT
import Gargantext.Components.Nodes.Texts.Types as TextsT
import Gargantext.Components.Nodes.Texts.Types as TextsT
import Gargantext.Components.Reload (textsReloadContext)
import Gargantext.Components.Reload (textsReloadContext)
...
@@ -192,7 +192,7 @@ docViewCpt = here.component "docView" cpt where
...
@@ -192,7 +192,7 @@ docViewCpt = here.component "docView" cpt where
, H.div { className: "col d-flex mt-5 mb-2" }
, H.div { className: "col d-flex mt-5 mb-2" }
[ H.div { className: "doc-add-action" }
[ H.div { className: "doc-add-action" }
[ H.button
[ H.button
{ className: "btn btn-light text-primary border-primary"
{ className: "btn btn-light text-primary border-primary"
, on: { click: toggleModal } }
, on: { click: toggleModal } }
[ H.i { className: "fa fa-plus mr-1" } []
[ H.i { className: "fa fa-plus mr-1" } []
...
@@ -304,9 +304,9 @@ searchBarCpt = here.component "searchBar" cpt
...
@@ -304,9 +304,9 @@ searchBarCpt = here.component "searchBar" cpt
, placeholder: "Search in documents"
, placeholder: "Search in documents"
, type: "text" }
, type: "text" }
, H.div {className: "input-group-append"}
, H.div {className: "input-group-append"}
[
[
if query' /= ""
if query' /= ""
then
then
R.fragment
R.fragment
[ clearButton query
[ clearButton query
, searchButton query queryText'
, searchButton query queryText'
...
@@ -450,7 +450,7 @@ pageLayoutCpt = here.component "pageLayout" cpt where
...
@@ -450,7 +450,7 @@ pageLayoutCpt = here.component "pageLayout" cpt where
, spinnerClass: Nothing
, spinnerClass: Nothing
}
}
NT.CacheOff -> do
NT.CacheOff -> do
localCategories <- T.useBox (Map.empty :: Local
UserScore
)
localCategories <- T.useBox (Map.empty :: Local
Categories
)
paramsS <- T.useBox params
paramsS <- T.useBox params
paramsS' <- T.useLive T.unequal paramsS
paramsS' <- T.useLive T.unequal paramsS
let loader p = do
let loader p = do
...
@@ -501,7 +501,7 @@ pagePaintCpt = here.component "pagePaintCpt" cpt
...
@@ -501,7 +501,7 @@ pagePaintCpt = here.component "pagePaintCpt" cpt
cpt { documents, layout, params } _ = do
cpt { documents, layout, params } _ = do
params' <- T.useLive T.unequal params
params' <- T.useLive T.unequal params
localCategories <- T.useBox (Map.empty :: Local
UserScore
)
localCategories <- T.useBox (Map.empty :: Local
Categories
)
pure $ pagePaintRaw { documents: A.fromFoldable (filteredRows params')
pure $ pagePaintRaw { documents: A.fromFoldable (filteredRows params')
, layout
, layout
, localCategories
, localCategories
...
@@ -522,7 +522,7 @@ pagePaintCpt = here.component "pagePaintCpt" cpt
...
@@ -522,7 +522,7 @@ pagePaintCpt = here.component "pagePaintCpt" cpt
type PagePaintRawProps =
type PagePaintRawProps =
( documents :: Array DocumentsView
( documents :: Array DocumentsView
, layout :: Record PageLayoutProps
, layout :: Record PageLayoutProps
, localCategories :: T.Box Local
UserScore
, localCategories :: T.Box Local
Categories
, params :: T.Box TT.Params
, params :: T.Box TT.Params
)
)
...
@@ -557,73 +557,141 @@ pagePaintRawCpt = here.component "pagePaintRaw" cpt where
...
@@ -557,73 +557,141 @@ pagePaintRawCpt = here.component "pagePaintRaw" cpt where
{ colNames
{ colNames
, container: TT.defaultContainer
, container: TT.defaultContainer
, params
, params
, rows: rows reload chartReload localCategories' mCurrentDocId'
, rows: rows { boxes
, reload
, chartReload
, frontends
, listId
, localCategories: localCategories'
, mCorpusId
, mCurrentDocId
, nodeId
, session
, sidePanel }
, syncResetButton : [ H.div {} [] ]
, syncResetButton : [ H.div {} [] ]
, totalRecords
, totalRecords
, wrapColElts
, wrapColElts
}
}
where
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)
-- checked = Star_1 == cat
selected = mCurrentDocId' == Just r._id
sid = sessionId session
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
corpusDocument
| Just cid <- mCorpusId = Routes.CorpusDocument sid cid listId
| Just cid <- mCorpusId = Routes.CorpusDocument sid cid listId
| otherwise = Routes.Document sid listId
| otherwise = Routes.Document sid listId
colNames = TT.ColumnName <$> [ "Show", "Tag", "Date", "Title", "Source", "Score" ]
wrapColElts = const identity
categoryS <- T.useBox cat
rows reload chartReload localCategories' mCurrentDocId' = row <$> A.toUnfoldable documents
categoryS' <- T.useLive T.unequal categoryS
where
row dv@(DocumentsView r@{ _id, category }) =
let tClassName = trashClassName categoryS' selected
{ row:
TT.makeRow'
pure $ TT.makeRow' { className: "page-paint-raw " <>
{ className: "page-paint-raw " <>
(selected ?
(selected ?
"page-paint-raw--selected" $
"page-paint-raw--selected" $
""
""
)
)
}
}
[ -- H.div {} [ H.a { className, style, on: {click: click Favorite} } [] ]
[ -- H.div {} [ H.a { className, style, on: {click: click Favorite} } [] ]
H.div { className: "" }
H.div { className: "" }
[ docChooser { boxes
[ docChooser { boxes
, listId
, listId
, mCorpusId
, mCorpusId
, nodeId: r._id
, nodeId: r._id
, sidePanel } []
, sidePanel } []
]
]
--, H.div { className: "column-tag flex" } [ caroussel { category: cat, nodeId, row: dv, session, setLocalCategories } [] ]
--, H.div { className: "column-tag flex" } [ caroussel { category: cat, nodeId, row: dv, session, setLocalCategories } [] ]
, H.div { className: "column-tag flex" }
, H.div { className: "column-tag flex" }
[ ratingSimple { -- chartReload
[ rating { chartReload
docId: _id
, nodeId
, category: categoryS
, row: dv
, corpusId: nodeId
, score: cat
-- , row: dv
, setLocalCategories: \lc -> T.modify_ lc localCategories
, session
, 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.input { type: "checkbox", defaultValue: checked, on: {click: click Trash} }
, H.div { className: tClassName } [ R2.showText r.date ]
-- TODO show date: Year-Month-Day only
,
, H.div { className: tClassName } [ R2.showText r.date ]
H.div
,
{ className: tClassName }
H.div
[
{ className: tClassName }
H.a
[
{ href: url frontends $ corpusDocument r._id
H.a
, target: "_blank"
{ href: url frontends $ corpusDocument r._id
, className: "text-primary"
, target: "_blank"
}
, className: "text-primary"
[ H.text r.title
}
, H.i { className: "fa fa-external-link mx-1 small" } []
[ H.text r.title
]
, H.i { className: "fa fa-external-link mx-1 small" } []
]
]
, H.div { className: tClassName } [ H.text $ showSource r.source ]
]
, H.div {} [ H.text $ maybe "-" show r.ngramCount ]
, 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 = (
type DocChooser = (
boxes :: Boxes
boxes :: Boxes
...
...
src/Gargantext/Components/DocsTable/Types.purs
View file @
c9d48a87
...
@@ -7,14 +7,14 @@ import Data.Generic.Rep (class Generic)
...
@@ -7,14 +7,14 @@ import Data.Generic.Rep (class Generic)
import Data.Map (Map)
import Data.Map (Map)
import Data.Maybe (Maybe(..), fromMaybe)
import Data.Maybe (Maybe(..), fromMaybe)
import Data.Tuple (Tuple(..))
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
import Simple.JSON as JSON
data Action
data Action
= MarkCategory Int Category
= MarkCategory Int Category
type DocumentsViewT =
type DocumentsViewT =
( category ::
Star
( category ::
Category
, date :: Int
, date :: Int
, ngramCount :: Maybe Int
, ngramCount :: Maybe Int
, score :: Maybe Int
, score :: Maybe Int
...
@@ -65,8 +65,8 @@ type ResponseT =
...
@@ -65,8 +65,8 @@ type ResponseT =
, score :: Maybe Int
, score :: Maybe Int
, title :: String )
, title :: String )
newtype Response = Response
newtype Response = Response
{ cid
:: Int
{ cid :: Int
, category ::
Star
, category ::
Category
| ResponseT
| ResponseT
}
}
...
@@ -74,7 +74,7 @@ instance JSON.ReadForeign Response where
...
@@ -74,7 +74,7 @@ instance JSON.ReadForeign Response where
readImpl f = do
readImpl f = do
{ category, id, hyperdata, ngramCount, score, title } :: { category :: Int, id :: Int | ResponseT } <- JSON.readImpl f
{ 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: decodeCategory category, cid, hyperdata, ngramCount, score, title }
pure $ Response { category: decode
Star
category
pure $ Response { category: decode
Category
category
, cid: id
, cid: id
, hyperdata
, hyperdata
, ngramCount
, ngramCount
...
@@ -110,7 +110,7 @@ sampleData' = DocumentsView { _id : 1
...
@@ -110,7 +110,7 @@ sampleData' = DocumentsView { _id : 1
, date : 2010
, date : 2010
, title : "title"
, title : "title"
, source : Just "source"
, source : Just "source"
, category :
Star_1
, category :
UnRead
, ngramCount : Just 1
, ngramCount : Just 1
, score: Just 1 }
, score: Just 1 }
...
@@ -121,7 +121,7 @@ sampleData = map (\(Tuple t s) -> DocumentsView { _id : 1
...
@@ -121,7 +121,7 @@ sampleData = map (\(Tuple t s) -> DocumentsView { _id : 1
, date : 2017
, date : 2017
, title: t
, title: t
, source: Just s
, source: Just s
, category :
Star_1
, category :
UnRead
, ngramCount : Just 10
, ngramCount : Just 10
, score: Just 1 }) sampleDocuments
, score: Just 1 }) sampleDocuments
...
...
src/Gargantext/Components/Document/Layout.purs
View file @
c9d48a87
...
@@ -16,7 +16,6 @@ import Gargantext.Components.AutoUpdate (autoUpdate)
...
@@ -16,7 +16,6 @@ import Gargantext.Components.AutoUpdate (autoUpdate)
import Gargantext.Components.Bootstrap as B
import Gargantext.Components.Bootstrap as B
import Gargantext.Components.Bootstrap.Types (ComponentStatus(..), SpinnerTheme(..))
import Gargantext.Components.Bootstrap.Types (ComponentStatus(..), SpinnerTheme(..))
import Gargantext.Components.Category (ratingSimpleLoader)
import Gargantext.Components.Category (ratingSimpleLoader)
import Gargantext.Components.Category.Types (decodeStar)
import Gargantext.Components.Document.Types (DocPath, Document(..), LoadedData, initialState)
import Gargantext.Components.Document.Types (DocPath, Document(..), LoadedData, initialState)
import Gargantext.Components.NgramsTable.AutoSync (useAutoSync)
import Gargantext.Components.NgramsTable.AutoSync (useAutoSync)
import Gargantext.Components.Node (NodePoly(..))
import Gargantext.Components.Node (NodePoly(..))
...
...
src/Gargantext/Components/FacetsTable.purs
View file @
c9d48a87
...
@@ -395,6 +395,7 @@ pageCpt = here.component "page" cpt
...
@@ -395,6 +395,7 @@ pageCpt = here.component "page" cpt
wrapColElts = const identity
wrapColElts = const identity
-- TODO: how to interprete other scores?
-- TODO: how to interprete other scores?
gi Trash = "fa fa-star-empty"
gi Trash = "fa fa-star-empty"
gi UnRead = "fa fa-star-empty"
gi _ = "fa fa-star"
gi _ = "fa fa-star"
documentUrl id { listId, nodeId } =
documentUrl id { listId, nodeId } =
...
...
Write
Preview
Markdown
is supported
0%
Try again
or
attach a new file
Attach a file
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Cancel
Please
register
or
sign in
to comment