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 @@
<body>
<div id="app"></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>
</body>
</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",
"version": "0.0.5.9",
"version": "0.0.5.9.5",
"scripts": {
"generate-purs-packages-nix": "./nix/generate-purs-packages.nix",
"generate-psc-packages-nix": "./nix/generate-packages-json.bash",
......
......@@ -22,7 +22,7 @@ import Data.Tuple (Tuple(..), snd)
import Data.Tuple.Nested ((/\))
import Effect (Effect)
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.Types (NgramsTable, NgramsTerm)
import Gargantext.Types (CTabNgramType(..), TermList)
......@@ -42,6 +42,7 @@ type Props =
( ngrams :: NgramsTable
, setTermList :: NgramsTerm -> Maybe TermList -> TermList -> Effect Unit
, text :: Maybe String
, mode :: ModeType
)
type MouseEvent = E.SyntheticEvent DE.MouseEvent
......@@ -73,7 +74,7 @@ annotatedFieldInner = R2.leafComponent annotatedFieldInnerCpt
annotatedFieldInnerCpt :: R.Component InnerProps
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
-- menu <- T.useBox (Nothing :: Maybe (Record AnnotationMenu))
......@@ -89,9 +90,29 @@ annotatedFieldInnerCpt = here.component "annotatedFieldInner" cpt where
[
annotationMenu { menuRef }
,
H.div
{ className: "annotated-field-runs" }
((\p -> annotateRun p) <$> wrap <$> compile ngrams fieldText)
case mode of
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
( MenuType(..)
, termClass
, ModeType(..)
)
where
......@@ -8,14 +9,36 @@ import Gargantext.Prelude
import Data.Eq.Generic (genericEq)
import Data.Generic.Rep (class Generic)
import Data.Maybe (Maybe(..))
import Data.Show.Generic (genericShow)
import Gargantext.Types (TermList(..))
---------------------------------------------------------
data MenuType = NewNgram | SetTermListItem
derive instance Generic MenuType _
instance Eq MenuType where
eq = genericEq
----------------------------------------------------------
termClass :: TermList -> String
termClass CandidateTerm = "candidate-term"
termClass MapTerm = "graph-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';
exports._addClassName = function(window, className) {
window.document.body.classList.add(className);
exports._show = show;
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) {
window.document.body.classList.remove(className);
/**
* @function hide
* @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 DOM.Simple (Window, window)
import Data.Foldable (intercalate)
import Data.Maybe (Maybe(..))
import Data.UUID as UUID
import Effect (Effect)
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 Reactix as R
import Reactix.DOM.HTML as H
import Toestand as T
foreign import _addClassName :: EffectFn2 Window String Unit
foreign import _removeClassName :: EffectFn2 Window String Unit
foreign import _show :: EffectFn2
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 =
( isVisibleBox :: T.Box Boolean
( isVisibleBox :: T.Box Boolean
| Options
)
type Options =
( id :: String
, title :: String
, hasBackground :: Boolean
, hasCollapsibleBackground :: Boolean
( modalClassName :: String
, title :: Maybe String
, hasCollapsibleBackground :: Boolean
, hasInnerScroll :: Boolean
, noHeader :: Boolean
, noBody :: Boolean -- ie. Bootstrap Body
, size :: ModalSizing
)
options :: Record Options
options =
{ id: ""
, title: ""
, hasBackground: true
, hasCollapsibleBackground: true
{ modalClassName : ""
, title : Nothing
, hasCollapsibleBackground : true
, hasInnerScroll : false
, noHeader : false
, noBody : false
, size : MediumModalSize
}
componentName :: String
componentName = "b-modal"
vendorName :: String
vendorName = "modal"
-- | Structural Component for the Bootstrap 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 = R2.optComponent component options
component :: R.Component Props
component = R.hooksComponent componentName cpt where
cpt { isVisibleBox
, id
, title
, hasBackground
, hasCollapsibleBackground
} children = do
-- State
cpt props@{ isVisibleBox
, title
, hasCollapsibleBackground
, hasInnerScroll
, noHeader
, noBody
, size
} children
= R.unsafeHooksEffect (UUID.genUUID >>= pure <<< UUID.toString)
>>= \uuid -> do
-- | States
-- |
isVisible <- R2.useLive' isVisibleBox
-- Hooks
R.useEffect1' isVisible $
(isVisible ? addClassName $ removeClassName) window "modal-open"
-- Computed
-- | Computed
-- |
let
className = intercalate " "
-- Component
[ componentName
, isVisible ?
componentName <> "--visible" $
componentName <> "--hidden"
-- Vendor
, vendorName
-- Bootstrap
, "modal"
]
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
[
H.div
{ id
{ id: id
, className
, role: "dialog"
, data: { show: true }
, tabIndex: "-1"
, key: id
, data:
{ keyboard: "false"
, backdrop: hasCollapsibleBackground ?
"true" $
"static"
}
}
[
R2.when (hasBackground) $
-- Overlay fixing collapsable click event
R2.when (hasCollapsibleBackground) $
H.div
{ className: intercalate " "
[ componentName <> "__overlay"
, hasCollapsibleBackground ?
componentName <> "__overlay--collapsible" $
""
]
, on: { click: hasCollapsibleBackground ?
toggle isVisibleBox $
const $ pure unit
}
{ className: componentName <> "__overlay"
, on: { click: onCloseButtonClick }
}
[ H.text $ nbsp 1 ]
[]
,
H.div
{ className: "modal-dialog modal-lg"
, role: "document"
{ className: intercalate " "
-- Bootstrap classNames
[ "modal-dialog"
, show size
, "modal-dialog-centered"
, hasInnerScroll ? "modal-dialog-scrollable" $ ""
-- provided custom className
, props.modalClassName
]
}
[
H.div
{ className: intercalate " "
[ componentName <> "__content"
, vendorName <> "-content"
, "modal-content"
]
}
[
R2.when (hasHeader) $
-- Header
R2.when (not noHeader) $
H.div
{ className: intercalate " "
[ componentName <> "__header"
, vendorName <> "-header"
, "modal-header"
]
}
[
H.div
{ className: componentName <> "__header__content" }
[ H.text title ]
R2.fromMaybe (title) \title' ->
H.div
{ className: componentName <> "__header__title" }
[ H.text title' ]
,
H.button
{ type: "button"
, className: "close"
, data: { dismiss: "modal" }
}
[
H.a
{ on: { click: toggle isVisibleBox }
, className: "btn fa fa-times" }
{
on: { click: onCloseButtonClick }
, className: "btn fa fa-times"
}
[]
]
]
,
-- Body
H.div
{ className: "modal-body" }
{ className: intercalate " "
[ componentName <> "__body"
, noBody ? "" $ "modal-body"
]
}
children
]
]
]
]
<$> 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 =
-- | 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 = R2.optComponent component options
......
......@@ -6,6 +6,7 @@ module Gargantext.Components.Bootstrap.Types
, TooltipEffect(..), TooltipPosition(..)
, Position(..)
, Elevation(..)
, ModalSizing(..)
) where
import Gargantext.Prelude
......@@ -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
-- |
-- | Example: https://material.io/design/environment/elevation.html
......@@ -176,3 +177,22 @@ data Elevation
derive instance Generic Elevation _
derive instance Eq Elevation
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
import Data.Maybe (Maybe(..))
import Effect.Aff (launchAff_)
import Effect.Class (liftEffect)
import Gargantext.Components.Bootstrap as B
import Gargantext.Components.Bootstrap.Types (Variant(..))
import Gargantext.Components.Category.Types (Category(..), Star(..), cat2score, categories, clickAgain, star2score, stars)
import Gargantext.Components.DocsTable.Types (DocumentsView(..), LocalCategories, LocalUserScore)
import Gargantext.Config.REST (AffRESTError)
import Gargantext.Routes (SessionRoute(NodeAPI))
import Gargantext.Sessions (Session, put)
import Gargantext.Types (NodeID, NodeType(..))
import Gargantext.Utils ((?))
import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Toestand as T2
import Reactix as R
......@@ -42,23 +45,53 @@ ratingCpt = here.component "rating" cpt where
, row: DocumentsView r
, score
, session
, setLocalCategories } _ =
pure $ H.div { className:"flex" } divs where
divs = map (\s -> H.div { className : icon' score s
, on: { click: onClick s } } []) stars
icon' Star_0 Star_0 = "fa fa-times-circle"
icon' _ Star_0 = "fa fa-times"
icon' c s = if star2score c < star2score s then "fa fa-star-o" else "fa fa-star"
, setLocalCategories
} _ = do
-- | Computed
-- |
let
icon' Star_0 Star_0 = "times-circle"
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
let c' = if score == c
then clickAgain c
else c
let c' = score == c ? clickAgain c $ c
setLocalCategories $ Map.insert r._id c'
launchAff_ $ do
_ <- putRating session nodeId $ RatingQuery { nodeIds: [r._id], rating: c' }
launchAff_ do
_ <- putRating session nodeId $ RatingQuery
{ nodeIds: [r._id]
, rating: c'
}
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 =
RatingQuery { nodeIds :: Array Int
, rating :: Star
......
......@@ -6,7 +6,6 @@ import Gargantext.Prelude
import DOM.Simple.Event as DE
import Data.Array (any)
import Data.Array as A
import Data.Either (Either)
import Data.Generic.Rep (class Generic)
import Data.Lens ((^.))
import Data.Lens.At (at)
......@@ -27,7 +26,7 @@ import Effect.Class (liftEffect)
import Effect.Timer (setTimeout)
import Gargantext.Components.App.Store (Boxes)
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.Types (Star(..))
import Gargantext.Components.DocsTable.DocumentFormCreation as DFC
......@@ -228,8 +227,9 @@ docViewCpt = here.component "docView" cpt where
-- Document Creation Modal
B.baseModal
{ isVisibleBox: isDocumentModalVisibleBox
, title: "Add a new document"
, title: Just "Add a new document"
, hasCollapsibleBackground: false
, size: LargeModalSize
}
[
DFC.documentFormCreation
......@@ -540,6 +540,9 @@ pagePaintRawCpt = here.component "pagePaintRaw" cpt where
reload <- T.useBox GUT.newReload
localCategories' <- T.useLive T.unequal localCategories
let
selected = mCurrentDocId' == Just nodeId
pure $ TT.table
{ colNames
, container: TT.defaultContainer
......@@ -551,9 +554,9 @@ pagePaintRawCpt = here.component "pagePaintRaw" cpt where
}
where
sid = sessionId session
trashClassName Star_0 _ = "trash"
trashClassName _ true = "active"
trashClassName _ false = ""
trashClassName Star_0 _ = "page-paint-row page-paint-row--trash"
trashClassName _ true = "page-paint-row page-paint-row--active"
trashClassName _ false = ""
corpusDocument
| Just cid <- mCorpusId = Routes.CorpusDocument sid cid listId
| otherwise = Routes.Document sid listId
......@@ -563,7 +566,14 @@ pagePaintRawCpt = here.component "pagePaintRaw" cpt where
where
row dv@(DocumentsView r@{ _id, category }) =
{ 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: "" }
[ docChooser { boxes
, listId
......@@ -582,10 +592,17 @@ pagePaintRawCpt = here.component "pagePaintRaw" cpt where
--, H.input { type: "checkbox", defaultValue: checked, on: {click: click Trash} }
-- TODO show date: Year-Month-Day only
, H.div { className: tClassName } [ R2.showText r.date ]
, H.div { className: tClassName }
[ H.a { href: url frontends $ corpusDocument r._id, target: "_blank" }
[ H.text r.title ]
]
,
H.div
{ 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 {} [ H.text $ maybe "-" show r.ngramCount ]
]
......@@ -623,11 +640,19 @@ docChooserCpt = here.component "docChooser" cpt
mCurrentDocId' <- T.useLive T.unequal mCurrentDocId
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" } [
H.span { className: "fa " <> eyeClass
, on: { click: onClick selected } } []
pure $
H.div
{ className: "doc-chooser" }
[
B.iconButton
{ name: eyeClass
, overlay: false
, variant
, callback: onClick selected
}
]
where
onClick selected _ = do
......
This diff is collapsed.
......@@ -28,19 +28,24 @@ nodePopupViewCpt :: R.Component NodePopupProps
nodePopupViewCpt = here.component "nodePopupView" cpt where
cpt props _ = do
pure $ H.div tooltipProps
[ H.div { className: "popup-container" }
[ H.div { className: "card" }
[ panelHeading props
]]]
closePopover props = props.onPopoverClose <<< R.unsafeEventTarget
tooltipProps = { id: "node-popup-tooltip", title: "Node settings"
, data: { toggle: "tooltip", placement: "right" } }
pure $
H.div
{ className: "node-popup-tooltip"
, title: "Node settings"
}
[
H.div
{ className: "popup-container card" }
[
panelHeading props
]
]
closeBox props = props.onPopoverClose <<< R.unsafeEventTarget
panelHeading props@{ nodeType } =
H.div { className: "card-header" }
H.div { className: "popup-container__header card-header" }
[ R2.row
[ H.div { className: "col-4" }
[ H.span { className: GT.fldr nodeType true} [] -- TODO fix names
......@@ -48,5 +53,5 @@ nodePopupViewCpt = here.component "nodePopupView" cpt where
, H.div { className: "col-6" }
[ H.span { className: "text-primary center" } [ H.text props.name ] ]
, H.div { className: "col-1" }
[ H.a { type: "button", on: { click: closePopover props }, title: "Close"
, className: glyphicon "window-close" } [] ]]]
[ H.a { type: "button", on: { click: closeBox props }, title: "Close"
, className: glyphicon "window-close" } [] ]]]
......@@ -7,7 +7,6 @@ import Data.Array as Array
import Data.Maybe (Maybe(..), isJust)
import Data.Traversable (intercalate, traverse, traverse_)
import Data.Tuple.Nested ((/\))
import Effect (Effect)
import Effect.Aff (Aff)
import Effect.Class (liftEffect)
import Gargantext.AsyncTasks as GAT
......@@ -31,13 +30,13 @@ import Gargantext.Components.Forest.Tree.Node.Tools.SubTree.Types (SubTreeOut(..
import Gargantext.Config.REST (AffRESTError, logRESTError)
import Gargantext.Config.Utils (handleRESTError)
import Gargantext.Ends (Frontends)
import Gargantext.Hooks.Loader (useLoader, useLoaderEffect)
import Gargantext.Hooks.Loader (useLoaderEffect)
import Gargantext.Routes as GR
import Gargantext.Sessions (Session, get, mkNodeId)
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.Utils (nbsp, (?))
import Gargantext.Utils ((?))
import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Toestand as T2
import Reactix as R
......@@ -99,11 +98,13 @@ type ChildLoaderProps =
( id :: ID
, render :: R2.Leaf TreeProps
, root :: ID
| NodeProps )
| NodeProps
)
type PerformActionProps =
( setPopoverRef :: R.Ref (Maybe (Boolean -> Effect Unit))
| PACommon )
( isBoxVisible :: T.Box Boolean
| PACommon
)
-- | Loads and renders the tree starting at the given root node id.
treeLoader :: R2.Leaf ( key :: String | LoaderProps )
......@@ -163,9 +164,9 @@ treeCpt = here.component "tree" cpt where
, session
, tree: NTree (LNode { id, name, nodeType }) children } _ = do
setPopoverRef <- R.useRef Nothing
folderOpen <- useOpenNodesMemberBox nodeId forestOpen
folderOpen' <- T.useLive T.unequal folderOpen
isBoxVisible <- T.useBox false
folderOpen <- useOpenNodesMemberBox nodeId forestOpen
folderOpen' <- T.useLive T.unequal folderOpen
pure $
......@@ -183,7 +184,7 @@ treeCpt = here.component "tree" cpt where
[
nodeSpan
{ boxes
, dispatch: dispatch setPopoverRef
, dispatch: dispatch' isBoxVisible
, folderOpen
, frontends
, id
......@@ -193,7 +194,7 @@ treeCpt = here.component "tree" cpt where
, reload
, root
, session
, setPopoverRef
, isBoxVisible
}
<>
R2.when (folderOpen')
......@@ -213,9 +214,9 @@ treeCpt = here.component "tree" cpt where
nodeId = mkNodeId session id
children' = A.sortWith fTreeID pubChildren
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
spr = { setPopoverRef }
extra = { isBoxVisible }
pub (LNode n@{ nodeType: t }) = LNode (n { nodeType = publicize t })
......@@ -295,10 +296,10 @@ childLoaderCpt = here.component "childLoader" cpt where
extra = { root, tree: tree' }
nodeProps = RecordE.pick p :: Record NodeProps
closePopover { setPopoverRef } =
liftEffect $ traverse_ (\set -> set false) (R.readRef setPopoverRef)
closeBox { isBoxVisible } =
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
case nt of
......@@ -407,6 +408,6 @@ performAction (MoveNode {params}) p = moveNode params
performAction (MergeNode {params}) p = mergeNode params p
performAction (LinkNode { nodeType, params }) p = linkNode nodeType params p
performAction RefreshTree p = refreshTree p
performAction ClosePopover p = closePopover p
performAction CloseBox p = closeBox p
performAction (DocumentsFromWriteNodes { id }) p = documentsFromWriteNodes id p
performAction NoAction _ = liftEffect $ here.log "[performAction] NoAction"
......@@ -8,7 +8,6 @@ import Gargantext.Prelude
import Data.Array.NonEmpty as NArray
import Data.Foldable (intercalate)
import Data.Maybe (Maybe(..), maybe)
import Data.Nullable (null)
import Data.String.Regex as Regex
import Data.Symbol (SProxy(..))
import Data.Tuple.Nested ((/\))
......@@ -31,7 +30,6 @@ import Gargantext.Components.Nodes.Corpus (loadCorpusWithChild)
import Gargantext.Config.REST (logRESTError)
import Gargantext.Context.Progress (asyncContext, asyncProgress)
import Gargantext.Ends (Frontends, url)
import Gargantext.Hooks.FirstEffect (useFirstEffect')
import Gargantext.Hooks.Loader (useLoaderEffect)
import Gargantext.Hooks.Version (Version, useVersion)
import Gargantext.Routes as Routes
......@@ -39,7 +37,6 @@ import Gargantext.Sessions (Session, sessionId)
import Gargantext.Types (ID, Name)
import Gargantext.Types as GT
import Gargantext.Utils (nbsp, textEllipsisBreak, (?))
import Gargantext.Utils.Popover as Popover
import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Toestand as T2
import React.SyntheticEvent as SE
......@@ -67,7 +64,7 @@ type NodeSpanProps =
, reload :: T2.ReloadS
, root :: ID
, session :: Session
, setPopoverRef :: R.Ref (Maybe (Boolean -> Effect Unit))
, isBoxVisible :: T.Box Boolean
)
type IsLeaf = Boolean
......@@ -91,7 +88,7 @@ nodeSpanCpt = here.component "nodeSpan" cpt
, nodeType
, reload
, session
, setPopoverRef
, isBoxVisible
} _ = do
-- States
......@@ -101,9 +98,8 @@ nodeSpanCpt = here.component "nodeSpan" cpt
droppedFile' <- T.useLive T.unequal droppedFile
isDragOver <- T.useBox false
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
folderOpen' <- R2.useLive' folderOpen
......@@ -196,20 +192,12 @@ nodeSpanCpt = here.component "nodeSpan" cpt
-- Nothing -> pure unit
-- T2.reload reloadRoot
onPopoverClose ::
Popover.PopoverRef
-> Effect Unit
onPopoverClose ref = Popover.setOpen ref false
-- NOTE Don't toggle tree if it is not selected
onNodeLinkClick :: Unit -> Effect Unit
onNodeLinkClick _ = when (not isSelected) (T.write_ true folderOpen)
-- Hooks
useFirstEffect' $
R.setRef setPopoverRef $ Just $ Popover.setOpen popoverRef
mVersion <- useVersion $ nodeType == GT.NodeUser ?
Just { session } $
Nothing
......@@ -313,42 +301,18 @@ nodeSpanCpt = here.component "nodeSpan" cpt
, 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) $
Popover.popover
{ arrow: false
, open: false
, onClose: \_ -> pure unit
, onOpen: \_ -> pure unit
, ref: popoverRef
B.iconButton
{ name: "cog"
, className: "mainleaf__settings-icon"
, callback: \_ -> T.write_ true isBoxVisible
, title:
"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 ->
......@@ -363,6 +327,27 @@ nodeSpanCpt = here.component "nodeSpan" cpt
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
icon (UploadArbitraryFile _ _ _ _ ) = glyphiconNodeAction Upload
icon UploadFrameCalc = glyphiconNodeAction Upload
icon RefreshTree = glyphiconNodeAction Refresh
icon ClosePopover = glyphiconNodeAction CloseNodePopover
icon CloseBox = glyphiconNodeAction CloseNodePopover
icon DownloadNode = glyphiconNodeAction Download
icon (MoveNode _ ) = glyphiconNodeAction (Move { subTreeParams : SubTreeParams {showtypes:[], valitypes:[] }})
icon (MergeNode _ ) = glyphiconNodeAction (Merge { subTreeParams : SubTreeParams {showtypes:[], valitypes:[] }})
......@@ -70,7 +70,7 @@ text (UploadFile _ _ _ _ _ _) = "Upload File !"
text (UploadArbitraryFile _ _ _ _) = "Upload arbitrary file !"
text UploadFrameCalc = "Upload frame calc"
text RefreshTree = "Refresh Tree !"
text ClosePopover = "Close Popover !"
text CloseBox = "Close Box !"
text DownloadNode = "Download !"
text (MoveNode _ ) = "Move !"
text (MergeNode _ ) = "Merge !"
......@@ -78,4 +78,3 @@ text (LinkNode _ ) = "Link !"
text (DocumentsFromWriteNodes _ ) = "Documents from Write Nodes !"
text NoAction = "No Action"
-----------------------------------------------------------------------
......@@ -37,7 +37,7 @@ actionSearchCpt = here.component "actionSearch" cpt
cpt { boxes: { errors }, dispatch, id, session } _ = do
search <- T.useBox $ defaultSearch { node_id = id }
pure $ R.fragment
[ H.p { className: "action-search" }
[ H.p { className: "action-search m-1" }
[ H.text $ "Search and create a private "
<> "corpus with the search query as corpus name." ]
, searchBar { errors
......@@ -54,7 +54,7 @@ actionSearchCpt = here.component "actionSearch" cpt
searchOn dispatch' task = do
_ <- launchAff $ dispatch' (DoSearch task)
-- close popup
_ <- launchAff $ dispatch' ClosePopover
_ <- launchAff $ dispatch' CloseBox
-- TODO
--snd p $ const Nothing
pure unit
......@@ -33,7 +33,7 @@ searchBarCpt = here.component "searchBar" cpt
where
cpt { errors, langs, onSearch, search, session } _ = do
--onSearchChange session s
pure $ H.div { className: "search-bar" }
pure $ H.div { className: "search-bar m-1" }
[ searchField { databases: allDatabases
, errors
, langs
......
......@@ -21,7 +21,7 @@ data Action = AddNode String GT.NodeType
| UploadFrameCalc
| DownloadNode
| RefreshTree
| ClosePopover
| CloseBox
| ShareTeam String
| AddContact AddContactParams
......@@ -48,7 +48,7 @@ instance Eq Action where
eq UploadFrameCalc UploadFrameCalc = true
eq DownloadNode DownloadNode = true
eq RefreshTree RefreshTree = true
eq ClosePopover ClosePopover = true
eq CloseBox CloseBox = true
eq (ShareTeam s1) (ShareTeam s2) = eq s1 s2
eq (AddContact ac1) (AddContact ac2) = eq ac1 ac2
eq (SharePublic p1) (SharePublic p2) = eq p1 p2
......@@ -72,7 +72,7 @@ instance Show Action where
show (UploadArbitraryFile _ _ _ _) = "UploadArbitraryFile"
show UploadFrameCalc = "UploadFrameCalc"
show RefreshTree = "RefreshTree"
show ClosePopover = "ClosePopover"
show CloseBox = "CloseBox"
show DownloadNode = "Download"
show (MoveNode _ ) = "MoveNode"
show (MergeNode _ ) = "MergeNode"
......
......@@ -2,7 +2,7 @@ module Gargantext.Components.Forest.Tree.Node.Action.Update where
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 Data.Either (Either(..))
......@@ -78,18 +78,28 @@ updateGraphCpt = here.component "updateGraph" cpt where
methodGraphMetric <- T.useBox Order1
methodGraphMetric' <- T.useLive T.unequal methodGraphMetric
methodGraphEdgesStrength <- T.useBox Strong
methodGraphEdgesStrength' <- T.useLive T.unequal methodGraphEdgesStrength
methodGraphClustering <- T.useBox Spinglass
methodGraphClustering' <- T.useLive T.unequal methodGraphClustering
let
callback :: Action -> Aff Unit
callback = dispatch >=> \_ -> dispatch ClosePopover
callback = dispatch >=> \_ -> dispatch CloseBox
pure $ panel [ -- H.text "Update with"
formChoiceSafe { items: [Order1, Order2]
pure $ panel [ H.text "Show subjects with Order1 or concepts with Order2 ?"
, formChoiceSafe { items: [Order1, Order2]
, default: methodGraphMetric'
, callback: \val -> T.write_ val methodGraphMetric
, 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]
, default: methodGraphClustering'
, callback: \val -> T.write_ val methodGraphClustering
......@@ -98,6 +108,7 @@ updateGraphCpt = here.component "updateGraph" cpt where
]
(submitButton (UpdateNode $ UpdateNodeParamsGraph { methodGraphMetric: methodGraphMetric'
, methodGraphClustering: methodGraphClustering'
, methodGraphEdgesStrength : methodGraphEdgesStrength'
}
) callback
)
......@@ -142,7 +153,7 @@ updatePhyloCpt = here.component "updatePhylo" cpt where
opts <- pure $ options r'
launchAff_ do
dispatch opts
dispatch ClosePopover
dispatch CloseBox
where
options :: Phylo.UpdateData -> Action
......
......@@ -14,6 +14,7 @@ import Simple.JSON.Generics as JSONG
data UpdateNodeParams
= UpdateNodeParamsList { methodList :: Method }
| UpdateNodeParamsGraph { methodGraphMetric :: GraphMetric
, methodGraphEdgesStrength :: Strength
, methodGraphClustering :: PartitionMethod
}
| UpdateNodeParamsTexts { methodTexts :: Granularity }
......@@ -28,9 +29,9 @@ instance JSON.WriteForeign UpdateNodeParams where
writeImpl (UpdateNodeParamsList { methodList }) =
JSON.writeImpl { type: "UpdateNodeParamsList"
, methodList }
writeImpl (UpdateNodeParamsGraph { methodGraphMetric, methodGraphClustering }) =
writeImpl (UpdateNodeParamsGraph { methodGraphMetric, methodGraphClustering, methodGraphEdgesStrength}) =
JSON.writeImpl { type: "UpdateNodeParamsGraph"
, methodGraphMetric, methodGraphClustering }
, methodGraphMetric, methodGraphClustering, methodGraphEdgesStrength}
writeImpl (UpdateNodeParamsTexts { methodTexts }) =
JSON.writeImpl { type: "UpdateNodeParamsTexts"
, methodTexts }
......@@ -71,6 +72,19 @@ instance Read GraphMetric where
instance JSON.ReadForeign GraphMetric where readImpl = JSONG.enumSumRep
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
derive instance Generic PartitionMethod _
derive instance Eq PartitionMethod
......
......@@ -265,7 +265,7 @@ uploadButtonCpt = here.component "uploadButton" cpt
T.write_ Plain fileFormat
T.write_ EN lang
T.write_ false onPendingBox
dispatch ClosePopover
dispatch CloseBox
uploadListView :: R2.Leaf Props
uploadListView = R2.leafComponent uploadListViewCpt
......
......@@ -5,11 +5,8 @@ import Gargantext.Prelude
import Data.Array as A
import Data.Maybe (Maybe(..))
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.Bootstrap as B
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.Delete (actionDelete)
......@@ -34,13 +31,17 @@ import Gargantext.Types (ID, Name, prettyNodeType)
import Gargantext.Types as GT
import Gargantext.Utils.Glyphicon (glyphicon, glyphiconActive)
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 "Gargantext.Components.Forest.Tree.Node.Box"
type CommonProps =
( dispatch :: Action -> Aff Unit
, session :: Session )
( dispatch :: Action -> Aff Unit
, session :: Session
)
nodePopupView :: R2.Leaf NodePopupProps
nodePopupView = R2.leafComponent nodePopupCpt
......@@ -53,24 +54,26 @@ nodePopupCpt = here.component "nodePopupView" cpt where
action <- T.useFocused (_.action) (\a b -> b { action = a }) nodePopup
nodePopup' <- T.useLive T.unequal nodePopup
pure $ H.div tooltipProps
[ H.div { className: "popup-container" }
[ H.div { className: "card" }
[ panelHeading renameIsOpen open p
, H.div { className: "popup-container-body" }
[
panelBody action p
,
mPanelAction nodePopup' p
]
]
pure $
H.div
{ className: "node-popup-tooltip"
, title: "Node settings"
}
[
H.div
{ 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 } =
H.div { className: "card-header" }
H.div { className: "popup-container__header card-header" }
[ R2.row
[ H.div { className: "col-4" }
[ H.span { className: GT.fldr nodeType true} [] -- TODO fix names
......@@ -83,7 +86,7 @@ nodePopupCpt = here.component "nodePopupView" cpt where
]
, H.div { className: "col-1" } [ editIcon renameIsOpen open ]
, 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" } [] ]]]
editIcon _ true = H.div {} []
editIcon isOpen false =
......@@ -92,8 +95,8 @@ nodePopupCpt = here.component "nodePopupView" cpt where
panelBody :: T.Box (Maybe NodeAction) -> Record NodePopupProps -> R.Element
panelBody nodePopupState { nodeType } =
let (SettingsBox { doc, buttons }) = settingsBox nodeType in
H.div {className: "card-body flex-space-between"}
$ [ H.p { className: "spacer" } []
H.div {className: "popup-container__body card-body flex-space-between"}
$ [ B.wad_ [ "m-1" ]
, H.div { className: "flex-center" }
[ buttonClick { action: doc, state: nodePopupState, nodeType } ]
, H.div {className: "flex-center"}
......@@ -114,15 +117,15 @@ nodePopupCpt = here.component "nodePopupView" cpt where
, session
}
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.h5 {} [ H.text " Select available actions of this node" ]
, 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.div { className: "fa-exclamation-triangle almost-useable" }
, H.div { className: "fa-exclamation-triangle panel-actions__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" ]]]]
type ActionState =
......
module Gargantext.Components.Forest.Tree.Node.Box.Types where
import DOM.Simple as DOM
import Data.Maybe (Maybe)
import Effect (Effect)
import Effect.Aff (Aff)
......@@ -18,11 +17,11 @@ type CommonProps =
)
type NodePopupProps =
( boxes :: Boxes
, id :: ID
, name :: Name
, nodeType :: GT.NodeType
, onPopoverClose :: DOM.Element -> Effect Unit
( boxes :: Boxes
, id :: ID
, name :: Name
, nodeType :: GT.NodeType
, closeCallback :: Unit -> Effect Unit
| 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
import Gargantext.Prelude
import Data.Maybe (Maybe(..))
import Data.Maybe (Maybe(..), isJust)
import Data.Tuple.Nested ((/\))
import Effect (Effect)
import Gargantext.Components.Bootstrap as B
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.Nodes.Corpus.Document (node)
import Gargantext.Sessions (Session, sessionId)
import Gargantext.Config.REST (logRESTError)
import Gargantext.Hooks.Loader (useLoaderEffect)
import Gargantext.Sessions (Session)
import Gargantext.Types (CTabNgramType(..), TabSubType(..), TabType(..))
import Gargantext.Utils.Reactix as R2
import Reactix as R
import Reactix.DOM.HTML as H
......@@ -25,41 +31,74 @@ type Props =
, closeCallback :: Unit -> Effect Unit
)
docFocus :: R2.Leaf Props
docFocus :: R2.Leaf ( key :: String | Props )
docFocus = R2.leaf docFocusCpt
docFocusCpt :: R.Component Props
docFocusCpt :: R.Component ( key :: String | Props )
docFocusCpt = here.component "main" cpt where
cpt { graphSideDoc: GraphSideDoc { docId, listId, corpusId }
, session
, closeCallback
} _ = 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
-- |
pure $
H.div
{ className: "graph-doc-focus" }
[
H.div
{ className: "graph-doc-focus__header" }
[
B.iconButton
{ name: "times"
, elevation: Level2
, callback: closeCallback
}
]
,
H.div
{ className: "graph-doc-focus__body" }
[
-- print the document node
node
{ listId
, mCorpusId: Just corpusId
, nodeId: docId
, key: show (sessionId session) <> "-" <> show docId
}
]
B.cloak
{ isDisplayed: isJust state'
, idlingPhaseDuration: Just 150
, cloakSlot:
B.preloader
{}
, defaultSlot:
R2.fromMaybe state' \loaded ->
layout
{ loaded
, path
, sideControlsSlot: Just $
H.div
{ className: "graph-doc-focus__header" }
[
B.iconButton
{ name: "times"
, elevation: Level2
, callback: closeCallback
}
]
}
}
]
......@@ -31,7 +31,7 @@ import Gargantext.Hooks.Sigmax as Sigmax
import Gargantext.Hooks.Sigmax.Types as SigmaxT
import Gargantext.Types as GT
import Gargantext.Types as Types
import Gargantext.Utils ((?))
import Gargantext.Utils (getter, (?))
import Gargantext.Utils.Range as Range
import Gargantext.Utils.Reactix as R2
import Partial.Unsafe (unsafePartial)
......@@ -145,6 +145,7 @@ layoutCpt = R.memo' $ here.component "explorerWriteGraph" cpt where
{ session
, graphSideDoc
, closeCallback: closeDoc
, key: show $ getter _.docId graphSideDoc
}
]
]
......
......@@ -384,7 +384,6 @@ onExpandSelectionChange { new } = do
neighborhood :: R2.Leaf ()
neighborhood = R2.leaf neighborhoodCpt
neighborhoodCpt :: R.Memo ()
neighborhoodCpt = R.memo' $ here.component "neighborhood" cpt where
cpt _ _ = do
......@@ -495,8 +494,9 @@ neighborhoodCpt = R.memo' $ here.component "neighborhood" cpt where
R2.when
(
withTruncateResults == false
|| index < maxTruncateResult
(withTruncateResults == false
|| index < maxTruncateResult)
&& (not $ Set.member node.id selectedNodeIds')
) $
H.li
{ className: "graph-neighborhood__badge" }
......
......@@ -114,6 +114,7 @@ newtype GraphSideDoc = GraphSideDoc
, corpusId :: CorpusId
, listId :: ListId
}
derive instance Newtype GraphSideDoc _
derive instance Generic GraphSideDoc _
instance Eq GraphSideDoc where eq = genericEq
......
......@@ -24,7 +24,8 @@ type UserInfo
, ui_cwCountry :: Maybe String
, ui_cwRole :: Maybe String
, ui_cwTouchPhone :: Maybe String
, ui_cwTouchMail :: Maybe String }
, ui_cwTouchMail :: Maybe String
, ui_cwDescription :: Maybe String }
type UserInfoM
= { token :: NotNull String
, ui_id :: NotNull Int
......@@ -41,7 +42,8 @@ type UserInfoM
, ui_cwCountry :: String
, ui_cwRole :: String
, ui_cwTouchPhone :: String
, ui_cwTouchMail :: String }
, ui_cwTouchMail :: String
, ui_cwDescription :: String }
userInfoQuery = { user_infos: { user_id: Var :: _ "id" Int } =>>
{ ui_id: unit
......@@ -58,7 +60,8 @@ userInfoQuery = { user_infos: { user_id: Var :: _ "id" Int } =>>
, ui_cwOffice: unit
, ui_cwRole: unit
, ui_cwTouchMail: unit
, ui_cwTouchPhone: unit }
, ui_cwTouchPhone: unit
, ui_cwDescription: unit }
}
_ui_cwFirstName :: Lens' UserInfo String
......@@ -122,6 +125,12 @@ _ui_cwTouchPhone = lens getter setter
getter ({ ui_cwTouchPhone: val }) = fromMaybe "" 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
= { u_id :: Int
, u_hyperdata ::
......
......@@ -11,8 +11,9 @@ import Data.String as DST
import Effect.Aff (launchAff_)
import Effect.Class (liftEffect)
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.Form (form)
import Gargantext.Components.Login.Types (FormType(..))
import Gargantext.Components.NgramsTable.Loader as NTL
import Gargantext.Ends (Backend(..))
......@@ -48,12 +49,14 @@ loginCpt = here.component "login" cpt where
mBackend <- R2.useLive' props.backend
formType <- T.useBox Login
formType' <- T.useLive T.unequal formType
-- Render
pure $
B.baseModal
{ isVisibleBox: visible
, title: "GarganText ecosystem explorer"
, title: Just "GarganText ecosystem explorer"
, size: ExtraLargeModalSize
}
[
case mBackend of
......
module Gargantext.Components.Login.ForgotPassword where
import Gargantext.Prelude
import DOM.Simple.Event as DE
import Data.Either (Either(..))
import Effect (Effect)
import Effect.Aff (launchAff_)
import Effect.Class (liftEffect)
import Formula as F
import Gargantext.Components.Forms (formGroup)
import Gargantext.Ends (Backend)
import Gargantext.Prelude
import Gargantext.Sessions (Sessions, postForgotPasswordRequest)
import Gargantext.Utils.Reactix as R2
import Formula as F
import Reactix as R
import Reactix.DOM.HTML as H
import Reactix.SyntheticEvent as E
......@@ -30,13 +32,15 @@ forgotPasswordCpt :: R.Component Props
forgotPasswordCpt = here.component "forgotPassword" cpt where
cpt { backend, sessions } _ = do
email <- T.useBox ""
message <- T.useBox ""
pure $ H.div { className: "row" }
[ H.form { className: "text-center col-md-12" }
[ H.h4 {} [ H.text "Forgot password" ]
, messageDisplay { message }
, formGroup
[ emailInput email ]
, submitButton { backend, email, sessions }
, submitButton { backend, email, sessions, message }
]
]
......@@ -50,14 +54,15 @@ emailInput value = F.bindInput { value
, maxLength: "254" }
type SubmitButtonProps =
( email :: T.Box Email
( email :: T.Box Email
, message :: T.Box String
| Props )
submitButton :: R2.Leaf SubmitButtonProps
submitButton = R2.leafComponent submitButtonCpt
submitButtonCpt :: R.Component SubmitButtonProps
submitButtonCpt = here.component "submitButton" cpt where
cpt { backend, email, sessions } _ = do
cpt { backend, email, sessions, message} _ = do
email' <- T.useLive T.unequal email
pure $ H.div {className: "form-group text-center"}
......@@ -75,3 +80,16 @@ submitButtonCpt = here.component "submitButton" cpt where
launchAff_ $ do
res <- postForgotPasswordRequest backend email'
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
yearFilter <- T.useBox (Nothing :: Maybe Year)
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 } =
[ "Documents" /\ docs
, "Patents" /\ ngramsView (viewProps Patents)
......
......@@ -16,7 +16,7 @@ import Effect.Class (liftEffect)
import Gargantext.Components.App.Store (Boxes)
import Gargantext.Components.GraphQL (getClient)
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.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)
......@@ -170,6 +170,7 @@ contactInfoItems =
, { label: "Role" , defaultVal: "Empty Role" , lens: _ui_cwRole }
, { label: "Phone" , defaultVal: "Empty Phone" , lens: _ui_cwTouchPhone }
, { label: "Mail" , defaultVal: "Empty Mail" , lens: _ui_cwTouchMail }
, { label: "Description" , defaultVal: "No description" , lens: _ui_cwDescription }
]
type UserInfoLens = L.ALens' UserInfo String
......@@ -284,7 +285,8 @@ saveUserInfo session id ui = do
, ui_cwCountry: ga ui.ui_cwCountry
, ui_cwRole: ga ui.ui_cwRole
, 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
where
ga Nothing = ArgL IgnoreArg
......
This diff is collapsed.
This diff is collapsed.
......@@ -275,6 +275,7 @@ layoutCpt = here.component "layout" cpt where
{ session
, frameDoc: frameDoc_
, 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