Commit 1a4bb5dc authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[tree] initial work on copying corpus from list

parent 05e18035
......@@ -211,4 +211,8 @@ a:focus, a:hover {
cursor: pointer;
}
.copy-from-corpus .tree .node {
padding-left: 10px;
}
/*# sourceMappingURL=Login.css.map */
......@@ -197,3 +197,8 @@ li
a:focus, a:hover
cursor: pointer
.copy-from-corpus
.tree
.node
padding-left: 10px
module Gargantext.Components.Forest.Tree.Node.Action.Upload where
import Prelude (class Show, Unit, bind, const, discard, map, pure, show, void, ($))
import Data.Maybe (Maybe(..), fromJust)
import Data.Newtype (class Newtype)
import Data.Tuple (Tuple(..))
import Data.Tuple (Tuple(..), fst, snd)
import Data.Tuple.Nested ((/\))
import DOM.Simple.Console (log2)
import Effect.Aff (Aff, launchAff)
import Effect.Class (liftEffect)
import Effect (Effect)
......@@ -15,10 +15,13 @@ import Reactix.DOM.HTML as H
import URI.Extra.QueryPairs as QP
import Web.File.FileReader.Aff (readAsText)
import Gargantext.Prelude
import Gargantext.Components.Data.Lang (readLang, Lang(..))
import Gargantext.Components.Forest.Tree.Node.Action
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Routes as GR
import Gargantext.Sessions (Session, postWwwUrlencoded)
import Gargantext.Sessions (Session(..), postWwwUrlencoded, get)
import Gargantext.Types as GT
import Gargantext.Utils (id)
import Gargantext.Utils.Reactix as R2
......@@ -43,9 +46,7 @@ uploadFileViewCpt = R.hooksComponent "G.C.F.T.N.A.U.UploadFileView" cpt
lang :: R.State (Maybe Lang) <- R.useState' (Just EN)
pure $ H.div {} [
H.div {} [ H.text "Upload file!" ]
, H.div {} [ H.input { type: "file"
H.div {} [ H.input { type: "file"
, placeholder: "Choose file"
, on: {change: onChangeContents mContents}
}
......@@ -250,9 +251,7 @@ uploadTermListViewCpt = R.hooksComponent "G.C.F.T.N.A.U.UploadTermListView" cpt
mContents :: R.State (Maybe UploadFileContents) <- R.useState' Nothing
pure $ H.div {} [
H.div {} [ H.text "Upload file!" ]
, H.div {} [ H.input { type: "file"
H.div {} [ H.input { type: "file"
, placeholder: "Choose file"
, on: {change: onChangeContents mContents}
}
......@@ -271,19 +270,6 @@ uploadTermListViewCpt = R.hooksComponent "G.C.F.T.N.A.U.UploadTermListView" cpt
liftEffect $ do
setMContents $ const $ Just $ UploadFileContents contents
onChangeFileType (fileType /\ setFileType) e = do
setFileType $ const
$ unsafePartial
$ fromJust
$ readFileType
$ R2.unsafeEventValue e
onChangeLang (lang /\ setLang) e = do
setLang $ const
$ unsafePartial
$ readLang
$ R2.unsafeEventValue e
type UploadTermButtonProps =
(
......@@ -312,3 +298,96 @@ uploadTermButtonCpt = R.hooksComponent "G.C.F.T.N.A.U.uploadTermButton" cpt
_ <- dispatch $ UploadFile nodeType CSV contents
liftEffect $ do
setMContents $ const $ Nothing
copyFromCorpusView :: Record Props -> R.Element
copyFromCorpusView props = R.createElement copyFromCorpusViewCpt props []
copyFromCorpusViewCpt :: R.Component Props
copyFromCorpusViewCpt = R.hooksComponent "G.C.F.T.N.A.U.copyFromCorpusView" cpt
where
cpt {dispatch, id, nodeType, session} _ = do
useLoader session loadCorporaTree $
\tree ->
copyFromCorpusViewLoaded {dispatch, id, nodeType, session, tree}
type CorpusTreeProps =
(
tree :: FTree
| Props
)
copyFromCorpusViewLoaded :: Record CorpusTreeProps -> R.Element
copyFromCorpusViewLoaded props = R.createElement copyFromCorpusViewLoadedCpt props []
copyFromCorpusViewLoadedCpt :: R.Component CorpusTreeProps
copyFromCorpusViewLoadedCpt = R.hooksComponent "G.C.F.T.N.A.U.copyFromCorpusViewLoadedCpt" cpt
where
cpt p@{dispatch, id, nodeType, session, tree} _ = do
mCorpusId :: R.State (Maybe ID) <- R.useState' Nothing
pure $ H.div { className: "copy-from-corpus" } [
H.div { className: "tree" } [copyFromCorpusTreeView p]
, H.div {} [ copyFromCorpusButton { dispatch, id, mCorpusId, nodeType, session } ]
]
-- onChangeContents :: forall e. R.State (Maybe ID) -> E.SyntheticEvent_ e -> Effect Unit
-- onChangeContents (mCorpusId /\ setMCorpusId) e = do
-- E.preventDefault e
-- E.stopPropagation e
-- setMCorpusId $ const $ Just 1
copyFromCorpusTreeView :: Record CorpusTreeProps -> R.Element
copyFromCorpusTreeView props = R.createElement copyFromCorpusTreeViewCpt props []
copyFromCorpusTreeViewCpt :: R.Component CorpusTreeProps
copyFromCorpusTreeViewCpt = R.hooksComponent "G.C.F.T.N.A.U.copyFromCorpusTreeViewCpt" cpt
where
cpt p@{tree: NTree (LNode { name }) ary} _ = do
pure $ H.div { className: "node" } ([
H.span {} [ H.text name ]
] <> children)
where
children = map (\c -> copyFromCorpusTreeView (p { tree = c })) ary
type CopyFromCorpusButtonProps =
(
dispatch :: Action -> Aff Unit
, id :: Int
, mCorpusId :: R.State (Maybe Int)
, nodeType :: GT.NodeType
, session :: Session
)
copyFromCorpusButton :: Record CopyFromCorpusButtonProps -> R.Element
copyFromCorpusButton props = R.createElement copyFromCorpusButtonCpt props []
copyFromCorpusButtonCpt :: R.Component CopyFromCorpusButtonProps
copyFromCorpusButtonCpt = R.hooksComponent "G.C.F.T.N.A.U.copyFromCorpusButton" cpt
where
cpt {dispatch, id, mCorpusId: (mCorpusId /\ setMCorpusId), nodeType, session} _ = do
R.useEffect' $ do
log2 "[copyFromCorpusButton] session" session
pure $ H.button {className: "btn btn-primary", disabled, on: {click: onClick}} [ H.text "Copy" ]
where
disabled = case mCorpusId of
Nothing -> "1"
Just _ -> ""
onClick :: forall e. e -> Effect Unit
onClick e = do
pure unit
-- let corpusId = unsafePartial $ fromJust mCorpusId
-- void $ launchAff do
-- _ <- dispatch $ UploadFile nodeType CSV contents
-- liftEffect $ do
-- setMContents $ const $ Nothing
loadCorporaTree :: Session -> Aff FTree
loadCorporaTree session = getCorporaTree session treeId
where
Session { treeId } = session
getCorporaTree :: Session -> Int -> Aff FTree
getCorporaTree session treeId = get session $ GR.NodeAPI GT.Tree (Just treeId) "?type=NodeList&type=NodeCorpus"
......@@ -22,7 +22,7 @@ import Gargantext.Components.Forest.Tree.Node (NodeAction(..), SettingsBox(..),
import Gargantext.Components.Forest.Tree.Node.Action (Action(..), DroppedFile(..), FileType(..), ID, Name, UploadFileContents(..))
import Gargantext.Components.Forest.Tree.Node.Action.Add (NodePopup(..), createNodeView)
import Gargantext.Components.Forest.Tree.Node.Action.Rename (renameBox)
import Gargantext.Components.Forest.Tree.Node.Action.Upload (uploadFileView, fileTypeView, uploadTermListView)
import Gargantext.Components.Forest.Tree.Node.Action.Upload (uploadFileView, fileTypeView, uploadTermListView, copyFromCorpusView)
import Gargantext.Components.Forest.Tree.Node.ProgressBar (asyncProgressBar)
import Gargantext.Components.Data.Lang (allLangs, Lang(EN))
import Gargantext.Components.Search.SearchBar (searchBar)
......@@ -434,6 +434,8 @@ panelActionCpt = R.hooksComponent "G.C.F.T.N.B.panelAction" cpt
]
cpt {action: Add xs, dispatch: d, id, name, nodePopupState: p, nodeType} _ = do
pure $ createNodeView d {id, name, nodeType} p xs
cpt {action: CopyFromCorpus, dispatch, id, nodeType, session} _ = do
pure $ copyFromCorpusView {dispatch, id, nodeType, session}
cpt _ _ = do
pure $ H.div {} []
......
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