Verified Commit 66cfeb1f authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

Merge branch 'dev' into dev-searx-parser

parents 263c5db9 27737199
Pipeline #1822 canceled with stage
......@@ -62,7 +62,7 @@ let
repl = pkgs.writeShellScriptBin "repl" ''
#!/usr/bin/env bash
pulp repl
spago repl
'';
test-ps = pkgs.writeShellScriptBin "test-ps" ''
......
......@@ -70,7 +70,7 @@ annotatedFieldInner p = R.createElement annotatedFieldInnerCpt p []
annotatedFieldInnerCpt :: R.Component InnerProps
annotatedFieldInnerCpt = here.component "annotatedFieldInner" cpt where
cpt { menuRef, ngrams, redrawMenu, setTermList, text: fieldText } _ = do
redrawMenu' <- T.useLive T.unequal redrawMenu
_redrawMenu' <- T.useLive T.unequal redrawMenu
-- menu <- T.useBox (Nothing :: Maybe (Record AnnotationMenu))
......@@ -109,7 +109,7 @@ onAnnotationSelect { menuRef, ngrams, redrawMenu, setTermList } Nothing event =
, redrawMenu
, setTermList }
Nothing -> hideMenu { menuRef, redrawMenu }
onAnnotationSelect { menuRef, ngrams, redrawMenu, setTermList } (Just (Tuple ngram list)) event = do
onAnnotationSelect { menuRef, redrawMenu, setTermList } (Just (Tuple ngram list)) event = do
showMenu { event
, getList: const (Just list)
, menuRef
......
......@@ -7,7 +7,6 @@ import Data.Generic.Rep (class Generic)
import Data.Eq.Generic (genericEq)
import Data.Maybe (Maybe(..))
import Effect (Effect)
import Effect.Uncurried (mkEffectFn1)
import Reactix as R
import Reactix.DOM.HTML as HTML
import Toestand as T
......
module Gargantext.Components.Charts.Options.Series where
import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, encodeJson, (.:), (~>), (:=))
import Data.Argonaut.Core (jsonEmptyObject)
import Data.Array (foldl)
import Data.Generic.Rep (class Generic)
import Data.Maybe (Maybe(..), maybe)
import Data.Newtype (class Newtype)
import Data.Symbol (SProxy(..))
import Gargantext.Components.Charts.Options.Data (DataD1, DataD2)
import Gargantext.Components.Charts.Options.Data (DataD1, DataD2)
import Gargantext.Components.Charts.Options.Font (ItemStyle, Tooltip)
import Gargantext.Components.Charts.Options.Font (ItemStyle, Tooltip)
import Gargantext.Components.Charts.Options.Legend (SelectedMode)
import Gargantext.Prelude
import Gargantext.Types (class Optional)
import Prelude (class Eq, class Show, bind, map, pure, show, ($), (+), (<<<), (<>), eq)
import Prelude (class Eq, class Show, bind, map, pure, show, ($), (+), (<<<), (<>))
import Record as Record
import Record.Unsafe (unsafeSet)
import Simple.JSON as JSON
......
module Gargantext.Components.CodeEditor where
import DOM.Simple.Types (Element)
import Data.Argonaut.Parser (jsonParser)
import Data.Either (either, Either(..))
import Data.Generic.Rep (class Generic)
......@@ -9,6 +8,7 @@ import Data.Show.Generic (genericShow)
import Data.Maybe (Maybe(..))
import Data.Nullable (Nullable, null, toMaybe)
import Data.String.Utils (endsWith)
import DOM.Simple.Types (Element)
import Effect (Effect)
import FFI.Simple ((.=))
import Reactix as R
......@@ -355,7 +355,7 @@ initControls code defaultCodeType = do
}
reinitControls :: Record Controls -> Code -> CodeType -> Effect Unit
reinitControls c@{ codeType, codeS, error } code defaultCodeType = do
reinitControls { codeType, codeS, error } code defaultCodeType = do
T.write_ defaultCodeType codeType
T.write_ code codeS
T.write_ Nothing error
......@@ -65,7 +65,7 @@ contextMenuCpt = here.component "contextMenu" cpt
, style: position menu rect
, data: { placement: "right", toggle: "popover" }
}
elems ref menu Nothing = HTML.div
elems ref _menu Nothing = HTML.div
{ ref
, key: "context-menu"
, className: "context-menu"
......@@ -98,7 +98,7 @@ documentClickHandler onClose menu =
documentScrollHandler :: Effect Unit -> Callback DE.MouseEvent
documentScrollHandler onClose =
R2.named "hideMenuOnScroll" $ callback $ \e -> onClose
R2.named "hideMenuOnScroll" $ callback $ \_ -> onClose
position :: forall t. Record (Props t) -> DOMRect -> { left :: Number, top :: Number }
position mouse {width: menuWidth, height: menuHeight} = {left, top}
......
......@@ -193,13 +193,13 @@ searchBarCpt = here.component "searchBar" cpt
searchButton query queryText' =
H.button { className: "btn btn-primary"
, on: { click: \e -> T.write_ queryText' query }
, on: { click: \_ -> T.write_ queryText' query }
, type: "submit" }
[ H.span {className: "fa fa-search"} [] ]
clearButton query =
H.button { className: "btn btn-danger"
, on: { click: \e -> T.write_ "" query } }
, on: { click: \_ -> T.write_ "" query } }
[ H.span {className: "fa fa-times"} [] ]
mock :: Boolean
......@@ -273,7 +273,7 @@ pageLayoutCpt = here.component "pageLayout" cpt where
let path = { listId, mCorpusId, nodeId, params, query, tabType, yearFilter: yearFilter' }
handleResponse :: HashedResponse (TableResult Response) -> Tuple Int (Array DocumentsView)
handleResponse (HashedResponse { hash, value: res }) = ret
handleResponse (HashedResponse { value: res }) = ret
where
filterDocs' q ds = case cacheState' of
NT.CacheOff -> ds
......
......@@ -333,14 +333,14 @@ pageCpt = here.component "page" cpt
let isDeleted (DocumentsView {id}) = Set.member id deletions'.deleted
rows path' = case rowsLoaded of
rows = case rowsLoaded of
Docs {docs} -> docRow path' <$> Seq.filter (not <<< isDeleted) docs
Contacts {contacts} -> contactRow path' <$> contacts
pure $ T.table { colNames
, container
, params
, rows: rows path'
, rows
, syncResetButton : [ H.div {} [] ]
, totalRecords
, wrapColElts
......
......@@ -299,9 +299,9 @@ performAction = performAction' where
deleteNode' nt p@{ nodeId: id, parentId: parent_id, session } = do
case nt of
NodePublic FolderPublic -> void $ deleteNode session nt id
NodePublic FolderPublic -> void $ deleteNode session id
NodePublic _ -> void $ unpublishNode session (Just parent_id) id
_ -> void $ deleteNode session nt id
_ -> void $ deleteNode session id
refreshFolders p
doSearch task { boxes: { tasks }, nodeId: id } = liftEffect $ do
......
......@@ -229,13 +229,13 @@ refreshTree p@{ reloadTree } = liftEffect $ T2.reload reloadTree *> closePopover
deleteNode' nt p@{ boxes: { forestOpen }, session, tree: (NTree (LNode {id, parent_id}) _) } = do
case nt of
GT.NodePublic GT.FolderPublic -> void $ deleteNode session nt id
GT.NodePublic GT.FolderPublic -> void $ deleteNode session id
GT.NodePublic _ -> void $ unpublishNode session parent_id id
_ -> void $ deleteNode session nt id
_ -> void $ deleteNode session id
liftEffect $ T.modify_ (openNodesDelete (mkNodeId session id)) forestOpen
refreshTree p
doSearch task p@{ boxes: { tasks }, tree: NTree (LNode {id}) _ } = liftEffect $ do
doSearch task { boxes: { tasks }, tree: NTree (LNode {id}) _ } = liftEffect $ do
GAT.insert id task tasks
here.log2 "[doSearch] DoSearch task:" task
......@@ -250,7 +250,7 @@ renameNode name p@{ boxes: { errors }, session, tree: (NTree (LNode {id}) _) } =
handleRESTError errors eTask $ \_task -> pure unit
refreshTree p
shareTeam username p@{ boxes: { errors }, session, tree: (NTree (LNode {id}) _)} = do
shareTeam username { boxes: { errors }, session, tree: (NTree (LNode {id}) _)} = do
eTask <- Share.shareReq session id $ Share.ShareTeamParams { username }
handleRESTError errors eTask $ \_task -> pure unit
......@@ -261,7 +261,7 @@ sharePublic params p@{ boxes: { errors, forestOpen }, session } = traverse_ f pa
liftEffect $ T.modify_ (openNodesInsert (mkNodeId p.session out)) forestOpen
refreshTree p
addContact params p@{ boxes: { errors }, session, tree: (NTree (LNode {id}) _) } = do
addContact params { boxes: { errors }, session, tree: (NTree (LNode {id}) _) } = do
eTask <- Contact.contactReq session id params
handleRESTError errors eTask $ \_task -> pure unit
......
......@@ -113,7 +113,7 @@ nodeMainSpanCpt = here.component "nodeMainSpan" cpt
pure $ H.span (dropProps droppedFile droppedFile' isDragOver isDragOver')
$ reverseHanded handed'
[ folderIcon { folderOpen, nodeType } []
, chevronIcon { folderOpen, handed, isLeaf, nodeType } []
, chevronIcon { folderOpen, handed, isLeaf } []
, nodeLink { boxes
, folderOpen
, frontends
......@@ -201,14 +201,14 @@ nodeMainSpanCpt = here.component "nodeMainSpan" cpt
{ className: "leaf " <> (dropClass droppedFile' isDragOver')
, on: { dragLeave: onDragLeave isDragOver
, dragOver: onDragOverHandler isDragOver
, drop: dropHandler droppedFile }
, drop: dropHandler }
}
where
dropClass (Just _) _ = "file-dropped"
dropClass _ true = "file-dropped"
dropClass Nothing _ = ""
dropHandler droppedFile e = do
dropHandler e = do
-- prevent redirection when file is dropped
E.preventDefault e
E.stopPropagation e
......@@ -248,7 +248,6 @@ type ChevronIconProps = (
folderOpen :: T.Box Boolean
, handed :: T.Box GT.Handed
, isLeaf :: Boolean
, nodeType :: GT.NodeType
)
chevronIcon :: R2.Component ChevronIconProps
......@@ -256,9 +255,9 @@ chevronIcon = R.createElement chevronIconCpt
chevronIconCpt :: R.Component ChevronIconProps
chevronIconCpt = here.component "chevronIcon" cpt
where
cpt { folderOpen, handed, isLeaf: true, nodeType } _ = do
cpt { isLeaf: true } _ = do
pure $ H.div {} []
cpt { folderOpen, handed, isLeaf: false, nodeType } _ = do
cpt { folderOpen, handed, isLeaf: false } _ = do
handed' <- T.useLive T.unequal handed
open <- T.useLive T.unequal folderOpen
pure $ H.a { className: "chevron-icon"
......
......@@ -77,8 +77,6 @@ addNodeView = R.createElement addNodeViewCpt
addNodeViewCpt :: R.Component CreateNodeProps
addNodeViewCpt = here.component "addNodeView" cpt where
cpt { dispatch
, id
, name
, nodeTypes } _ = do
nodeName <- T.useBox "Name"
nodeName' <- T.useLive T.unequal nodeName
......
......@@ -23,8 +23,8 @@ here = R2.here "Gargantext.Components.Forest.Tree.Node.Action.Delete"
-- TODO Delete with asyncTaskWithType
deleteNode :: Session -> NodeType -> GT.ID -> Aff (Either RESTError GT.ID)
deleteNode session nt nodeId = delete session $ NodeAPI GT.Node (Just nodeId) ""
deleteNode :: Session -> GT.ID -> Aff (Either RESTError GT.ID)
deleteNode session nodeId = delete session $ NodeAPI GT.Node (Just nodeId) ""
{-
case nt of
......
......@@ -77,5 +77,5 @@ actionDownloadOther :: R2.Component ActionDownload
actionDownloadOther = R.createElement actionDownloadOtherCpt
actionDownloadOtherCpt :: R.Component ActionDownload
actionDownloadOtherCpt = here.component "actionDownloadOther" cpt where
cpt { id, session } _ = do
cpt _ _ = do
pure $ fragmentPT $ "Soon, you will be able to download your file here "
......@@ -6,10 +6,9 @@ import Data.Maybe (Maybe)
import Effect (Effect)
import Effect.Aff (Aff, launchAff)
import Gargantext.Components.App.Data (Boxes)
import Gargantext.Components.Forest.Tree.Node.Action.Types (Action(..))
import Gargantext.Components.Forest.Tree.Node.Action.Add (NodePopup)
import Gargantext.Components.Forest.Tree.Node.Action.Search.SearchBar (searchBar)
import Gargantext.Components.Forest.Tree.Node.Action.Search.SearchField (defaultSearch)
import Gargantext.Components.Forest.Tree.Node.Action.Types (Action(..))
import Gargantext.Components.Lang (allLangs)
import Gargantext.Sessions (Session)
import Gargantext.Types (ID)
......@@ -50,8 +49,8 @@ actionSearchCpt = here.component "actionSearch" cpt
]
where
searchOn :: (Action -> Aff Unit)
-> GT.AsyncTaskWithType
-> Effect Unit
-> GT.AsyncTaskWithType
-> Effect Unit
searchOn dispatch' task = do
_ <- launchAff $ dispatch' (DoSearch task)
-- close popup
......
......@@ -9,7 +9,6 @@ import Data.Show.Generic (genericShow)
import Data.Maybe (Maybe(..))
import Data.Nullable (Nullable)
import Data.Tuple (Tuple(..))
import Data.Tuple.Nested ((/\))
import Reactix as R
import Reactix.DOM.HTML as H
import Toestand as T
......@@ -44,7 +43,6 @@ type SearchIFramesProps = (
searchIframes :: R2.Component SearchIFramesProps
searchIframes = R.createElement searchIframesCpt
searchIframesCpt :: R.Component SearchIFramesProps
searchIframesCpt = here.component "searchIframes" cpt
where
......@@ -67,7 +65,6 @@ type IFrameProps = (
divIframe :: R2.Component IFrameProps
divIframe = R.createElement divIframeCpt
divIframeCpt :: R.Component IFrameProps
divIframeCpt = here.component "divIframe" cpt
where
......@@ -82,7 +79,6 @@ frameUrl Searx = "https://searx.frame.gargantext.org" -- 192.168.1.4:8080"
iframeWith :: R2.Component IFrameProps
iframeWith = R.createElement iframeWithCpt
iframeWithCpt :: R.Component IFrameProps
iframeWithCpt = here.component "iframeWith" cpt
where
......
......@@ -99,7 +99,6 @@ componentIMTCpt = here.component "componentIMT" cpt
componentCNRS :: R2.Component ComponentProps
componentCNRS = R.createElement componentCNRSCpt
componentCNRSCpt :: R.Component ComponentProps
componentCNRSCpt = here.component "componentCNRS" cpt
where
......@@ -234,15 +233,14 @@ langNavCpt = here.component "langNav" cpt
------------------------------------------------------------------------
type DataFieldNavProps =
( datafields :: Array DataField
, search :: T.Box Search )
( search :: T.Box Search )
dataFieldNav :: R2.Component DataFieldNavProps
dataFieldNav = R.createElement dataFieldNavCpt
dataFieldNavCpt :: R.Component DataFieldNavProps
dataFieldNavCpt = here.component "dataFieldNav" cpt
where
cpt { datafields, search } _ = do
cpt { search } _ = do
search'@{ datafield } <- T.useLive T.unequal search
pure $ R.fragment
......@@ -367,7 +365,7 @@ datafieldInputCpt = here.component "datafieldInput" cpt where
iframeRef <- R.useRef null
pure $ H.div {}
[ dataFieldNav { datafields: dataFields, search } []
[ dataFieldNav { search } []
, if isExternal search'.datafield
then databaseInput { databases, search } []
......
......@@ -236,7 +236,7 @@ fileTypeViewCpt = here.component "fileTypeView" cpt
case droppedFile' of
Nothing -> pure $ H.div {} []
Just df@(DroppedFile { blob, fileType }) ->
Just df@(DroppedFile _) ->
pure $ H.div tooltipProps [ H.div { className: "card"}
[ panelHeading
, panelBody df
......@@ -270,12 +270,12 @@ fileTypeViewCpt = here.component "fileTypeView" cpt
panelBody (DroppedFile { blob }) =
H.div {className: "card-body"}
[ R2.select {className: "col-md-12 form-control"
, on: {change: onChange blob}
, on: {change: onChange}
}
(map renderOption [CSV, CSV_HAL, WOS])
]
where
onChange blob e l =
onChange e l =
T.write_ (Just $ DroppedFile $ { blob
, fileType: read $ R.unsafeEventValue e
, lang : fromMaybe EN $ read $ R.unsafeEventValue l
......@@ -477,7 +477,7 @@ uploadTermButtonCpt = here.component "uploadTermButton" cpt
, on: { click: onClick mFile' uploadType' }
} [ H.text "Upload" ]
where
onClick mFile' uploadType' e = do
onClick mFile' uploadType' _ = do
let {name, blob} = unsafePartial $ fromJust mFile'
void $ launchAff do
contents <- readUFBAsText blob
......
......@@ -90,7 +90,7 @@ nodePopupCpt = here.component "nodePopupView" cpt where
, title : "Rename", on: { click: \_ -> T.write_ true isOpen } } []
panelBody :: T.Box (Maybe NodeAction) -> Record NodePopupProps -> R.Element
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.p { className: "spacer" } []
, H.div { className: "flex-center" }
......@@ -181,25 +181,25 @@ panelAction p = R.createElement panelActionCpt p []
panelActionCpt :: R.Component PanelActionProps
panelActionCpt = here.component "panelAction" cpt
where
cpt {action: Documentation nodeType} _ = pure $ actionDoc { nodeType } []
cpt {action: Download, id, nodeType, session} _ = pure $ actionDownload { id, nodeType, session } []
cpt {action: Upload, dispatch, id, nodeType, session} _ = pure $ actionUpload { dispatch, id, nodeType, session } []
cpt {action: Delete, nodeType, dispatch} _ = pure $ actionDelete { dispatch, nodeType } []
cpt {action: Add xs, dispatch, id, name, nodeType} _ =
cpt { action: Documentation nodeType} _ = pure $ actionDoc { nodeType } []
cpt { action: Download, id, nodeType, session} _ = pure $ actionDownload { id, nodeType, session } []
cpt { action: Upload, dispatch, id, nodeType, session} _ = pure $ actionUpload { dispatch, id, nodeType, session } []
cpt { action: Delete, nodeType, dispatch} _ = pure $ actionDelete { dispatch, nodeType } []
cpt { action: Add xs, dispatch, id, name, nodeType} _ =
pure $ addNodeView {dispatch, id, name, nodeType, nodeTypes: xs} []
cpt {action: Refresh , dispatch, nodeType} _ = pure $ update { dispatch, nodeType } []
cpt {action: Config, nodeType} _ =
cpt { action: Refresh , dispatch, nodeType } _ = pure $ update { dispatch, nodeType } []
cpt { action: Config, nodeType } _ =
pure $ fragmentPT $ "Config " <> show nodeType
-- Functions using SubTree
cpt { action: Merge {subTreeParams}, boxes, dispatch, id, nodeType, session } _ =
pure $ mergeNode { boxes, dispatch, id, nodeType, session, subTreeParams } []
cpt {action: Move {subTreeParams}, boxes, dispatch, id, nodeType, session } _ =
cpt { action: Move {subTreeParams}, boxes, dispatch, id, nodeType, session } _ =
pure $ moveNode { boxes, dispatch, id, nodeType, session, subTreeParams } []
cpt {action: Link {subTreeParams}, boxes, dispatch, id, nodeType, session } _ =
cpt { action: Link {subTreeParams}, boxes, dispatch, id, nodeType, session } _ =
pure $ linkNode { boxes, dispatch, id, nodeType, session, subTreeParams } []
cpt {action : Share, dispatch, id } _ = pure $ Share.shareNode { dispatch, id } []
cpt {action : AddingContact, dispatch, id } _ = pure $ Contact.actionAddContact { dispatch, id } []
cpt {action : Publish {subTreeParams}, boxes, dispatch, id, nodeType, session } _ =
cpt { action : Share, dispatch, id } _ = pure $ Share.shareNode { dispatch, id } []
cpt { action : AddingContact, dispatch, id } _ = pure $ Contact.actionAddContact { dispatch, id } []
cpt { action : Publish {subTreeParams}, boxes, dispatch, id, nodeType, session } _ =
pure $ Share.publishNode { boxes, dispatch, id, nodeType, session, subTreeParams } []
cpt { action: SearchBox, boxes, dispatch, id, session } _ =
pure $ actionSearch { boxes, dispatch, id: (Just id), session } []
......
module Gargantext.Components.Forest.Tree.Node.Settings where
import Data.Generic.Rep (class Generic)
import Data.Show.Generic (genericShow)
import Data.Eq.Generic (genericEq)
import Gargantext.Prelude (class Eq, class Show, show, (&&), (<>), (==))
import Gargantext.Components.Forest.Tree.Node.Tools.SubTree.Types (SubTreeParams(..))
import Data.Array (foldl)
import Gargantext.Types
------------------------------------------------------------------------
......@@ -55,15 +51,15 @@ instance Show NodeAction where
show Download = "Download"
show Upload = "Upload"
show Refresh = "Refresh"
show (Move t) = "Move with subtree params" -- <> show t
show (Move _) = "Move with subtree params" -- <> show t
show Clone = "Clone"
show Delete = "Delete"
show Share = "Share"
show Config = "Config"
show (Link x) = "Link to " -- <> show x
show (Add xs) = "Add Child" -- foldl (\a b -> a <> show b) "Add " xs
show (Merge t) = "Merge with subtree" -- <> show t
show (Publish x) = "Publish" -- <> show x
show (Link _) = "Link to " -- <> show x
show (Add _) = "Add Child" -- foldl (\a b -> a <> show b) "Add " xs
show (Merge _) = "Merge with subtree" -- <> show t
show (Publish _) = "Publish" -- <> show x
show AddingContact = "AddingContact"
show CloseNodePopover = "CloseNodePopover"
......
......@@ -223,11 +223,10 @@ type CheckboxesListGroup a =
checkboxesListGroup :: forall a. Ord a => Show a => R2.Component (CheckboxesListGroup a)
checkboxesListGroup = R.createElement checkboxesListGroupCpt
checkboxesListGroupCpt :: forall a. Ord a => Show a => R.Component (CheckboxesListGroup a)
checkboxesListGroupCpt = here.component "checkboxesListGroup" cpt
where
cpt { groups, options } _ = do
cpt { options } _ = do
options' <- T.useLive T.unequal options
let one a =
......@@ -278,7 +277,6 @@ nodeLinkCpt = here.component "nodeLink" cpt
, nodeType
, session
} _ = do
pure $
H.div { className: "node-link"
, on: { click } }
......
module Gargantext.Components.Forest.Tree.Node.Tools.FTree where
import Data.Array as A
import Data.Generic.Rep (class Generic)
import Data.Eq.Generic (genericEq)
import Data.Maybe (Maybe(..))
import Data.Newtype (class Newtype)
import Foreign as F
import Simple.JSON as JSON
import Simple.JSON.Generics as JSONG
import Gargantext.Prelude
......
......@@ -84,7 +84,6 @@ type NodeActionsNodeListProps =
nodeActionsNodeList :: Record NodeActionsNodeListProps -> R.Element
nodeActionsNodeList p = R.createElement nodeActionsNodeListCpt p []
nodeActionsNodeListCpt :: R.Component NodeActionsNodeListProps
nodeActionsNodeListCpt = here.component "nodeActionsNodeList" cpt
where
......@@ -106,7 +105,7 @@ nodeListUpdateButton p = R.createElement nodeListUpdateButtonCpt p []
nodeListUpdateButtonCpt :: R.Component NodeListUpdateButtonProps
nodeListUpdateButtonCpt = here.component "nodeListUpdateButton" cpt
where
cpt { listId, nodeId, nodeType, session, refresh } _ = do
cpt _ _ = do
-- enabled <- T.useBox true
pure $ H.div {} [] {- { className: "update-button "
......
......@@ -260,7 +260,7 @@ updateTermButtonCpt = here.component "updateTermButton" cpt
, rType
, session
, text } _ = do
{ removedNodeIds, sideTab, selectedNodeIds } <- GEST.focusedSidePanel sidePanelGraph
{ removedNodeIds, selectedNodeIds } <- GEST.focusedSidePanel sidePanelGraph
selectedNodeIds' <- T.useLive T.unequal selectedNodeIds
pure $ if Set.isEmpty selectedNodeIds' then
......
......@@ -25,8 +25,7 @@ topBar :: R2.Leaf TopBar
topBar p = R.createElement topBarCpt p []
topBarCpt :: R.Component TopBar
topBarCpt = here.component "topBar" cpt where
cpt { boxes: { showTree
, sidePanelGraph
cpt { boxes: { sidePanelGraph
, sidePanelState } } _ = do
{ mGraph, multiSelectEnabled, selectedNodeIds, showControls } <- GEST.focusedSidePanel sidePanelGraph
......@@ -43,7 +42,3 @@ topBarCpt = here.component "topBar" cpt where
, Toggle.sidebarToggleButton { state: sidePanelState } []
, search
]
where
rowToggle = RH.ul { className: "navbar-nav ml-auto mr-auto" }
col = RH.li { className: "nav-item" }
spaces = RH.a { className: "nav-link" }
......@@ -72,7 +72,7 @@ chooserCpt = here.component "chooser" cpt where
-- Shown in the chooser
activeConnections :: forall s. T.ReadWrite s Sessions => s -> Sessions -> Array R.Element
activeConnections sessions sessions' | Sessions.null sessions' = []
activeConnections _ sessions' | Sessions.null sessions' = []
activeConnections sessions sessions' =
[ H.h3 {} [ H.text "Active connection(s)" ]
, H.ul {} [ renderSessions sessions sessions' ] ]
......
......@@ -55,7 +55,7 @@ form props = R.createElement formCpt props []
formCpt :: forall s v. T.ReadWrite s Sessions => T.ReadWrite v Boolean
=> R.Component (Props s v)
formCpt = here.component "form" cpt where
cpt props@{ backend, sessions, visible } _ = do
cpt { backend, sessions, visible } _ = do
cell <- T.useBox emptyForm
cursors <- useFocusedFields cell {}
pure $ R2.row
......
......@@ -80,7 +80,7 @@ setTermListSetA ngramsTable ns new_list =
CoreAction $ CommitPatch $ fromNgramsPatches $ PatchMap $ mapWithIndex f $ toMap ns
where
f :: NgramsTerm -> Unit -> NgramsPatch
f n unit = NgramsPatch { patch_list, patch_children: mempty }
f n _unit = NgramsPatch { patch_list, patch_children: mempty }
where
cur_list = ngramsTable ^? at n <<< _Just <<< _NgramsRepoElement <<< _list
patch_list = maybe mempty (\c -> replace c new_list) cur_list
......@@ -379,14 +379,14 @@ loadedNgramsTableBodyCpt = here.component "loadedNgramsTableBody" cpt where
, performAction: performAction <<< CoreAction }
-- autoUpdate :: Array R.Element
-- autoUpdate path' = if withAutoUpdate then
-- [ R2.buff
-- $ autoUpdateElt
-- { duration: 5000
-- , effect: performAction $ CoreAction $ Synchronize { afterSync: afterSync' }
-- }
-- ]
-- else []
-- autoUpdate = if withAutoUpdate then
-- [ R2.buff
-- $ autoUpdateElt
-- { duration: 5000
-- , effect: performAction $ CoreAction $ Synchronize { afterSync: afterSync' }
-- }
-- ]
-- else []
ngramsParentRoot :: Maybe NgramsTerm
ngramsParentRoot =
......
......@@ -503,7 +503,7 @@ highlightNgrams ntype table@(NgramsTable {ngrams_repo_elements: elts}) input0 =
A.fromFoldable ((\(s /\ ls)-> undb s /\ ls) <$> unsafePartial (foldl goFold ((input /\ Nil) : Nil) ixs))
where
spR x = " " <> R.replace wordBoundaryReg "$1$1" x <> " "
reR = R.replace wordBoundaryReg " "
-- reR = R.replace wordBoundaryReg " "
db = S.replaceAll (S.Pattern " ") (S.Replacement " ")
sp x = " " <> db x <> " "
undb = R.replace wordBoundaryReg2 "$1"
......@@ -911,7 +911,6 @@ syncPatches :: forall p s. CoreParams p -> T.Box (CoreState s) -> (Unit -> Aff U
syncPatches props state callback = do
{ ngramsLocalPatch: ngramsLocalPatch@{ ngramsPatches }
, ngramsStagePatch
, ngramsValidPatch
, ngramsVersion } <- T.read state
when (isEmptyNgramsTablePatch ngramsStagePatch) $ do
let pt = Versioned { data: ngramsPatches, version: ngramsVersion }
......@@ -970,8 +969,10 @@ commitPatch tablePatch state = do
loadNgramsTable :: PageParams -> Aff (Either RESTError VersionedNgramsTable)
loadNgramsTable
{ nodeId, listIds, termListFilter, termSizeFilter, session, scoreType
, searchQuery, tabType, params: {offset, limit, orderBy}}
{ nodeId
, listIds
, session
, tabType }
= get session query
where
query = GetNgramsTableAll { listIds
......@@ -988,7 +989,7 @@ loadNgramsTable
type NgramsListByTabType = Map TabType VersionedNgramsTable
loadNgramsTableAll :: PageParams -> Aff (Either RESTError NgramsListByTabType)
loadNgramsTableAll { nodeId, listIds, session, scoreType } = do
loadNgramsTableAll { nodeId, listIds, session } = do
let
cTagNgramTypes =
[ CTabTerms
......
......@@ -109,7 +109,7 @@ fieldsCodeEditor = R.createElement fieldsCodeEditorCpt
fieldsCodeEditorCpt :: R.Component FieldsCodeEditorProps
fieldsCodeEditorCpt = here.component "fieldsCodeEditorCpt" cpt
where
cpt { fields, nodeId, session } _ = do
cpt { fields } _ = do
(FTFieldsWithIndex fields') <- T.useLive T.unequal fields
masterKey <- T.useBox T2.newReload
masterKey' <- T.useLive T.unequal masterKey
......@@ -175,7 +175,6 @@ type FieldCodeEditorProps =
fieldCodeEditorWrapper :: Record FieldCodeEditorProps -> R.Element
fieldCodeEditorWrapper props = R.createElement fieldCodeEditorWrapperCpt props []
fieldCodeEditorWrapperCpt :: R.Component FieldCodeEditorProps
fieldCodeEditorWrapperCpt = here.component "fieldCodeEditorWrapperCpt" cpt
where
......@@ -230,7 +229,6 @@ type RenameableProps =
renameable :: Record RenameableProps -> R.Element
renameable props = R.createElement renameableCpt props []
renameableCpt :: R.Component RenameableProps
renameableCpt = here.component "renameableCpt" cpt
where
......@@ -326,29 +324,29 @@ fieldCodeEditorCpt = here.component "fieldCodeEditorCpt" cpt
-- CE.Code is the editor code (might have been the cause of the trigger)
changeCode :: (FieldType -> Effect Unit) -> FieldType -> CE.CodeType -> CE.Code -> Effect Unit
changeCode onc (Haskell hs) CE.Haskell c = onc $ Haskell $ hs { haskell = c }
changeCode onc (Haskell hs) CE.Python c = onc $ Python $ defaultPython' { python = c }
changeCode onc (Haskell {haskell}) CE.JSON c = onc $ JSON $ defaultJSON' { desc = haskell }
changeCode onc (Haskell {haskell}) CE.Markdown c = onc $ Markdown $ defaultMarkdown' { text = haskell }
changeCode onc (Haskell _) CE.Python c = onc $ Python $ defaultPython' { python = c }
changeCode onc (Haskell {haskell}) CE.JSON _ = onc $ JSON $ defaultJSON' { desc = haskell }
changeCode onc (Haskell {haskell}) CE.Markdown _ = onc $ Markdown $ defaultMarkdown' { text = haskell }
changeCode onc (Python hs) CE.Python c = onc $ Python $ hs { python = c }
changeCode onc (Python hs) CE.Haskell c = onc $ Haskell $ defaultHaskell' { haskell = c }
changeCode onc (Python {python}) CE.JSON c = onc $ JSON $ defaultJSON' { desc = python }
changeCode onc (Python {python}) CE.Markdown c = onc $ Markdown $ defaultMarkdown' { text = python }
changeCode onc (Python _) CE.Haskell c = onc $ Haskell $ defaultHaskell' { haskell = c }
changeCode onc (Python {python}) CE.JSON _ = onc $ JSON $ defaultJSON' { desc = python }
changeCode onc (Python {python}) CE.Markdown _ = onc $ Markdown $ defaultMarkdown' { text = python }
changeCode onc (Markdown md) CE.Haskell c = onc $ Haskell $ defaultHaskell' { haskell = c }
changeCode onc (Markdown md) CE.Python c = onc $ Python $ defaultPython' { python = c }
changeCode onc (Markdown md) CE.JSON c = onc $ Markdown $ defaultMarkdown' { text = c }
changeCode onc (Markdown _) CE.Haskell c = onc $ Haskell $ defaultHaskell' { haskell = c }
changeCode onc (Markdown _) CE.Python c = onc $ Python $ defaultPython' { python = c }
changeCode onc (Markdown _) CE.JSON c = onc $ Markdown $ defaultMarkdown' { text = c }
changeCode onc (Markdown md) CE.Markdown c = onc $ Markdown $ md { text = c }
changeCode onc (JSON j@{desc}) CE.Haskell c = onc $ Haskell $ defaultHaskell' { haskell = haskell }
changeCode onc (JSON j) CE.Haskell _ = onc $ Haskell $ defaultHaskell' { haskell = haskell }
where
haskell = R2.stringify (JSON.writeImpl j) 2
changeCode onc (JSON j@{desc}) CE.Python c = onc $ Python $ defaultPython' { python = toCode }
changeCode onc (JSON j) CE.Python _ = onc $ Python $ defaultPython' { python = toCode }
where
toCode = R2.stringify (JSON.writeImpl j) 2
changeCode onc _ CE.JSON c = do
case JSON.readJSON c of
Left err -> here.log2 "[fieldCodeEditor'] cannot parse json" c
Left err -> here.log2 "[fieldCodeEditor'] cannot parse json" c -- TODO Refactor?
Right j' -> onc $ JSON j'
-- case jsonParser c of
-- Left err -> here.log2 "[fieldCodeEditor'] cannot parse json" c
......@@ -455,7 +453,7 @@ type LoadWithReloadProps =
-- Just to make reloading effective
loadCorpusWithChildAndReload :: Record LoadWithReloadProps -> Aff (Either RESTError CorpusData)
loadCorpusWithChildAndReload {nodeId, reload, session} = loadCorpusWithChild {nodeId, session}
loadCorpusWithChildAndReload {nodeId, session} = loadCorpusWithChild {nodeId, session}
data ViewType = Code | Folders
derive instance Generic ViewType _
......
module Gargantext.Components.Nodes.Corpus.Chart.Tree where
import Data.Either (Either(..))
import Data.Either (Either)
import Data.Generic.Rep (class Generic)
import Data.Maybe (Maybe(..))
import Data.Newtype (class Newtype)
......
......@@ -7,9 +7,8 @@ import Gargantext.Components.App.Data (Boxes)
import Gargantext.Components.Charts.Options.Type (EChartsInstance, MouseEvent)
import Gargantext.Prelude (Unit)
import Gargantext.Sessions (Session)
import Gargantext.Types (FrontendError, TabType)
import Gargantext.Types (TabType)
import Gargantext.Utils.Toestand as T2
import Toestand as T
type Path = (
corpusId :: Int
......
......@@ -5,8 +5,6 @@ import Gargantext.Prelude
-- import Gargantext.Utils.Toestand as T2
-- import Toestand as T
import Data.Tuple.Nested ((/\))
import Effect (Effect)
import Gargantext.Sessions (Session)
import Gargantext.Types (NodeID)
import Gargantext.Utils.Reactix as R2
......@@ -20,7 +18,6 @@ type Props = ( nodeId :: NodeID, session :: Session )
phyloLayout :: R2.Component Props
phyloLayout = R.createElement phyloLayoutCpt
phyloLayoutCpt :: R.Component Props
phyloLayoutCpt = here.component "phyloLayout" cpt where
cpt { nodeId, session } content = do
......
module Gargantext.Components.Nodes.Corpus.Types where
import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, (.:), (:=), (~>), jsonEmptyObject)
import Data.Eq.Generic (genericEq)
import Data.Generic.Rep (class Generic)
import Data.List as List
import Data.Maybe (Maybe(..))
import Data.Newtype (class Newtype)
import Gargantext.Components.Node (NodePoly)
import Gargantext.Components.Nodes.Types (FTField, Field(..), FieldType(..), FTField, FTFieldList(..), isJSON)
import Gargantext.Components.Nodes.Types (Field(..), FieldType(..), FTFieldList(..), isJSON)
import Gargantext.Prelude
import Reactix as R
import Record as Record
import Simple.JSON as JSON
import Toestand as T
newtype Hyperdata =
Hyperdata { fields :: FTFieldList }
......
module Gargantext.Components.Nodes.File where
import Data.Generic.Rep (class Generic)
import Data.Either (Either(..))
import Data.Either (Either)
import Data.Eq.Generic (genericEq)
import Data.Maybe (Maybe(..))
import Data.Newtype (class Newtype)
......
module Gargantext.Components.Nodes.Lists.Tabs where
import Gargantext.Components.Nodes.Lists.Types
import Data.Array as A
import Data.Maybe (Maybe(..), fromMaybe)
import Data.Tuple.Nested ((/\))
......@@ -14,6 +12,7 @@ import Gargantext.Components.Nodes.Corpus.Chart.Pie (pie, bar)
import Gargantext.Components.Nodes.Corpus.Chart.Tree (tree)
import Gargantext.Components.Nodes.Corpus.Chart.Utils (mNgramsTypeFromTabType)
import Gargantext.Components.Nodes.Corpus.Types (CorpusData)
import Gargantext.Components.Nodes.Lists.Types hiding (here)
import Gargantext.Components.Tab as Tab
import Gargantext.Prelude (bind, pure, unit, ($), (<>))
import Gargantext.Sessions (Session)
......@@ -70,7 +69,7 @@ ngramsViewCpt = here.component "ngramsView" cpt where
chartsReload <- T.useBox T2.newReload
path <- T.useBox $ NTC.initialPageParams props.session initialPath.corpusId [initialPath.listId] initialPath.tabType
{ listIds, nodeId, params, tabType } <- T.useLive T.unequal path
{ listIds, nodeId, params } <- T.useLive T.unequal path
let path' = {
corpusId: nodeId
, limit: params.limit
......@@ -101,7 +100,7 @@ ngramsViewCpt = here.component "ngramsView" cpt where
where
afterSync chartsReload _ = do
case mNgramsType of
Just ngramsType -> do
Just _ -> do
-- NOTE: No need to recompute chart, after ngrams are sync this
-- should be recomputed already
-- We just refresh it
......@@ -119,7 +118,7 @@ ngramsViewCpt = here.component "ngramsView" cpt where
, tabType
}
charts params CTabTerms = [
charts _params CTabTerms = [
{-
H.div {className: "row"}
[ H.div {className: "col-12 d-flex justify-content-center"}
......
......@@ -381,10 +381,10 @@ type SidePanelProps = (
, sidePanel :: T.Box (Maybe (Record TT.SidePanel))
)
sidePanel :: R2.Component SidePanelProps
sidePanel = R.createElement sidePanelCpt
sidePanelCpt :: R.Component SidePanelProps
sidePanelCpt = here.component "sidePanel" cpt
textsSidePanel :: R2.Component SidePanelProps
textsSidePanel = R.createElement textsSidePanelCpt
textsSidePanelCpt :: R.Component SidePanelProps
textsSidePanelCpt = here.component "sidePanel" cpt
where
cpt { boxes: { sidePanelState }
, session
......@@ -465,7 +465,6 @@ type SidePanelDocView = (
sidePanelDocView :: R2.Component SidePanelDocView
sidePanelDocView = R.createElement sidePanelDocViewCpt
sidePanelDocViewCpt :: R.Component SidePanelDocView
sidePanelDocViewCpt = here.component "sidePanelDocView" cpt
where
......
......@@ -2,7 +2,6 @@ module Gargantext.Components.Nodes.Texts.SidePanelToggleButton
( Props, sidePanelToggleButton
) where
import Data.Tuple.Nested ((/\))
import Prelude
import Reactix as R
import Reactix.DOM.HTML as H
......
module Gargantext.Components.Renameable where
import Data.Tuple (Tuple(..), fst, snd)
import Data.Tuple.Nested ((/\))
import Effect (Effect)
import Reactix as R
import Reactix.DOM.HTML as H
......@@ -24,7 +22,6 @@ type RenameableProps =
renameable :: R2.Component RenameableProps
renameable = R.createElement renameableCpt
renameableCpt :: R.Component RenameableProps
renameableCpt = here.component "renameableCpt" cpt
where
......@@ -54,11 +51,10 @@ type RenameableTextProps =
renameableText :: R2.Component RenameableTextProps
renameableText = R.createElement renameableTextCpt
renameableTextCpt :: R.Component RenameableTextProps
renameableTextCpt = here.component "renameableText" cpt
where
cpt props@{ isEditing, state } _ = do
cpt props@{ isEditing } _ = do
isEditing' <- T.useLive T.unequal isEditing
pure $ if isEditing' then
......@@ -69,11 +65,10 @@ renameableTextCpt = here.component "renameableText" cpt
notEditing :: R2.Component RenameableTextProps
notEditing = R.createElement notEditingCpt
notEditingCpt :: R.Component RenameableTextProps
notEditingCpt = here.component "notEditing" cpt
where
cpt props@{ isEditing, state } _ = do
cpt { isEditing, state } _ = do
state' <- T.useLive T.unequal state
pure $ H.div { className: "input-group" }
......@@ -90,11 +85,10 @@ notEditingCpt = here.component "notEditing" cpt
editing :: R2.Component RenameableTextProps
editing = R.createElement editingCpt
editingCpt :: R.Component RenameableTextProps
editingCpt = here.component "editing" cpt
where
cpt props@{ isEditing, onRename, state } _ = do
cpt { isEditing, onRename, state } _ = do
state' <- T.useLive T.unequal state
pure $ H.div { className: "input-group" }
......
......@@ -330,9 +330,9 @@ openedSidePanelCpt = here.component "openedSidePanel" cpt where
} [] ]
GR.Texts _s _n -> do
pure $ wrapper
[ Texts.sidePanel { boxes
, session
, sidePanel: sidePanelTexts } [] ]
[ Texts.textsSidePanel { boxes
, session
, sidePanel: sidePanelTexts } [] ]
_ -> pure $ wrapper []
annuaire :: R2.Component SessionNodeProps
......
......@@ -163,7 +163,7 @@ menuButton = R.createElement menuButtonCpt
menuButtonCpt :: R.Component MenuButtonProps
menuButtonCpt = here.component "menuButton" cpt
where
cpt { element: LiNav { title, href, icon, text }, show } _ = do
cpt { element: LiNav { icon, text, title }, show } _ = do
pure $ H.a { className: "dropdown-toggle navbar-text"
-- , data: {toggle: "dropdown"}
, title
......
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