Commit e72762fe authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

Merge branch 'dev' into 395-dev-ps-0.15-update

parents c9c3dc2a ff2130a2
Pipeline #3077 canceled with stage
...@@ -12,6 +12,8 @@ ...@@ -12,6 +12,8 @@
<body> <body>
<div id="app"></div> <div id="app"></div>
<div id="portal"></div> <div id="portal"></div>
<script src="js/jquery@3.5.1/jquery.slim.min.js"></script>
<script src="js/bootstrap@4.6.2/bootstrap.bundle.min.js"></script>
<script src="bundle.js"></script> <script src="bundle.js"></script>
</body> </body>
</html> </html>
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
{ {
"name": "Gargantext", "name": "Gargantext",
"version": "0.0.5.9", "version": "0.0.5.9.5",
"scripts": { "scripts": {
"generate-purs-packages-nix": "./nix/generate-purs-packages.nix", "generate-purs-packages-nix": "./nix/generate-purs-packages.nix",
"generate-psc-packages-nix": "./nix/generate-packages-json.bash", "generate-psc-packages-nix": "./nix/generate-packages-json.bash",
......
...@@ -22,7 +22,7 @@ import Data.Tuple (Tuple(..), snd) ...@@ -22,7 +22,7 @@ import Data.Tuple (Tuple(..), snd)
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import Effect (Effect) import Effect (Effect)
import Gargantext.Components.Annotation.Menu (annotationMenu, AnnotationMenu) import Gargantext.Components.Annotation.Menu (annotationMenu, AnnotationMenu)
import Gargantext.Components.Annotation.Types (termClass, MenuType(..)) import Gargantext.Components.Annotation.Types (MenuType(..), ModeType(..), termClass)
import Gargantext.Core.NgramsTable.Functions (findNgramTermList, highlightNgrams, normNgram) 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.Types (CTabNgramType(..), TermList)
...@@ -42,6 +42,7 @@ type Props = ...@@ -42,6 +42,7 @@ type Props =
( ngrams :: NgramsTable ( ngrams :: NgramsTable
, setTermList :: NgramsTerm -> Maybe TermList -> TermList -> Effect Unit , setTermList :: NgramsTerm -> Maybe TermList -> TermList -> Effect Unit
, text :: Maybe String , text :: Maybe String
, mode :: ModeType
) )
type MouseEvent = E.SyntheticEvent DE.MouseEvent type MouseEvent = E.SyntheticEvent DE.MouseEvent
...@@ -73,7 +74,7 @@ annotatedFieldInner = R2.leafComponent annotatedFieldInnerCpt ...@@ -73,7 +74,7 @@ annotatedFieldInner = R2.leafComponent annotatedFieldInnerCpt
annotatedFieldInnerCpt :: R.Component InnerProps annotatedFieldInnerCpt :: R.Component InnerProps
annotatedFieldInnerCpt = here.component "annotatedFieldInner" cpt where annotatedFieldInnerCpt = here.component "annotatedFieldInner" cpt where
cpt { menuRef, ngrams, redrawMenu, setTermList, text: fieldText } _ = do cpt { menuRef, ngrams, redrawMenu, setTermList, text: fieldText, mode } _ = do
_redrawMenu' <- T.useLive T.unequal redrawMenu _redrawMenu' <- T.useLive T.unequal redrawMenu
-- menu <- T.useBox (Nothing :: Maybe (Record AnnotationMenu)) -- menu <- T.useBox (Nothing :: Maybe (Record AnnotationMenu))
...@@ -89,9 +90,29 @@ annotatedFieldInnerCpt = here.component "annotatedFieldInner" cpt where ...@@ -89,9 +90,29 @@ annotatedFieldInnerCpt = here.component "annotatedFieldInner" cpt where
[ [
annotationMenu { menuRef } annotationMenu { menuRef }
, ,
H.div case mode of
{ className: "annotated-field-runs" }
((\p -> annotateRun p) <$> wrap <$> compile ngrams fieldText) EditionMode ->
H.div
{ className: "annotated-field-runs" }
((\p -> annotateRun p) <$> wrap <$> compile ngrams fieldText)
AdditionMode ->
R2.fromMaybe fieldText \t ->
H.div
{ className: "annotated-field-runs" }
[
annotateRun
{ list: mempty
, text: t
, onSelect: onAnnotationSelect { menuRef, ngrams, redrawMenu, setTermList }
}
]
] ]
----------------------------------------------------------- -----------------------------------------------------------
......
module Gargantext.Components.Annotation.Types module Gargantext.Components.Annotation.Types
( MenuType(..) ( MenuType(..)
, termClass , termClass
, ModeType(..)
) )
where where
...@@ -8,14 +9,36 @@ import Gargantext.Prelude ...@@ -8,14 +9,36 @@ import Gargantext.Prelude
import Data.Eq.Generic (genericEq) import Data.Eq.Generic (genericEq)
import Data.Generic.Rep (class Generic) import Data.Generic.Rep (class Generic)
import Data.Maybe (Maybe(..))
import Data.Show.Generic (genericShow)
import Gargantext.Types (TermList(..)) import Gargantext.Types (TermList(..))
---------------------------------------------------------
data MenuType = NewNgram | SetTermListItem data MenuType = NewNgram | SetTermListItem
derive instance Generic MenuType _ derive instance Generic MenuType _
instance Eq MenuType where instance Eq MenuType where
eq = genericEq eq = genericEq
----------------------------------------------------------
termClass :: TermList -> String termClass :: TermList -> String
termClass CandidateTerm = "candidate-term" termClass CandidateTerm = "candidate-term"
termClass MapTerm = "graph-term" termClass MapTerm = "graph-term"
termClass StopTerm = "stop-term" termClass StopTerm = "stop-term"
---------------------------------------------------------
data ModeType
= EditionMode
| AdditionMode
derive instance Generic ModeType _
instance Eq ModeType where eq = genericEq
instance Show ModeType where show = genericShow
instance Read ModeType where
read :: String -> Maybe ModeType
read = case _ of
"EditionMode" -> Just EditionMode
"AdditionMode" -> Just AdditionMode
_ -> Nothing
'use strict'; 'use strict';
exports._addClassName = function(window, className) { exports._show = show;
window.document.body.classList.add(className); exports._hide = hide;
/**
* @function show
* @param {Window} window
* @param {string} querySelector
* @unpure {Object} window.$
*/
function show(window, querySelector) {
window.$(querySelector).modal('show');
} }
/**
exports._removeClassName = function(window, className) { * @function hide
window.document.body.classList.remove(className); * @param {Window} window
* @param {string} querySelector
* @unpure {Object} window.$
*/
function hide(window, querySelector) {
window.$(querySelector).modal('hide');
// @XXX Bootstrap not removing some modal elements on "hide" method
// @https://stackoverflow.com/questions/50168312/bootstrap-4-close-modal-backdrop-doesnt-disappear
window.$('body').removeClass('modal-open');
window.$('body').css('padding-right', '0');
window.$('.modal-backdrop').remove();
} }
module Gargantext.Components.Bootstrap.BaseModal (baseModal) where module Gargantext.Components.Bootstrap.BaseModal
(baseModal
, showModal, hideModal
) where
import Gargantext.Prelude import Gargantext.Prelude
import DOM.Simple (Window, window) import DOM.Simple (Window, window)
import Data.Foldable (intercalate) import Data.Foldable (intercalate)
import Data.Maybe (Maybe(..))
import Data.UUID as UUID
import Effect (Effect) import Effect (Effect)
import Effect.Uncurried (EffectFn2, runEffectFn2) import Effect.Uncurried (EffectFn2, runEffectFn2)
import Gargantext.Utils (nbsp, (?)) import Gargantext.Components.Bootstrap.Types (ModalSizing(..))
import Gargantext.Hooks.UpdateEffect (useUpdateEffect1')
import Gargantext.Utils ((?))
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import Reactix as R import Reactix as R
import Reactix.DOM.HTML as H import Reactix.DOM.HTML as H
import Toestand as T import Toestand as T
foreign import _addClassName :: EffectFn2 Window String Unit foreign import _show :: EffectFn2
foreign import _removeClassName :: EffectFn2 Window String Unit Window
String
Unit
showModal ::
Window
-> String
-> Effect Unit
showModal = runEffectFn2 _show
foreign import _hide :: EffectFn2
Window
String
Unit
hideModal ::
Window
-> String
-> Effect Unit
hideModal = runEffectFn2 _hide
type Props = type Props =
( isVisibleBox :: T.Box Boolean ( isVisibleBox :: T.Box Boolean
| Options | Options
) )
type Options = type Options =
( id :: String ( modalClassName :: String
, title :: String , title :: Maybe String
, hasBackground :: Boolean , hasCollapsibleBackground :: Boolean
, hasCollapsibleBackground :: Boolean , hasInnerScroll :: Boolean
, noHeader :: Boolean
, noBody :: Boolean -- ie. Bootstrap Body
, size :: ModalSizing
) )
options :: Record Options options :: Record Options
options = options =
{ id: "" { modalClassName : ""
, title: "" , title : Nothing
, hasBackground: true , hasCollapsibleBackground : true
, hasCollapsibleBackground: true , hasInnerScroll : false
, noHeader : false
, noBody : false
, size : MediumModalSize
} }
componentName :: String componentName :: String
componentName = "b-modal" componentName = "b-modal"
vendorName :: String -- | Structural Component for the Bootstrap modal
vendorName = "modal" -- |
-- | @XXX Bootstrap not removing some modal elements on "hide" method
-- | This implies that:
-- | - a FFI fix has been added to remove left elements
-- | - an overlay has been added to synchronise the close button
-- | - the keyboard shortcut has been removed
-- | @https://stackoverflow.com/questions/50168312/bootstrap-4-close-modal-backdrop-doesnt-disappear
-- |
-- | https://getbootstrap.com/docs/4.6/components/modal/
baseModal :: forall r. R2.OptComponent Options Props r baseModal :: forall r. R2.OptComponent Options Props r
baseModal = R2.optComponent component options baseModal = R2.optComponent component options
component :: R.Component Props component :: R.Component Props
component = R.hooksComponent componentName cpt where component = R.hooksComponent componentName cpt where
cpt { isVisibleBox cpt props@{ isVisibleBox
, id , title
, title , hasCollapsibleBackground
, hasBackground , hasInnerScroll
, hasCollapsibleBackground , noHeader
} children = do , noBody
-- State , size
} children
= R.unsafeHooksEffect (UUID.genUUID >>= pure <<< UUID.toString)
>>= \uuid -> do
-- | States
-- |
isVisible <- R2.useLive' isVisibleBox isVisible <- R2.useLive' isVisibleBox
-- Hooks -- | Computed
R.useEffect1' isVisible $ -- |
(isVisible ? addClassName $ removeClassName) window "modal-open"
-- Computed
let let
className = intercalate " " className = intercalate " "
-- Component -- Component
[ componentName [ componentName
, isVisible ? -- Bootstrap
componentName <> "--visible" $ , "modal"
componentName <> "--hidden"
-- Vendor
, vendorName
] ]
hasHeader = not $ eq title "" id = componentName <> "-" <> uuid
-- Render selector = "#" <> id
-- | Hooks
-- |
useUpdateEffect1' isVisible
if isVisible
then showModal window selector
else hideModal window selector
-- | Behaviors
-- |
let
onCloseButtonClick _ = T.modify_ (not) isVisibleBox
-- [ Render
-- |
R.createPortal R.createPortal
[ [
H.div H.div
{ id { id: id
, className , className
, role: "dialog" , tabIndex: "-1"
, data: { show: true }
, key: id , key: id
, data:
{ keyboard: "false"
, backdrop: hasCollapsibleBackground ?
"true" $
"static"
}
} }
[ [
R2.when (hasBackground) $ -- Overlay fixing collapsable click event
R2.when (hasCollapsibleBackground) $
H.div H.div
{ className: intercalate " " { className: componentName <> "__overlay"
[ componentName <> "__overlay" , on: { click: onCloseButtonClick }
, hasCollapsibleBackground ?
componentName <> "__overlay--collapsible" $
""
]
, on: { click: hasCollapsibleBackground ?
toggle isVisibleBox $
const $ pure unit
}
} }
[ H.text $ nbsp 1 ] []
, ,
H.div H.div
{ className: "modal-dialog modal-lg" { className: intercalate " "
, role: "document" -- Bootstrap classNames
[ "modal-dialog"
, show size
, "modal-dialog-centered"
, hasInnerScroll ? "modal-dialog-scrollable" $ ""
-- provided custom className
, props.modalClassName
]
} }
[ [
H.div H.div
{ className: intercalate " " { className: intercalate " "
[ componentName <> "__content" [ componentName <> "__content"
, vendorName <> "-content" , "modal-content"
] ]
} }
[ [
R2.when (hasHeader) $ -- Header
R2.when (not noHeader) $
H.div H.div
{ className: intercalate " " { className: intercalate " "
[ componentName <> "__header" [ componentName <> "__header"
, vendorName <> "-header" , "modal-header"
] ]
} }
[ [
H.div R2.fromMaybe (title) \title' ->
{ className: componentName <> "__header__content" }
[ H.text title ] H.div
{ className: componentName <> "__header__title" }
[ H.text title' ]
, ,
H.button H.button
{ type: "button" { type: "button"
, className: "close"
, data: { dismiss: "modal" }
} }
[ [
H.a H.a
{ on: { click: toggle isVisibleBox } {
, className: "btn fa fa-times" } on: { click: onCloseButtonClick }
, className: "btn fa fa-times"
}
[] []
] ]
] ]
, ,
-- Body
H.div H.div
{ className: "modal-body" } { className: intercalate " "
[ componentName <> "__body"
, noBody ? "" $ "modal-body"
]
}
children children
] ]
] ]
] ]
] ]
<$> R2.getPortalHost <$> R2.getPortalHost
toggle :: forall event. T.Box Boolean -> event -> Effect Unit
toggle box _ = T.modify_ not box
addClassName :: Window -> String -> Effect Unit
addClassName = runEffectFn2 _addClassName
removeClassName :: Window -> String -> Effect Unit
removeClassName = runEffectFn2 _removeClassName
...@@ -42,7 +42,7 @@ options = ...@@ -42,7 +42,7 @@ options =
-- | Structural Component for the Bootstrap button -- | Structural Component for the Bootstrap button
-- | -- |
-- | https://getbootstrap.com/docs/4.0/components/buttons/ -- | https://getbootstrap.com/docs/4.6/components/buttons/
button :: forall r. R2.OptComponent Options Props r button :: forall r. R2.OptComponent Options Props r
button = R2.optComponent component options button = R2.optComponent component options
......
...@@ -6,6 +6,7 @@ module Gargantext.Components.Bootstrap.Types ...@@ -6,6 +6,7 @@ module Gargantext.Components.Bootstrap.Types
, TooltipEffect(..), TooltipPosition(..) , TooltipEffect(..), TooltipPosition(..)
, Position(..) , Position(..)
, Elevation(..) , Elevation(..)
, ModalSizing(..)
) where ) where
import Gargantext.Prelude import Gargantext.Prelude
...@@ -164,7 +165,7 @@ instance Show TooltipPosition where ...@@ -164,7 +165,7 @@ instance Show TooltipPosition where
---------------------------------------------------------------------- ----------------------------------------------------------------------
-- | Elevarion measure scale values used on various custom components -- | Elevation measure scale values used on various custom components
-- | and properties -- | and properties
-- | -- |
-- | Example: https://material.io/design/environment/elevation.html -- | Example: https://material.io/design/environment/elevation.html
...@@ -176,3 +177,22 @@ data Elevation ...@@ -176,3 +177,22 @@ data Elevation
derive instance Generic Elevation _ derive instance Generic Elevation _
derive instance Eq Elevation derive instance Eq Elevation
instance Show Elevation where show = kebabCase <<< genericShow instance Show Elevation where show = kebabCase <<< genericShow
----------------------------------------------------------------------
-- | Modal custom sizing used by Bootstrap for its modals
-- |
-- | https://getbootstrap.com/docs/4.6/components/modal/#optional-sizes
data ModalSizing
= SmallModalSize
| MediumModalSize
| LargeModalSize
| ExtraLargeModalSize
derive instance Generic ModalSizing _
derive instance Eq ModalSizing
instance Show ModalSizing where
show SmallModalSize = "modal-sm"
show MediumModalSize = ""
show LargeModalSize = "modal-lg"
show ExtraLargeModalSize = "modal-xl"
...@@ -9,12 +9,15 @@ import Data.Map as Map ...@@ -9,12 +9,15 @@ import Data.Map as Map
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Effect.Aff (launchAff_) import Effect.Aff (launchAff_)
import Effect.Class (liftEffect) 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, star2score, stars) import Gargantext.Components.Category.Types (Category(..), Star(..), cat2score, categories, clickAgain, star2score, stars)
import Gargantext.Components.DocsTable.Types (DocumentsView(..), LocalCategories, LocalUserScore) import Gargantext.Components.DocsTable.Types (DocumentsView(..), LocalCategories, LocalUserScore)
import Gargantext.Config.REST (AffRESTError) import Gargantext.Config.REST (AffRESTError)
import Gargantext.Routes (SessionRoute(NodeAPI)) import Gargantext.Routes (SessionRoute(NodeAPI))
import Gargantext.Sessions (Session, put) import Gargantext.Sessions (Session, put)
import Gargantext.Types (NodeID, NodeType(..)) import Gargantext.Types (NodeID, NodeType(..))
import Gargantext.Utils ((?))
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Toestand as T2 import Gargantext.Utils.Toestand as T2
import Reactix as R import Reactix as R
...@@ -42,23 +45,53 @@ ratingCpt = here.component "rating" cpt where ...@@ -42,23 +45,53 @@ ratingCpt = here.component "rating" cpt where
, row: DocumentsView r , row: DocumentsView r
, score , score
, session , session
, setLocalCategories } _ = , setLocalCategories
pure $ H.div { className:"flex" } divs where } _ = do
divs = map (\s -> H.div { className : icon' score s -- | Computed
, on: { click: onClick s } } []) stars -- |
icon' Star_0 Star_0 = "fa fa-times-circle" let
icon' _ Star_0 = "fa fa-times" icon' Star_0 Star_0 = "times-circle"
icon' c s = if star2score c < star2score s then "fa fa-star-o" else "fa fa-star" icon' _ Star_0 = "times"
icon' c s = star2score c < star2score s ? "star-o" $ "star"
variant' Star_0 Star_0 = Dark
variant' _ Star_0 = Dark
variant' _ _ = Dark
className' Star_0 Star_0 = "rating-group__action"
className' _ Star_0 = "rating-group__action"
className' _ _ = "rating-group__star"
-- | Behaviors
-- |
let
onClick c _ = do onClick c _ = do
let c' = if score == c let c' = score == c ? clickAgain c $ c
then clickAgain c
else c
setLocalCategories $ Map.insert r._id c' setLocalCategories $ Map.insert r._id c'
launchAff_ $ do launchAff_ do
_ <- putRating session nodeId $ RatingQuery { nodeIds: [r._id], rating: c' } _ <- putRating session nodeId $ RatingQuery
{ nodeIds: [r._id]
, rating: c'
}
liftEffect $ T2.reload chartReload liftEffect $ T2.reload chartReload
-- | Render
-- |
pure $
H.div
{ className: "rating-group" } $
stars <#> \s ->
B.iconButton
{ name: icon' score s
, callback: onClick s
, overlay: false
, variant: variant' score s
, className: className' score s
}
newtype RatingQuery = newtype RatingQuery =
RatingQuery { nodeIds :: Array Int RatingQuery { nodeIds :: Array Int
, rating :: Star , rating :: Star
......
...@@ -6,7 +6,6 @@ import Gargantext.Prelude ...@@ -6,7 +6,6 @@ import Gargantext.Prelude
import DOM.Simple.Event as DE import DOM.Simple.Event as DE
import Data.Array (any) import Data.Array (any)
import Data.Array as A import Data.Array as A
import Data.Either (Either)
import Data.Generic.Rep (class Generic) import Data.Generic.Rep (class Generic)
import Data.Lens ((^.)) import Data.Lens ((^.))
import Data.Lens.At (at) import Data.Lens.At (at)
...@@ -27,7 +26,7 @@ import Effect.Class (liftEffect) ...@@ -27,7 +26,7 @@ import Effect.Class (liftEffect)
import Effect.Timer (setTimeout) 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(..)) import Gargantext.Components.Bootstrap.Types (ComponentStatus(..), ModalSizing(..), Variant(..))
import Gargantext.Components.Category (rating) import Gargantext.Components.Category (rating)
import Gargantext.Components.Category.Types (Star(..)) import Gargantext.Components.Category.Types (Star(..))
import Gargantext.Components.DocsTable.DocumentFormCreation as DFC import Gargantext.Components.DocsTable.DocumentFormCreation as DFC
...@@ -228,8 +227,9 @@ docViewCpt = here.component "docView" cpt where ...@@ -228,8 +227,9 @@ docViewCpt = here.component "docView" cpt where
-- Document Creation Modal -- Document Creation Modal
B.baseModal B.baseModal
{ isVisibleBox: isDocumentModalVisibleBox { isVisibleBox: isDocumentModalVisibleBox
, title: "Add a new document" , title: Just "Add a new document"
, hasCollapsibleBackground: false , hasCollapsibleBackground: false
, size: LargeModalSize
} }
[ [
DFC.documentFormCreation DFC.documentFormCreation
...@@ -540,6 +540,9 @@ pagePaintRawCpt = here.component "pagePaintRaw" cpt where ...@@ -540,6 +540,9 @@ pagePaintRawCpt = here.component "pagePaintRaw" cpt where
reload <- T.useBox GUT.newReload reload <- T.useBox GUT.newReload
localCategories' <- T.useLive T.unequal localCategories localCategories' <- T.useLive T.unequal localCategories
let
selected = mCurrentDocId' == Just nodeId
pure $ TT.table pure $ TT.table
{ colNames { colNames
, container: TT.defaultContainer , container: TT.defaultContainer
...@@ -551,9 +554,9 @@ pagePaintRawCpt = here.component "pagePaintRaw" cpt where ...@@ -551,9 +554,9 @@ pagePaintRawCpt = here.component "pagePaintRaw" cpt where
} }
where where
sid = sessionId session sid = sessionId session
trashClassName Star_0 _ = "trash" trashClassName Star_0 _ = "page-paint-row page-paint-row--trash"
trashClassName _ true = "active" trashClassName _ true = "page-paint-row page-paint-row--active"
trashClassName _ false = "" 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
...@@ -563,7 +566,14 @@ pagePaintRawCpt = here.component "pagePaintRaw" cpt where ...@@ -563,7 +566,14 @@ pagePaintRawCpt = here.component "pagePaintRaw" cpt where
where where
row dv@(DocumentsView r@{ _id, category }) = row dv@(DocumentsView r@{ _id, category }) =
{ row: { row:
TT.makeRow [ -- H.div {} [ H.a { className, style, on: {click: click Favorite} } [] ] TT.makeRow'
{ className: "page-paint-raw " <>
(selected ?
"page-paint-raw--selected" $
""
)
}
[ -- H.div {} [ H.a { className, style, on: {click: click Favorite} } [] ]
H.div { className: "" } H.div { className: "" }
[ docChooser { boxes [ docChooser { boxes
, listId , listId
...@@ -582,10 +592,17 @@ pagePaintRawCpt = here.component "pagePaintRaw" cpt where ...@@ -582,10 +592,17 @@ pagePaintRawCpt = here.component "pagePaintRaw" cpt where
--, H.input { type: "checkbox", defaultValue: checked, on: {click: click Trash} } --, H.input { type: "checkbox", defaultValue: checked, on: {click: click Trash} }
-- TODO show date: Year-Month-Day only -- TODO show date: Year-Month-Day only
, H.div { className: tClassName } [ R2.showText r.date ] , H.div { className: tClassName } [ R2.showText r.date ]
, H.div { className: tClassName } ,
[ H.a { href: url frontends $ corpusDocument r._id, target: "_blank" } H.div
[ H.text r.title ] { className: tClassName }
] [
H.a
{ href: url frontends $ corpusDocument r._id
, target: "_blank"
, className: "text-primary"
}
[ H.text r.title ]
]
, H.div { className: tClassName } [ H.text $ showSource r.source ] , H.div { className: tClassName } [ H.text $ showSource r.source ]
, H.div {} [ H.text $ maybe "-" show r.ngramCount ] , H.div {} [ H.text $ maybe "-" show r.ngramCount ]
] ]
...@@ -623,11 +640,19 @@ docChooserCpt = here.component "docChooser" cpt ...@@ -623,11 +640,19 @@ docChooserCpt = here.component "docChooser" cpt
mCurrentDocId' <- T.useLive T.unequal mCurrentDocId mCurrentDocId' <- T.useLive T.unequal mCurrentDocId
let selected = mCurrentDocId' == Just nodeId let selected = mCurrentDocId' == Just nodeId
eyeClass = if selected then "fa-eye" else "fa-eye-slash" eyeClass = selected ? "eye" $ "eye-slash"
variant = selected ? Info $ Dark
pure $ H.div { className: "btn" } [ pure $
H.span { className: "fa " <> eyeClass H.div
, on: { click: onClick selected } } [] { className: "doc-chooser" }
[
B.iconButton
{ name: eyeClass
, overlay: false
, variant
, callback: onClick selected
}
] ]
where where
onClick selected _ = do onClick selected _ = do
......
This diff is collapsed.
...@@ -28,19 +28,24 @@ nodePopupViewCpt :: R.Component NodePopupProps ...@@ -28,19 +28,24 @@ nodePopupViewCpt :: R.Component NodePopupProps
nodePopupViewCpt = here.component "nodePopupView" cpt where nodePopupViewCpt = here.component "nodePopupView" cpt where
cpt props _ = do cpt props _ = do
pure $ H.div tooltipProps pure $
[ H.div { className: "popup-container" }
[ H.div { className: "card" } H.div
[ panelHeading props { className: "node-popup-tooltip"
]]] , title: "Node settings"
}
closePopover props = props.onPopoverClose <<< R.unsafeEventTarget [
H.div
tooltipProps = { id: "node-popup-tooltip", title: "Node settings" { className: "popup-container card" }
, data: { toggle: "tooltip", placement: "right" } } [
panelHeading props
]
]
closeBox props = props.onPopoverClose <<< R.unsafeEventTarget
panelHeading props@{ nodeType } = panelHeading props@{ nodeType } =
H.div { className: "card-header" } H.div { className: "popup-container__header card-header" }
[ R2.row [ R2.row
[ H.div { className: "col-4" } [ H.div { className: "col-4" }
[ H.span { className: GT.fldr nodeType true} [] -- TODO fix names [ H.span { className: GT.fldr nodeType true} [] -- TODO fix names
...@@ -48,5 +53,5 @@ nodePopupViewCpt = here.component "nodePopupView" cpt where ...@@ -48,5 +53,5 @@ nodePopupViewCpt = here.component "nodePopupView" cpt where
, H.div { className: "col-6" } , H.div { className: "col-6" }
[ H.span { className: "text-primary center" } [ H.text props.name ] ] [ H.span { className: "text-primary center" } [ H.text props.name ] ]
, H.div { className: "col-1" } , H.div { className: "col-1" }
[ H.a { type: "button", on: { click: closePopover props }, title: "Close" [ H.a { type: "button", on: { click: closeBox props }, title: "Close"
, className: glyphicon "window-close" } [] ]]] , className: glyphicon "window-close" } [] ]]]
...@@ -7,7 +7,6 @@ import Data.Array as Array ...@@ -7,7 +7,6 @@ import Data.Array as Array
import Data.Maybe (Maybe(..), isJust) import Data.Maybe (Maybe(..), isJust)
import Data.Traversable (intercalate, traverse, traverse_) import Data.Traversable (intercalate, traverse, traverse_)
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import Effect (Effect)
import Effect.Aff (Aff) import Effect.Aff (Aff)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
import Gargantext.AsyncTasks as GAT import Gargantext.AsyncTasks as GAT
...@@ -31,13 +30,13 @@ import Gargantext.Components.Forest.Tree.Node.Tools.SubTree.Types (SubTreeOut(.. ...@@ -31,13 +30,13 @@ import Gargantext.Components.Forest.Tree.Node.Tools.SubTree.Types (SubTreeOut(..
import Gargantext.Config.REST (AffRESTError, logRESTError) import Gargantext.Config.REST (AffRESTError, logRESTError)
import Gargantext.Config.Utils (handleRESTError) import Gargantext.Config.Utils (handleRESTError)
import Gargantext.Ends (Frontends) import Gargantext.Ends (Frontends)
import Gargantext.Hooks.Loader (useLoader, useLoaderEffect) import Gargantext.Hooks.Loader (useLoaderEffect)
import Gargantext.Routes as GR import Gargantext.Routes as GR
import Gargantext.Sessions (Session, get, mkNodeId) import Gargantext.Sessions (Session, get, mkNodeId)
import Gargantext.Sessions.Types (useOpenNodesMemberBox, openNodesInsert, openNodesDelete) import Gargantext.Sessions.Types (useOpenNodesMemberBox, openNodesInsert, openNodesDelete)
import Gargantext.Types (Handed, ID, isPublic, publicize, switchHanded) import Gargantext.Types (Handed, ID, isPublic, publicize)
import Gargantext.Types as GT import Gargantext.Types as GT
import Gargantext.Utils (nbsp, (?)) import Gargantext.Utils ((?))
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Toestand as T2 import Gargantext.Utils.Toestand as T2
import Reactix as R import Reactix as R
...@@ -99,11 +98,13 @@ type ChildLoaderProps = ...@@ -99,11 +98,13 @@ type ChildLoaderProps =
( id :: ID ( id :: ID
, render :: R2.Leaf TreeProps , render :: R2.Leaf TreeProps
, root :: ID , root :: ID
| NodeProps ) | NodeProps
)
type PerformActionProps = type PerformActionProps =
( setPopoverRef :: R.Ref (Maybe (Boolean -> Effect Unit)) ( isBoxVisible :: T.Box Boolean
| PACommon ) | PACommon
)
-- | Loads and renders the tree starting at the given root node id. -- | Loads and renders the tree starting at the given root node id.
treeLoader :: R2.Leaf ( key :: String | LoaderProps ) treeLoader :: R2.Leaf ( key :: String | LoaderProps )
...@@ -163,9 +164,9 @@ treeCpt = here.component "tree" cpt where ...@@ -163,9 +164,9 @@ treeCpt = here.component "tree" cpt where
, session , session
, tree: NTree (LNode { id, name, nodeType }) children } _ = do , tree: NTree (LNode { id, name, nodeType }) children } _ = do
setPopoverRef <- R.useRef Nothing isBoxVisible <- T.useBox false
folderOpen <- useOpenNodesMemberBox nodeId forestOpen folderOpen <- useOpenNodesMemberBox nodeId forestOpen
folderOpen' <- T.useLive T.unequal folderOpen folderOpen' <- T.useLive T.unequal folderOpen
pure $ pure $
...@@ -183,7 +184,7 @@ treeCpt = here.component "tree" cpt where ...@@ -183,7 +184,7 @@ treeCpt = here.component "tree" cpt where
[ [
nodeSpan nodeSpan
{ boxes { boxes
, dispatch: dispatch setPopoverRef , dispatch: dispatch' isBoxVisible
, folderOpen , folderOpen
, frontends , frontends
, id , id
...@@ -193,7 +194,7 @@ treeCpt = here.component "tree" cpt where ...@@ -193,7 +194,7 @@ treeCpt = here.component "tree" cpt where
, reload , reload
, root , root
, session , session
, setPopoverRef , isBoxVisible
} }
<> <>
R2.when (folderOpen') R2.when (folderOpen')
...@@ -213,9 +214,9 @@ treeCpt = here.component "tree" cpt where ...@@ -213,9 +214,9 @@ treeCpt = here.component "tree" cpt where
nodeId = mkNodeId session id nodeId = mkNodeId session id
children' = A.sortWith fTreeID pubChildren children' = A.sortWith fTreeID pubChildren
pubChildren = if isPublic nodeType then map (map pub) children else children pubChildren = if isPublic nodeType then map (map pub) children else children
dispatch setPopoverRef a = performAction a (Record.merge common' spr) where dispatch' isBoxVisible a = performAction a (Record.merge common' extra) where
common' = RecordE.pick p :: Record PACommon common' = RecordE.pick p :: Record PACommon
spr = { setPopoverRef } extra = { isBoxVisible }
pub (LNode n@{ nodeType: t }) = LNode (n { nodeType = publicize t }) pub (LNode n@{ nodeType: t }) = LNode (n { nodeType = publicize t })
...@@ -295,10 +296,10 @@ childLoaderCpt = here.component "childLoader" cpt where ...@@ -295,10 +296,10 @@ childLoaderCpt = here.component "childLoader" cpt where
extra = { root, tree: tree' } extra = { root, tree: tree' }
nodeProps = RecordE.pick p :: Record NodeProps nodeProps = RecordE.pick p :: Record NodeProps
closePopover { setPopoverRef } = closeBox { isBoxVisible } =
liftEffect $ traverse_ (\set -> set false) (R.readRef setPopoverRef) liftEffect $ T.write_ false isBoxVisible
refreshTree p@{ reloadTree } = liftEffect $ T2.reload reloadTree *> closePopover p refreshTree p@{ reloadTree } = liftEffect $ T2.reload reloadTree *> closeBox p
deleteNode' nt p@{ boxes: { forestOpen }, session, tree: (NTree (LNode {id, parent_id}) _) } = do deleteNode' nt p@{ boxes: { forestOpen }, session, tree: (NTree (LNode {id, parent_id}) _) } = do
case nt of case nt of
...@@ -407,6 +408,6 @@ performAction (MoveNode {params}) p = moveNode params ...@@ -407,6 +408,6 @@ performAction (MoveNode {params}) p = moveNode params
performAction (MergeNode {params}) p = mergeNode params p performAction (MergeNode {params}) p = mergeNode params p
performAction (LinkNode { nodeType, params }) p = linkNode nodeType params p performAction (LinkNode { nodeType, params }) p = linkNode nodeType params p
performAction RefreshTree p = refreshTree p performAction RefreshTree p = refreshTree p
performAction ClosePopover p = closePopover p performAction CloseBox p = closeBox p
performAction (DocumentsFromWriteNodes { id }) p = documentsFromWriteNodes id p performAction (DocumentsFromWriteNodes { id }) p = documentsFromWriteNodes id p
performAction NoAction _ = liftEffect $ here.log "[performAction] NoAction" performAction NoAction _ = liftEffect $ here.log "[performAction] NoAction"
...@@ -8,7 +8,6 @@ import Gargantext.Prelude ...@@ -8,7 +8,6 @@ import Gargantext.Prelude
import Data.Array.NonEmpty as NArray import Data.Array.NonEmpty as NArray
import Data.Foldable (intercalate) import Data.Foldable (intercalate)
import Data.Maybe (Maybe(..), maybe) import Data.Maybe (Maybe(..), maybe)
import Data.Nullable (null)
import Data.String.Regex as Regex import Data.String.Regex as Regex
import Data.Symbol (SProxy(..)) import Data.Symbol (SProxy(..))
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
...@@ -31,7 +30,6 @@ import Gargantext.Components.Nodes.Corpus (loadCorpusWithChild) ...@@ -31,7 +30,6 @@ import Gargantext.Components.Nodes.Corpus (loadCorpusWithChild)
import Gargantext.Config.REST (logRESTError) import Gargantext.Config.REST (logRESTError)
import Gargantext.Context.Progress (asyncContext, asyncProgress) import Gargantext.Context.Progress (asyncContext, asyncProgress)
import Gargantext.Ends (Frontends, url) import Gargantext.Ends (Frontends, url)
import Gargantext.Hooks.FirstEffect (useFirstEffect')
import Gargantext.Hooks.Loader (useLoaderEffect) import Gargantext.Hooks.Loader (useLoaderEffect)
import Gargantext.Hooks.Version (Version, useVersion) import Gargantext.Hooks.Version (Version, useVersion)
import Gargantext.Routes as Routes import Gargantext.Routes as Routes
...@@ -39,7 +37,6 @@ import Gargantext.Sessions (Session, sessionId) ...@@ -39,7 +37,6 @@ import Gargantext.Sessions (Session, sessionId)
import Gargantext.Types (ID, Name) import Gargantext.Types (ID, Name)
import Gargantext.Types as GT import Gargantext.Types as GT
import Gargantext.Utils (nbsp, textEllipsisBreak, (?)) import Gargantext.Utils (nbsp, textEllipsisBreak, (?))
import Gargantext.Utils.Popover as Popover
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Toestand as T2 import Gargantext.Utils.Toestand as T2
import React.SyntheticEvent as SE import React.SyntheticEvent as SE
...@@ -67,7 +64,7 @@ type NodeSpanProps = ...@@ -67,7 +64,7 @@ type NodeSpanProps =
, reload :: T2.ReloadS , reload :: T2.ReloadS
, root :: ID , root :: ID
, session :: Session , session :: Session
, setPopoverRef :: R.Ref (Maybe (Boolean -> Effect Unit)) , isBoxVisible :: T.Box Boolean
) )
type IsLeaf = Boolean type IsLeaf = Boolean
...@@ -91,7 +88,7 @@ nodeSpanCpt = here.component "nodeSpan" cpt ...@@ -91,7 +88,7 @@ nodeSpanCpt = here.component "nodeSpan" cpt
, nodeType , nodeType
, reload , reload
, session , session
, setPopoverRef , isBoxVisible
} _ = do } _ = do
-- States -- States
...@@ -101,9 +98,8 @@ nodeSpanCpt = here.component "nodeSpan" cpt ...@@ -101,9 +98,8 @@ nodeSpanCpt = here.component "nodeSpan" cpt
droppedFile' <- T.useLive T.unequal droppedFile droppedFile' <- T.useLive T.unequal droppedFile
isDragOver <- T.useBox false isDragOver <- T.useBox false
isDragOver' <- T.useLive T.unequal isDragOver isDragOver' <- T.useLive T.unequal isDragOver
popoverRef <- R.useRef null
currentTasks <- GAT.focus id tasks currentTasks <- GAT.focus id tasks
currentTasks' <- T.useLive T.unequal currentTasks currentTasks' <- T.useLive T.unequal currentTasks
folderOpen' <- R2.useLive' folderOpen folderOpen' <- R2.useLive' folderOpen
...@@ -196,20 +192,12 @@ nodeSpanCpt = here.component "nodeSpan" cpt ...@@ -196,20 +192,12 @@ nodeSpanCpt = here.component "nodeSpan" cpt
-- Nothing -> pure unit -- Nothing -> pure unit
-- T2.reload reloadRoot -- T2.reload reloadRoot
onPopoverClose ::
Popover.PopoverRef
-> Effect Unit
onPopoverClose ref = Popover.setOpen ref false
-- NOTE Don't toggle tree if it is not selected -- NOTE Don't toggle tree if it is not selected
onNodeLinkClick :: Unit -> Effect Unit onNodeLinkClick :: Unit -> Effect Unit
onNodeLinkClick _ = when (not isSelected) (T.write_ true folderOpen) onNodeLinkClick _ = when (not isSelected) (T.write_ true folderOpen)
-- Hooks -- Hooks
useFirstEffect' $
R.setRef setPopoverRef $ Just $ Popover.setOpen popoverRef
mVersion <- useVersion $ nodeType == GT.NodeUser ? mVersion <- useVersion $ nodeType == GT.NodeUser ?
Just { session } $ Just { session } $
Nothing Nothing
...@@ -313,42 +301,18 @@ nodeSpanCpt = here.component "nodeSpan" cpt ...@@ -313,42 +301,18 @@ nodeSpanCpt = here.component "nodeSpan" cpt
, session , session
} [] } []
, ,
-- @XXX: React Awesome Popover not suited for the feature UX
-- We SHOULD use a more common `Modal` type of thing
-- As of now, we have issues on z-index management and erratic
-- popup close action
R2.when (showBox) $ R2.when (showBox) $
Popover.popover B.iconButton
{ arrow: false { name: "cog"
, open: false , className: "mainleaf__settings-icon"
, onClose: \_ -> pure unit , callback: \_ -> T.write_ true isBoxVisible
, onOpen: \_ -> pure unit , title:
, ref: popoverRef "Each node of the Tree can perform some actions.\n"
<> "Click here to execute one of them."
, variant: Secondary
, elevation: Level1
} }
[
B.iconButton
{ name: "cog"
, className: "mainleaf__settings-icon"
-- (cf. Popover callbacks)
, callback: const R.nothing
, title:
"Each node of the Tree can perform some actions.\n"
<> "Click here to execute one of them."
, variant: Secondary
, elevation: Level1
}
,
nodePopupView
{ boxes
, dispatch
, id
, name
, nodeType
, onPopoverClose: const $ onPopoverClose popoverRef
, session
}
]
, ,
R.fragment $ flip map currentTasks' \task -> R.fragment $ flip map currentTasks' \task ->
...@@ -363,6 +327,27 @@ nodeSpanCpt = here.component "nodeSpan" cpt ...@@ -363,6 +327,27 @@ nodeSpanCpt = here.component "nodeSpan" cpt
taskProgress taskProgress
{} {}
] ]
,
-- // Modals //
B.baseModal
{ isVisibleBox: isBoxVisible
, noBody: true
, noHeader: true
, modalClassName: "forest-tree-node-modal"
}
[
nodePopupView
{ boxes
, dispatch
, id
, name
, nodeType
, closeCallback: \_ -> T.write_ false isBoxVisible
, session
}
]
] ]
......
...@@ -46,7 +46,7 @@ icon (UploadFile _ _ _ _ _ _) = glyphiconNodeAction Upload ...@@ -46,7 +46,7 @@ icon (UploadFile _ _ _ _ _ _) = glyphiconNodeAction Upload
icon (UploadArbitraryFile _ _ _ _ ) = glyphiconNodeAction Upload icon (UploadArbitraryFile _ _ _ _ ) = glyphiconNodeAction Upload
icon UploadFrameCalc = glyphiconNodeAction Upload icon UploadFrameCalc = glyphiconNodeAction Upload
icon RefreshTree = glyphiconNodeAction Refresh icon RefreshTree = glyphiconNodeAction Refresh
icon ClosePopover = glyphiconNodeAction CloseNodePopover icon CloseBox = glyphiconNodeAction CloseNodePopover
icon DownloadNode = glyphiconNodeAction Download icon DownloadNode = glyphiconNodeAction Download
icon (MoveNode _ ) = glyphiconNodeAction (Move { subTreeParams : SubTreeParams {showtypes:[], valitypes:[] }}) icon (MoveNode _ ) = glyphiconNodeAction (Move { subTreeParams : SubTreeParams {showtypes:[], valitypes:[] }})
icon (MergeNode _ ) = glyphiconNodeAction (Merge { subTreeParams : SubTreeParams {showtypes:[], valitypes:[] }}) icon (MergeNode _ ) = glyphiconNodeAction (Merge { subTreeParams : SubTreeParams {showtypes:[], valitypes:[] }})
...@@ -70,7 +70,7 @@ text (UploadFile _ _ _ _ _ _) = "Upload File !" ...@@ -70,7 +70,7 @@ text (UploadFile _ _ _ _ _ _) = "Upload File !"
text (UploadArbitraryFile _ _ _ _) = "Upload arbitrary file !" text (UploadArbitraryFile _ _ _ _) = "Upload arbitrary file !"
text UploadFrameCalc = "Upload frame calc" text UploadFrameCalc = "Upload frame calc"
text RefreshTree = "Refresh Tree !" text RefreshTree = "Refresh Tree !"
text ClosePopover = "Close Popover !" text CloseBox = "Close Box !"
text DownloadNode = "Download !" text DownloadNode = "Download !"
text (MoveNode _ ) = "Move !" text (MoveNode _ ) = "Move !"
text (MergeNode _ ) = "Merge !" text (MergeNode _ ) = "Merge !"
...@@ -78,4 +78,3 @@ text (LinkNode _ ) = "Link !" ...@@ -78,4 +78,3 @@ text (LinkNode _ ) = "Link !"
text (DocumentsFromWriteNodes _ ) = "Documents from Write Nodes !" text (DocumentsFromWriteNodes _ ) = "Documents from Write Nodes !"
text NoAction = "No Action" text NoAction = "No Action"
----------------------------------------------------------------------- -----------------------------------------------------------------------
...@@ -37,7 +37,7 @@ actionSearchCpt = here.component "actionSearch" cpt ...@@ -37,7 +37,7 @@ actionSearchCpt = here.component "actionSearch" cpt
cpt { boxes: { errors }, dispatch, id, session } _ = do cpt { boxes: { errors }, dispatch, id, session } _ = do
search <- T.useBox $ defaultSearch { node_id = id } search <- T.useBox $ defaultSearch { node_id = id }
pure $ R.fragment pure $ R.fragment
[ H.p { className: "action-search" } [ H.p { className: "action-search m-1" }
[ H.text $ "Search and create a private " [ H.text $ "Search and create a private "
<> "corpus with the search query as corpus name." ] <> "corpus with the search query as corpus name." ]
, searchBar { errors , searchBar { errors
...@@ -54,7 +54,7 @@ actionSearchCpt = here.component "actionSearch" cpt ...@@ -54,7 +54,7 @@ actionSearchCpt = here.component "actionSearch" cpt
searchOn dispatch' task = do searchOn dispatch' task = do
_ <- launchAff $ dispatch' (DoSearch task) _ <- launchAff $ dispatch' (DoSearch task)
-- close popup -- close popup
_ <- launchAff $ dispatch' ClosePopover _ <- launchAff $ dispatch' CloseBox
-- TODO -- TODO
--snd p $ const Nothing --snd p $ const Nothing
pure unit pure unit
...@@ -33,7 +33,7 @@ searchBarCpt = here.component "searchBar" cpt ...@@ -33,7 +33,7 @@ searchBarCpt = here.component "searchBar" cpt
where where
cpt { errors, langs, onSearch, search, session } _ = do cpt { errors, langs, onSearch, search, session } _ = do
--onSearchChange session s --onSearchChange session s
pure $ H.div { className: "search-bar" } pure $ H.div { className: "search-bar m-1" }
[ searchField { databases: allDatabases [ searchField { databases: allDatabases
, errors , errors
, langs , langs
......
...@@ -21,7 +21,7 @@ data Action = AddNode String GT.NodeType ...@@ -21,7 +21,7 @@ data Action = AddNode String GT.NodeType
| UploadFrameCalc | UploadFrameCalc
| DownloadNode | DownloadNode
| RefreshTree | RefreshTree
| ClosePopover | CloseBox
| ShareTeam String | ShareTeam String
| AddContact AddContactParams | AddContact AddContactParams
...@@ -48,7 +48,7 @@ instance Eq Action where ...@@ -48,7 +48,7 @@ instance Eq Action where
eq UploadFrameCalc UploadFrameCalc = true eq UploadFrameCalc UploadFrameCalc = true
eq DownloadNode DownloadNode = true eq DownloadNode DownloadNode = true
eq RefreshTree RefreshTree = true eq RefreshTree RefreshTree = true
eq ClosePopover ClosePopover = true eq CloseBox CloseBox = true
eq (ShareTeam s1) (ShareTeam s2) = eq s1 s2 eq (ShareTeam s1) (ShareTeam s2) = eq s1 s2
eq (AddContact ac1) (AddContact ac2) = eq ac1 ac2 eq (AddContact ac1) (AddContact ac2) = eq ac1 ac2
eq (SharePublic p1) (SharePublic p2) = eq p1 p2 eq (SharePublic p1) (SharePublic p2) = eq p1 p2
...@@ -72,7 +72,7 @@ instance Show Action where ...@@ -72,7 +72,7 @@ instance Show Action where
show (UploadArbitraryFile _ _ _ _) = "UploadArbitraryFile" show (UploadArbitraryFile _ _ _ _) = "UploadArbitraryFile"
show UploadFrameCalc = "UploadFrameCalc" show UploadFrameCalc = "UploadFrameCalc"
show RefreshTree = "RefreshTree" show RefreshTree = "RefreshTree"
show ClosePopover = "ClosePopover" show CloseBox = "CloseBox"
show DownloadNode = "Download" show DownloadNode = "Download"
show (MoveNode _ ) = "MoveNode" show (MoveNode _ ) = "MoveNode"
show (MergeNode _ ) = "MergeNode" show (MergeNode _ ) = "MergeNode"
......
...@@ -2,7 +2,7 @@ module Gargantext.Components.Forest.Tree.Node.Action.Update where ...@@ -2,7 +2,7 @@ module Gargantext.Components.Forest.Tree.Node.Action.Update where
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Components.Forest.Tree.Node.Action.Update.Types (Charts(..), Granularity(..), GraphMetric(..), Method(..), PartitionMethod(..), UpdateNodeParams(..)) import Gargantext.Components.Forest.Tree.Node.Action.Update.Types (Charts(..), Granularity(..), GraphMetric(..), Method(..), PartitionMethod(..), UpdateNodeParams(..), Strength(..))
import DOM.Simple.Console (log3) import DOM.Simple.Console (log3)
import Data.Either (Either(..)) import Data.Either (Either(..))
...@@ -78,18 +78,28 @@ updateGraphCpt = here.component "updateGraph" cpt where ...@@ -78,18 +78,28 @@ updateGraphCpt = here.component "updateGraph" cpt where
methodGraphMetric <- T.useBox Order1 methodGraphMetric <- T.useBox Order1
methodGraphMetric' <- T.useLive T.unequal methodGraphMetric methodGraphMetric' <- T.useLive T.unequal methodGraphMetric
methodGraphEdgesStrength <- T.useBox Strong
methodGraphEdgesStrength' <- T.useLive T.unequal methodGraphEdgesStrength
methodGraphClustering <- T.useBox Spinglass methodGraphClustering <- T.useBox Spinglass
methodGraphClustering' <- T.useLive T.unequal methodGraphClustering methodGraphClustering' <- T.useLive T.unequal methodGraphClustering
let let
callback :: Action -> Aff Unit callback :: Action -> Aff Unit
callback = dispatch >=> \_ -> dispatch ClosePopover callback = dispatch >=> \_ -> dispatch CloseBox
pure $ panel [ -- H.text "Update with" pure $ panel [ H.text "Show subjects with Order1 or concepts with Order2 ?"
formChoiceSafe { items: [Order1, Order2] , formChoiceSafe { items: [Order1, Order2]
, default: methodGraphMetric' , default: methodGraphMetric'
, callback: \val -> T.write_ val methodGraphMetric , callback: \val -> T.write_ val methodGraphMetric
, print: show } [] , print: show } []
, H.text "Show Strong (expected) links or weak (maybe unexpected) links?"
, formChoiceSafe { items: [Strong, Weak]
, default: methodGraphEdgesStrength'
, callback: \val -> T.write_ val methodGraphEdgesStrength
, print: show } []
, formChoiceSafe { items: [Spinglass, Infomap, Confluence] , formChoiceSafe { items: [Spinglass, Infomap, Confluence]
, default: methodGraphClustering' , default: methodGraphClustering'
, callback: \val -> T.write_ val methodGraphClustering , callback: \val -> T.write_ val methodGraphClustering
...@@ -98,6 +108,7 @@ updateGraphCpt = here.component "updateGraph" cpt where ...@@ -98,6 +108,7 @@ updateGraphCpt = here.component "updateGraph" cpt where
] ]
(submitButton (UpdateNode $ UpdateNodeParamsGraph { methodGraphMetric: methodGraphMetric' (submitButton (UpdateNode $ UpdateNodeParamsGraph { methodGraphMetric: methodGraphMetric'
, methodGraphClustering: methodGraphClustering' , methodGraphClustering: methodGraphClustering'
, methodGraphEdgesStrength : methodGraphEdgesStrength'
} }
) callback ) callback
) )
...@@ -142,7 +153,7 @@ updatePhyloCpt = here.component "updatePhylo" cpt where ...@@ -142,7 +153,7 @@ updatePhyloCpt = here.component "updatePhylo" cpt where
opts <- pure $ options r' opts <- pure $ options r'
launchAff_ do launchAff_ do
dispatch opts dispatch opts
dispatch ClosePopover dispatch CloseBox
where where
options :: Phylo.UpdateData -> Action options :: Phylo.UpdateData -> Action
......
...@@ -14,6 +14,7 @@ import Simple.JSON.Generics as JSONG ...@@ -14,6 +14,7 @@ import Simple.JSON.Generics as JSONG
data UpdateNodeParams data UpdateNodeParams
= UpdateNodeParamsList { methodList :: Method } = UpdateNodeParamsList { methodList :: Method }
| UpdateNodeParamsGraph { methodGraphMetric :: GraphMetric | UpdateNodeParamsGraph { methodGraphMetric :: GraphMetric
, methodGraphEdgesStrength :: Strength
, methodGraphClustering :: PartitionMethod , methodGraphClustering :: PartitionMethod
} }
| UpdateNodeParamsTexts { methodTexts :: Granularity } | UpdateNodeParamsTexts { methodTexts :: Granularity }
...@@ -28,9 +29,9 @@ instance JSON.WriteForeign UpdateNodeParams where ...@@ -28,9 +29,9 @@ instance JSON.WriteForeign UpdateNodeParams where
writeImpl (UpdateNodeParamsList { methodList }) = writeImpl (UpdateNodeParamsList { methodList }) =
JSON.writeImpl { type: "UpdateNodeParamsList" JSON.writeImpl { type: "UpdateNodeParamsList"
, methodList } , methodList }
writeImpl (UpdateNodeParamsGraph { methodGraphMetric, methodGraphClustering }) = writeImpl (UpdateNodeParamsGraph { methodGraphMetric, methodGraphClustering, methodGraphEdgesStrength}) =
JSON.writeImpl { type: "UpdateNodeParamsGraph" JSON.writeImpl { type: "UpdateNodeParamsGraph"
, methodGraphMetric, methodGraphClustering } , methodGraphMetric, methodGraphClustering, methodGraphEdgesStrength}
writeImpl (UpdateNodeParamsTexts { methodTexts }) = writeImpl (UpdateNodeParamsTexts { methodTexts }) =
JSON.writeImpl { type: "UpdateNodeParamsTexts" JSON.writeImpl { type: "UpdateNodeParamsTexts"
, methodTexts } , methodTexts }
...@@ -71,6 +72,19 @@ instance Read GraphMetric where ...@@ -71,6 +72,19 @@ instance Read GraphMetric where
instance JSON.ReadForeign GraphMetric where readImpl = JSONG.enumSumRep instance JSON.ReadForeign GraphMetric where readImpl = JSONG.enumSumRep
instance JSON.WriteForeign GraphMetric where writeImpl = JSON.writeImpl <<< show instance JSON.WriteForeign GraphMetric where writeImpl = JSON.writeImpl <<< show
data Strength = Strong | Weak
derive instance Generic Strength _
derive instance Eq Strength
instance Show Strength where show = genericShow
instance Read Strength where
read "Strong" = Just Strong
read "Weak" = Just Weak
read _ = Nothing
instance JSON.ReadForeign Strength where readImpl = JSONG.enumSumRep
instance JSON.WriteForeign Strength where writeImpl = JSON.writeImpl <<< show
data PartitionMethod = Spinglass | Infomap | Confluence data PartitionMethod = Spinglass | Infomap | Confluence
derive instance Generic PartitionMethod _ derive instance Generic PartitionMethod _
derive instance Eq PartitionMethod derive instance Eq PartitionMethod
......
...@@ -265,7 +265,7 @@ uploadButtonCpt = here.component "uploadButton" cpt ...@@ -265,7 +265,7 @@ uploadButtonCpt = here.component "uploadButton" cpt
T.write_ Plain fileFormat T.write_ Plain fileFormat
T.write_ EN lang T.write_ EN lang
T.write_ false onPendingBox T.write_ false onPendingBox
dispatch ClosePopover dispatch CloseBox
uploadListView :: R2.Leaf Props uploadListView :: R2.Leaf Props
uploadListView = R2.leafComponent uploadListViewCpt uploadListView = R2.leafComponent uploadListViewCpt
......
...@@ -5,11 +5,8 @@ import Gargantext.Prelude ...@@ -5,11 +5,8 @@ import Gargantext.Prelude
import Data.Array as A import Data.Array as A
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Effect.Aff (Aff) import Effect.Aff (Aff)
import Reactix as R
import Reactix.DOM.HTML as H
import Toestand as T
import Gargantext.Components.App.Store (Boxes) import Gargantext.Components.App.Store (Boxes)
import Gargantext.Components.Bootstrap as B
import Gargantext.Components.Forest.Tree.Node.Action.Add (addNodeView) import Gargantext.Components.Forest.Tree.Node.Action.Add (addNodeView)
import Gargantext.Components.Forest.Tree.Node.Action.Contact as Contact import Gargantext.Components.Forest.Tree.Node.Action.Contact as Contact
import Gargantext.Components.Forest.Tree.Node.Action.Delete (actionDelete) import Gargantext.Components.Forest.Tree.Node.Action.Delete (actionDelete)
...@@ -34,13 +31,17 @@ import Gargantext.Types (ID, Name, prettyNodeType) ...@@ -34,13 +31,17 @@ import Gargantext.Types (ID, Name, prettyNodeType)
import Gargantext.Types as GT import Gargantext.Types as GT
import Gargantext.Utils.Glyphicon (glyphicon, glyphiconActive) import Gargantext.Utils.Glyphicon (glyphicon, glyphiconActive)
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import Reactix as R
import Reactix.DOM.HTML as H
import Toestand as T
here :: R2.Here here :: R2.Here
here = R2.here "Gargantext.Components.Forest.Tree.Node.Box" here = R2.here "Gargantext.Components.Forest.Tree.Node.Box"
type CommonProps = type CommonProps =
( dispatch :: Action -> Aff Unit ( dispatch :: Action -> Aff Unit
, session :: Session ) , session :: Session
)
nodePopupView :: R2.Leaf NodePopupProps nodePopupView :: R2.Leaf NodePopupProps
nodePopupView = R2.leafComponent nodePopupCpt nodePopupView = R2.leafComponent nodePopupCpt
...@@ -53,24 +54,26 @@ nodePopupCpt = here.component "nodePopupView" cpt where ...@@ -53,24 +54,26 @@ nodePopupCpt = here.component "nodePopupView" cpt where
action <- T.useFocused (_.action) (\a b -> b { action = a }) nodePopup action <- T.useFocused (_.action) (\a b -> b { action = a }) nodePopup
nodePopup' <- T.useLive T.unequal nodePopup nodePopup' <- T.useLive T.unequal nodePopup
pure $ H.div tooltipProps pure $
[ H.div { className: "popup-container" }
[ H.div { className: "card" } H.div
[ panelHeading renameIsOpen open p { className: "node-popup-tooltip"
, H.div { className: "popup-container-body" } , title: "Node settings"
[ }
panelBody action p [
, H.div
mPanelAction nodePopup' p { className: "popup-container card" }
] [
] panelHeading renameIsOpen open p
,
panelBody action p
,
mPanelAction nodePopup' p
] ]
] ]
closePopover p = p.onPopoverClose <<< R.unsafeEventTarget
tooltipProps = { id: "node-popup-tooltip", title: "Node settings"
, data: { toggle: "tooltip", placement: "right" } }
panelHeading renameIsOpen open p@{ dispatch, id, name, nodeType } = panelHeading renameIsOpen open p@{ dispatch, id, name, nodeType } =
H.div { className: "card-header" } H.div { className: "popup-container__header card-header" }
[ R2.row [ R2.row
[ H.div { className: "col-4" } [ H.div { className: "col-4" }
[ H.span { className: GT.fldr nodeType true} [] -- TODO fix names [ H.span { className: GT.fldr nodeType true} [] -- TODO fix names
...@@ -83,7 +86,7 @@ nodePopupCpt = here.component "nodePopupView" cpt where ...@@ -83,7 +86,7 @@ nodePopupCpt = here.component "nodePopupView" cpt where
] ]
, H.div { className: "col-1" } [ editIcon renameIsOpen open ] , H.div { className: "col-1" } [ editIcon renameIsOpen open ]
, H.div { className: "col-1" } , H.div { className: "col-1" }
[ H.a { type: "button", on: { click: closePopover p }, title: "Close" [ H.a { type: "button", on: { click: \_ -> p.closeCallback unit }, title: "Close"
, className: glyphicon "window-close" } [] ]]] , className: glyphicon "window-close" } [] ]]]
editIcon _ true = H.div {} [] editIcon _ true = H.div {} []
editIcon isOpen false = editIcon isOpen false =
...@@ -92,8 +95,8 @@ nodePopupCpt = here.component "nodePopupView" cpt where ...@@ -92,8 +95,8 @@ nodePopupCpt = here.component "nodePopupView" cpt where
panelBody :: T.Box (Maybe NodeAction) -> Record NodePopupProps -> R.Element panelBody :: T.Box (Maybe NodeAction) -> Record NodePopupProps -> R.Element
panelBody nodePopupState { nodeType } = panelBody nodePopupState { nodeType } =
let (SettingsBox { doc, buttons }) = settingsBox nodeType in let (SettingsBox { doc, buttons }) = settingsBox nodeType in
H.div {className: "card-body flex-space-between"} H.div {className: "popup-container__body card-body flex-space-between"}
$ [ H.p { className: "spacer" } [] $ [ B.wad_ [ "m-1" ]
, H.div { className: "flex-center" } , H.div { className: "flex-center" }
[ buttonClick { action: doc, state: nodePopupState, nodeType } ] [ buttonClick { action: doc, state: nodePopupState, nodeType } ]
, H.div {className: "flex-center"} , H.div {className: "flex-center"}
...@@ -114,15 +117,15 @@ nodePopupCpt = here.component "nodePopupView" cpt where ...@@ -114,15 +117,15 @@ nodePopupCpt = here.component "nodePopupView" cpt where
, session , session
} }
mPanelAction { action: Nothing } _ = mPanelAction { action: Nothing } _ =
H.div { className: "card-footer" } H.div { className: "popup-container__footer card-footer" }
[ H.div {className:"center fa-hand-pointer-o"} [ H.div {className:"center fa-hand-pointer-o"}
[ H.h5 {} [ H.text " Select available actions of this node" ] [ H.h5 {} [ H.text " Select available actions of this node" ]
, H.ul { className: "panel-actions" } , H.ul { className: "panel-actions" }
[ H.div { className: "fa-thumbs-o-up ok-to-use" } [ H.div { className: "fa-thumbs-o-up panel-actions__ok-to-use" }
[ H.text " Black: usable" ] [ H.text " Black: usable" ]
, H.div { className: "fa-exclamation-triangle almost-useable" } , H.div { className: "fa-exclamation-triangle panel-actions__almost-useable" }
[ H.text " Orange: almost useable" ] [ H.text " Orange: almost useable" ]
, H.div { className: "fa-rocket development-in-progress" } , H.div { className: "fa-rocket panel-actions__development-in-progress" }
[ H.text " Red: development in progress" ]]]] [ H.text " Red: development in progress" ]]]]
type ActionState = type ActionState =
......
module Gargantext.Components.Forest.Tree.Node.Box.Types where module Gargantext.Components.Forest.Tree.Node.Box.Types where
import DOM.Simple as DOM
import Data.Maybe (Maybe) import Data.Maybe (Maybe)
import Effect (Effect) import Effect (Effect)
import Effect.Aff (Aff) import Effect.Aff (Aff)
...@@ -18,11 +17,11 @@ type CommonProps = ...@@ -18,11 +17,11 @@ type CommonProps =
) )
type NodePopupProps = type NodePopupProps =
( boxes :: Boxes ( boxes :: Boxes
, id :: ID , id :: ID
, name :: Name , name :: Name
, nodeType :: GT.NodeType , nodeType :: GT.NodeType
, onPopoverClose :: DOM.Element -> Effect Unit , closeCallback :: Unit -> Effect Unit
| CommonProps | CommonProps
) )
......
module Gargantext.Components.ForgotPassword where
import Gargantext.Prelude
import Data.Maybe (Maybe(..))
import Gargantext.Config.REST (AffRESTError, logRESTError, get)
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Utils.Reactix as R2
import Reactix as R
import Reactix.DOM.HTML as H
here :: R2.Here
here = R2.here "Gargantext.Components.ForgotPassword"
type ForgotPasswordProps = ( server :: String, uuid :: String )
forgotPasswordLayout :: R2.Component ForgotPasswordProps
forgotPasswordLayout = R.createElement forgotPasswordLayoutCpt
forgotPasswordLayoutCpt :: R.Component ForgotPasswordProps
forgotPasswordLayoutCpt = here.component "forgotPasswordLayout" cpt where
cpt { server, uuid } _ = do
useLoader { errorHandler
, loader: loadPassword
, path: { server, uuid }
, render: \{ password } ->
H.p {} [ H.text ("Your new password is: " <> password) ] }
where
errorHandler = logRESTError here "[forgotPasswordLayout]"
------------------------------------
type PasswordData = ( password :: String )
loadPassword :: Record ForgotPasswordProps -> AffRESTError (Record PasswordData)
loadPassword { server, uuid } = get Nothing (server <> "/api/v1.0/forgot-password?uuid=" <> uuid )
...@@ -4,13 +4,19 @@ module Gargantext.Components.GraphExplorer.Frame.DocFocus ...@@ -4,13 +4,19 @@ module Gargantext.Components.GraphExplorer.Frame.DocFocus
import Gargantext.Prelude import Gargantext.Prelude
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..), isJust)
import Data.Tuple.Nested ((/\))
import Effect (Effect) import Effect (Effect)
import Gargantext.Components.Bootstrap as B import Gargantext.Components.Bootstrap as B
import Gargantext.Components.Bootstrap.Types (Elevation(..)) import Gargantext.Components.Bootstrap.Types (Elevation(..))
import Gargantext.Components.Document.API (loadData)
import Gargantext.Components.Document.Layout (layout)
import Gargantext.Components.Document.Types (LoadedData, DocPath)
import Gargantext.Components.GraphExplorer.Types (GraphSideDoc(..)) import Gargantext.Components.GraphExplorer.Types (GraphSideDoc(..))
import Gargantext.Components.Nodes.Corpus.Document (node) import Gargantext.Config.REST (logRESTError)
import Gargantext.Sessions (Session, sessionId) import Gargantext.Hooks.Loader (useLoaderEffect)
import Gargantext.Sessions (Session)
import Gargantext.Types (CTabNgramType(..), TabSubType(..), TabType(..))
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import Reactix as R import Reactix as R
import Reactix.DOM.HTML as H import Reactix.DOM.HTML as H
...@@ -25,41 +31,74 @@ type Props = ...@@ -25,41 +31,74 @@ type Props =
, closeCallback :: Unit -> Effect Unit , closeCallback :: Unit -> Effect Unit
) )
docFocus :: R2.Leaf Props docFocus :: R2.Leaf ( key :: String | Props )
docFocus = R2.leaf docFocusCpt docFocus = R2.leaf docFocusCpt
docFocusCpt :: R.Component Props docFocusCpt :: R.Component ( key :: String | Props )
docFocusCpt = here.component "main" cpt where docFocusCpt = here.component "main" cpt where
cpt { graphSideDoc: GraphSideDoc { docId, listId, corpusId } cpt { graphSideDoc: GraphSideDoc { docId, listId, corpusId }
, session , session
, closeCallback , closeCallback
} _ = do } _ = do
-- | States
-- |
state' /\ state <- R2.useBox' (Nothing :: Maybe LoadedData)
-- | Computed
-- |
let
tabType :: TabType
tabType = TabDocument (TabNgramType CTabTerms)
path :: DocPath
path =
{ listIds: [listId]
, mCorpusId: Just corpusId
, nodeId: docId
, session
, tabType
}
-- | Hooks
-- |
useLoaderEffect
{ errorHandler: logRESTError here "[docFocus]"
, loader: loadData
, path
, state
}
-- | Render -- | Render
-- | -- |
pure $ pure $
H.div H.div
{ className: "graph-doc-focus" } { className: "graph-doc-focus" }
[ [
H.div B.cloak
{ className: "graph-doc-focus__header" } { isDisplayed: isJust state'
[ , idlingPhaseDuration: Just 150
B.iconButton , cloakSlot:
{ name: "times" B.preloader
, elevation: Level2 {}
, callback: closeCallback
} , defaultSlot:
] R2.fromMaybe state' \loaded ->
, layout
H.div { loaded
{ className: "graph-doc-focus__body" } , path
[ , sideControlsSlot: Just $
-- print the document node H.div
node { className: "graph-doc-focus__header" }
{ listId [
, mCorpusId: Just corpusId B.iconButton
, nodeId: docId { name: "times"
, key: show (sessionId session) <> "-" <> show docId , elevation: Level2
} , callback: closeCallback
] }
]
}
}
] ]
...@@ -31,7 +31,7 @@ import Gargantext.Hooks.Sigmax as Sigmax ...@@ -31,7 +31,7 @@ import Gargantext.Hooks.Sigmax as Sigmax
import Gargantext.Hooks.Sigmax.Types as SigmaxT import Gargantext.Hooks.Sigmax.Types as SigmaxT
import Gargantext.Types as GT import Gargantext.Types as GT
import Gargantext.Types as Types import Gargantext.Types as Types
import Gargantext.Utils ((?)) import Gargantext.Utils (getter, (?))
import Gargantext.Utils.Range as Range import Gargantext.Utils.Range as Range
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import Partial.Unsafe (unsafePartial) import Partial.Unsafe (unsafePartial)
...@@ -145,6 +145,7 @@ layoutCpt = R.memo' $ here.component "explorerWriteGraph" cpt where ...@@ -145,6 +145,7 @@ layoutCpt = R.memo' $ here.component "explorerWriteGraph" cpt where
{ session { session
, graphSideDoc , graphSideDoc
, closeCallback: closeDoc , closeCallback: closeDoc
, key: show $ getter _.docId graphSideDoc
} }
] ]
] ]
......
...@@ -384,7 +384,6 @@ onExpandSelectionChange { new } = do ...@@ -384,7 +384,6 @@ onExpandSelectionChange { new } = do
neighborhood :: R2.Leaf () neighborhood :: R2.Leaf ()
neighborhood = R2.leaf neighborhoodCpt neighborhood = R2.leaf neighborhoodCpt
neighborhoodCpt :: R.Memo () neighborhoodCpt :: R.Memo ()
neighborhoodCpt = R.memo' $ here.component "neighborhood" cpt where neighborhoodCpt = R.memo' $ here.component "neighborhood" cpt where
cpt _ _ = do cpt _ _ = do
...@@ -495,8 +494,9 @@ neighborhoodCpt = R.memo' $ here.component "neighborhood" cpt where ...@@ -495,8 +494,9 @@ neighborhoodCpt = R.memo' $ here.component "neighborhood" cpt where
R2.when R2.when
( (
withTruncateResults == false (withTruncateResults == false
|| index < maxTruncateResult || index < maxTruncateResult)
&& (not $ Set.member node.id selectedNodeIds')
) $ ) $
H.li H.li
{ className: "graph-neighborhood__badge" } { className: "graph-neighborhood__badge" }
......
...@@ -114,6 +114,7 @@ newtype GraphSideDoc = GraphSideDoc ...@@ -114,6 +114,7 @@ newtype GraphSideDoc = GraphSideDoc
, corpusId :: CorpusId , corpusId :: CorpusId
, listId :: ListId , listId :: ListId
} }
derive instance Newtype GraphSideDoc _
derive instance Generic GraphSideDoc _ derive instance Generic GraphSideDoc _
instance Eq GraphSideDoc where eq = genericEq instance Eq GraphSideDoc where eq = genericEq
......
...@@ -24,7 +24,8 @@ type UserInfo ...@@ -24,7 +24,8 @@ type UserInfo
, ui_cwCountry :: Maybe String , ui_cwCountry :: Maybe String
, ui_cwRole :: Maybe String , ui_cwRole :: Maybe String
, ui_cwTouchPhone :: Maybe String , ui_cwTouchPhone :: Maybe String
, ui_cwTouchMail :: Maybe String } , ui_cwTouchMail :: Maybe String
, ui_cwDescription :: Maybe String }
type UserInfoM type UserInfoM
= { token :: NotNull String = { token :: NotNull String
, ui_id :: NotNull Int , ui_id :: NotNull Int
...@@ -41,7 +42,8 @@ type UserInfoM ...@@ -41,7 +42,8 @@ type UserInfoM
, ui_cwCountry :: String , ui_cwCountry :: String
, ui_cwRole :: String , ui_cwRole :: String
, ui_cwTouchPhone :: String , ui_cwTouchPhone :: String
, ui_cwTouchMail :: String } , ui_cwTouchMail :: String
, ui_cwDescription :: String }
userInfoQuery = { user_infos: { user_id: Var :: _ "id" Int } =>> userInfoQuery = { user_infos: { user_id: Var :: _ "id" Int } =>>
{ ui_id: unit { ui_id: unit
...@@ -58,7 +60,8 @@ userInfoQuery = { user_infos: { user_id: Var :: _ "id" Int } =>> ...@@ -58,7 +60,8 @@ userInfoQuery = { user_infos: { user_id: Var :: _ "id" Int } =>>
, ui_cwOffice: unit , ui_cwOffice: unit
, ui_cwRole: unit , ui_cwRole: unit
, ui_cwTouchMail: unit , ui_cwTouchMail: unit
, ui_cwTouchPhone: unit } , ui_cwTouchPhone: unit
, ui_cwDescription: unit }
} }
_ui_cwFirstName :: Lens' UserInfo String _ui_cwFirstName :: Lens' UserInfo String
...@@ -122,6 +125,12 @@ _ui_cwTouchPhone = lens getter setter ...@@ -122,6 +125,12 @@ _ui_cwTouchPhone = lens getter setter
getter ({ ui_cwTouchPhone: val }) = fromMaybe "" val getter ({ ui_cwTouchPhone: val }) = fromMaybe "" val
setter ui val = ui { ui_cwTouchPhone = Just val } setter ui val = ui { ui_cwTouchPhone = Just val }
_ui_cwDescription :: Lens' UserInfo String
_ui_cwDescription = lens getter setter
where
getter ({ui_cwDescription: val}) = fromMaybe "" val
setter ui val = ui { ui_cwDescription = Just val }
type User type User
= { u_id :: Int = { u_id :: Int
, u_hyperdata :: , u_hyperdata ::
......
...@@ -11,8 +11,9 @@ import Data.String as DST ...@@ -11,8 +11,9 @@ import Data.String as DST
import Effect.Aff (launchAff_) 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.Login.Form (form) import Gargantext.Components.Bootstrap.Types (ModalSizing(..))
import Gargantext.Components.Login.ForgotPassword (forgotPassword) import Gargantext.Components.Login.ForgotPassword (forgotPassword)
import Gargantext.Components.Login.Form (form)
import Gargantext.Components.Login.Types (FormType(..)) import Gargantext.Components.Login.Types (FormType(..))
import Gargantext.Components.NgramsTable.Loader as NTL import Gargantext.Components.NgramsTable.Loader as NTL
import Gargantext.Ends (Backend(..)) import Gargantext.Ends (Backend(..))
...@@ -48,12 +49,14 @@ loginCpt = here.component "login" cpt where ...@@ -48,12 +49,14 @@ loginCpt = here.component "login" cpt where
mBackend <- R2.useLive' props.backend mBackend <- R2.useLive' props.backend
formType <- T.useBox Login formType <- T.useBox Login
formType' <- T.useLive T.unequal formType formType' <- T.useLive T.unequal formType
-- Render -- Render
pure $ pure $
B.baseModal B.baseModal
{ isVisibleBox: visible { isVisibleBox: visible
, title: "GarganText ecosystem explorer" , title: Just "GarganText ecosystem explorer"
, size: ExtraLargeModalSize
} }
[ [
case mBackend of case mBackend of
......
module Gargantext.Components.Login.ForgotPassword where module Gargantext.Components.Login.ForgotPassword where
import Gargantext.Prelude
import DOM.Simple.Event as DE import DOM.Simple.Event as DE
import Data.Either (Either(..))
import Effect (Effect) import Effect (Effect)
import Effect.Aff (launchAff_) import Effect.Aff (launchAff_)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
import Formula as F
import Gargantext.Components.Forms (formGroup) import Gargantext.Components.Forms (formGroup)
import Gargantext.Ends (Backend) import Gargantext.Ends (Backend)
import Gargantext.Prelude
import Gargantext.Sessions (Sessions, postForgotPasswordRequest) import Gargantext.Sessions (Sessions, postForgotPasswordRequest)
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import Formula as F
import Reactix as R import Reactix as R
import Reactix.DOM.HTML as H import Reactix.DOM.HTML as H
import Reactix.SyntheticEvent as E import Reactix.SyntheticEvent as E
...@@ -30,13 +32,15 @@ forgotPasswordCpt :: R.Component Props ...@@ -30,13 +32,15 @@ forgotPasswordCpt :: R.Component Props
forgotPasswordCpt = here.component "forgotPassword" cpt where forgotPasswordCpt = here.component "forgotPassword" cpt where
cpt { backend, sessions } _ = do cpt { backend, sessions } _ = do
email <- T.useBox "" email <- T.useBox ""
message <- T.useBox ""
pure $ H.div { className: "row" } pure $ H.div { className: "row" }
[ H.form { className: "text-center col-md-12" } [ H.form { className: "text-center col-md-12" }
[ H.h4 {} [ H.text "Forgot password" ] [ H.h4 {} [ H.text "Forgot password" ]
, messageDisplay { message }
, formGroup , formGroup
[ emailInput email ] [ emailInput email ]
, submitButton { backend, email, sessions } , submitButton { backend, email, sessions, message }
] ]
] ]
...@@ -50,14 +54,15 @@ emailInput value = F.bindInput { value ...@@ -50,14 +54,15 @@ emailInput value = F.bindInput { value
, maxLength: "254" } , maxLength: "254" }
type SubmitButtonProps = type SubmitButtonProps =
( email :: T.Box Email ( email :: T.Box Email
, message :: T.Box String
| Props ) | Props )
submitButton :: R2.Leaf SubmitButtonProps submitButton :: R2.Leaf SubmitButtonProps
submitButton = R2.leafComponent submitButtonCpt submitButton = R2.leafComponent submitButtonCpt
submitButtonCpt :: R.Component SubmitButtonProps submitButtonCpt :: R.Component SubmitButtonProps
submitButtonCpt = here.component "submitButton" cpt where submitButtonCpt = here.component "submitButton" cpt where
cpt { backend, email, sessions } _ = do cpt { backend, email, sessions, message} _ = do
email' <- T.useLive T.unequal email email' <- T.useLive T.unequal email
pure $ H.div {className: "form-group text-center"} pure $ H.div {className: "form-group text-center"}
...@@ -75,3 +80,16 @@ submitButtonCpt = here.component "submitButton" cpt where ...@@ -75,3 +80,16 @@ submitButtonCpt = here.component "submitButton" cpt where
launchAff_ $ do launchAff_ $ do
res <- postForgotPasswordRequest backend email' res <- postForgotPasswordRequest backend email'
liftEffect $ here.log2 "res" res liftEffect $ here.log2 "res" res
liftEffect $ case res of
Left s -> T.write_ s message
Right _ -> T.write_ "Request sent!" message
messageDisplay :: R2.Leaf (message :: T.Box String)
messageDisplay = R2.leafComponent messageDisplayCpt
messageDisplayCpt :: R.Component (message :: T.Box String)
messageDisplayCpt = here.component "messageDisplay" cpt where
cpt {message} _ = do
message' <- T.useLive T.unequal message
pure $ H.p {} [H.text message']
\ No newline at end of file
'use strict';
exports.modalShow = function(name) {
return function(){
var myModal = document.getElementById(name);
var myModalInstance = new Modal(myModal);
myModalInstance.show();
};
};
exports.modalHide = function(name){
return function() {
var myModal = document.getElementById(name);
var myModalInstance = new Modal(myModal);
myModalInstance.hide();
};
};
module Gargantext.Components.Modals.Modal where
import Prelude (Unit)
import Effect (Effect)
foreign import modalShow :: String -> Effect Unit
foreign import modalHide :: String -> Effect Unit
This diff is collapsed.
...@@ -68,7 +68,12 @@ tabsCpt = here.component "tabs" cpt where ...@@ -68,7 +68,12 @@ tabsCpt = here.component "tabs" cpt where
yearFilter <- T.useBox (Nothing :: Maybe Year) yearFilter <- T.useBox (Nothing :: Maybe Year)
chartReload <- T.useBox T2.newReload chartReload <- T.useBox T2.newReload
pure $ Tab.tabs { activeTab, tabs: tabs' yearFilter chartReload props } pure $
Tab.tabs
{ activeTab
, tabs: tabs' yearFilter chartReload props
, className: "nodes-annuaire-layout-tabs"
}
tabs' yearFilter chartReload props@{ boxes, defaultListId, sidePanel } = tabs' yearFilter chartReload props@{ boxes, defaultListId, sidePanel } =
[ "Documents" /\ docs [ "Documents" /\ docs
, "Patents" /\ ngramsView (viewProps Patents) , "Patents" /\ ngramsView (viewProps Patents)
......
...@@ -16,7 +16,7 @@ import Effect.Class (liftEffect) ...@@ -16,7 +16,7 @@ import Effect.Class (liftEffect)
import Gargantext.Components.App.Store (Boxes) import Gargantext.Components.App.Store (Boxes)
import Gargantext.Components.GraphQL (getClient) import Gargantext.Components.GraphQL (getClient)
import Gargantext.Components.GraphQL.Endpoints (getUserInfo) import Gargantext.Components.GraphQL.Endpoints (getUserInfo)
import Gargantext.Components.GraphQL.User (UserInfo, _ui_cwCity, _ui_cwCountry, _ui_cwFirstName, _ui_cwLabTeamDeptsFirst, _ui_cwLastName, _ui_cwOffice, _ui_cwOrganizationFirst, _ui_cwRole, _ui_cwTouchMail, _ui_cwTouchPhone) import Gargantext.Components.GraphQL.User (UserInfo, _ui_cwCity, _ui_cwCountry, _ui_cwFirstName, _ui_cwLabTeamDeptsFirst, _ui_cwLastName, _ui_cwOffice, _ui_cwOrganizationFirst, _ui_cwRole, _ui_cwTouchMail, _ui_cwTouchPhone, _ui_cwDescription)
import Gargantext.Components.InputWithEnter (inputWithEnter) import Gargantext.Components.InputWithEnter (inputWithEnter)
import Gargantext.Components.Nodes.Annuaire.Tabs as Tabs import Gargantext.Components.Nodes.Annuaire.Tabs as Tabs
import Gargantext.Components.Nodes.Annuaire.User.Contacts.Types (Contact(..), ContactData, ContactTouch(..), ContactWhere(..), ContactWho(..), HyperdataContact(..), HyperdataUser(..), _city, _country, _firstName, _labTeamDeptsJoinComma, _lastName, _mail, _office, _organizationJoinComma, _ouFirst, _phone, _role, _shared, _touch, _who, defaultContactTouch, defaultContactWhere, defaultContactWho, defaultHyperdataContact, defaultHyperdataUser) import Gargantext.Components.Nodes.Annuaire.User.Contacts.Types (Contact(..), ContactData, ContactTouch(..), ContactWhere(..), ContactWho(..), HyperdataContact(..), HyperdataUser(..), _city, _country, _firstName, _labTeamDeptsJoinComma, _lastName, _mail, _office, _organizationJoinComma, _ouFirst, _phone, _role, _shared, _touch, _who, defaultContactTouch, defaultContactWhere, defaultContactWho, defaultHyperdataContact, defaultHyperdataUser)
...@@ -170,6 +170,7 @@ contactInfoItems = ...@@ -170,6 +170,7 @@ contactInfoItems =
, { label: "Role" , defaultVal: "Empty Role" , lens: _ui_cwRole } , { label: "Role" , defaultVal: "Empty Role" , lens: _ui_cwRole }
, { label: "Phone" , defaultVal: "Empty Phone" , lens: _ui_cwTouchPhone } , { label: "Phone" , defaultVal: "Empty Phone" , lens: _ui_cwTouchPhone }
, { label: "Mail" , defaultVal: "Empty Mail" , lens: _ui_cwTouchMail } , { label: "Mail" , defaultVal: "Empty Mail" , lens: _ui_cwTouchMail }
, { label: "Description" , defaultVal: "No description" , lens: _ui_cwDescription }
] ]
type UserInfoLens = L.ALens' UserInfo String type UserInfoLens = L.ALens' UserInfo String
...@@ -284,7 +285,8 @@ saveUserInfo session id ui = do ...@@ -284,7 +285,8 @@ saveUserInfo session id ui = do
, ui_cwCountry: ga ui.ui_cwCountry , ui_cwCountry: ga ui.ui_cwCountry
, ui_cwRole: ga ui.ui_cwRole , ui_cwRole: ga ui.ui_cwRole
, ui_cwTouchPhone: ga ui.ui_cwTouchPhone , ui_cwTouchPhone: ga ui.ui_cwTouchPhone
, ui_cwTouchMail: ga ui.ui_cwTouchMail } } , ui_cwTouchMail: ga ui.ui_cwTouchMail
, ui_cwDescription: ga ui.ui_cwDescription } }
pure $ Right res.update_user_info pure $ Right res.update_user_info
where where
ga Nothing = ArgL IgnoreArg ga Nothing = ArgL IgnoreArg
......
This diff is collapsed.
This diff is collapsed.
...@@ -275,6 +275,7 @@ layoutCpt = here.component "layout" cpt where ...@@ -275,6 +275,7 @@ layoutCpt = here.component "layout" cpt where
{ session { session
, frameDoc: frameDoc_ , frameDoc: frameDoc_
, closeCallback: closeDocCallback , closeCallback: closeDocCallback
, key: show $ getter _.docId frameDoc_
} }
] ]
] ]
......
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
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