Commit 773c9d8b authored by Alexandre Delanoë's avatar Alexandre Delanoë

[FEAT][FOREST] Refactoring, mv path of files/modules.

parent 3b3ca047
......@@ -14,12 +14,12 @@ import Effect.Aff (Aff, launchAff, runAff)
import Effect.Class (liftEffect)
import Effect.Uncurried (mkEffectFn1)
import FFI.Simple ((..))
import Gargantext.Components.Forest.Action
import Gargantext.Components.Forest.Action.Add
import Gargantext.Components.Forest.Action.Rename
import Gargantext.Components.Forest.Action.Upload
import Gargantext.Components.Forest.NodeActions
import Gargantext.Components.Forest.Tree.HTML
import Gargantext.Components.Forest.Tree.Node.Action
import Gargantext.Components.Forest.Tree.Node.Action.Add
import Gargantext.Components.Forest.Tree.Node.Action.Rename
import Gargantext.Components.Forest.Tree.Node.Action.Upload
import Gargantext.Components.Forest.Tree.Node
import Gargantext.Components.Forest.Tree.Node.Box
import Gargantext.Ends (Frontends)
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Routes (AppRoute)
......
module Gargantext.Components.Forest.NodeActions where
module Gargantext.Components.Forest.Tree.Node where
import Prelude
import Gargantext.Types
......
module Gargantext.Components.Forest.Action where
module Gargantext.Components.Forest.Tree.Node.Action where
import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, jsonEmptyObject, (.:), (:=), (~>))
import Data.Generic.Rep (class Generic)
......
module Gargantext.Components.Forest.Action.Add where
module Gargantext.Components.Forest.Tree.Node.Action.Add where
import DOM.Simple.Console (log2)
import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, jsonEmptyObject, (.:), (:=), (~>))
import Data.Array (filter, null)
import Data.Array (filter, null, length, head)
import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Eq (genericEq)
import Data.Generic.Rep.Show (genericShow)
import Data.Maybe (Maybe(..), fromJust)
import Data.Maybe (Maybe(..), fromJust, fromMaybe)
import Data.Newtype (class Newtype)
import Data.Tuple (Tuple)
import Data.Tuple.Nested ((/\))
......@@ -14,8 +14,8 @@ import Effect.Aff (Aff, launchAff, runAff)
import Effect.Class (liftEffect)
import Effect.Uncurried (mkEffectFn1)
import FFI.Simple ((..))
import Gargantext.Components.Forest.Action
import Gargantext.Components.Forest.NodeActions
import Gargantext.Components.Forest.Tree.Node.Action
import Gargantext.Components.Forest.Tree.Node
import Gargantext.Ends (Frontends, url)
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Routes (AppRoute, SessionRoute(..))
......@@ -54,7 +54,7 @@ createNodeView d p@{nodeType} (Just CreatePopup /\ setPopupOpen) = R.createEleme
el = R.hooksComponent "CreateNodeView" cpt
cpt {id, name} _ = do
nodeName <- R.useState' ""
nodeType <- R.useState' NodeUser
nodeType <- R.useState' $ fromMaybe NodeUser $ head nodeTypes
pure $ H.div tooltipProps $
[ H.div {className: "panel panel-default"}
[ panelHeading
......@@ -101,8 +101,10 @@ createNodeView d p@{nodeType} (Just CreatePopup /\ setPopupOpen) = R.createEleme
, onInput: mkEffectFn1 $ \e -> setNodeName $ const $ e .. "target" .. "value"
}
]
, -} H.div {className: "form-group"}
[ R2.select { className: "form-control"
, -}
if length nodeTypes > 1
then
R.fragment [H.div {className: "form-group"} $ [ R2.select { className: "form-control"
, onChange: mkEffectFn1 $ \e -> setNodeType
$ const
$ readIt
......@@ -110,9 +112,14 @@ createNodeView d p@{nodeType} (Just CreatePopup /\ setPopupOpen) = R.createEleme
}
(map (\opt -> H.option {} [ H.text $ show opt ]) nodeTypes)
]
-- , H.text "config"
, showConfig nt
]
else
H.button { className : "btn btn-success"
, type : "button"
, onClick : mkEffectFn1 $ \_ -> setNodeType (const $ fromMaybe nt $ head nodeTypes)
} [showConfig nt]
]
]
]
]
......@@ -137,8 +144,11 @@ createNodeView _ _ _ = R.createElement el {} []
showConfig :: NodeType -> R.Element
showConfig Graph = H.text $ show Graph
showConfig _ = H.text $ show ""
showConfig NodeUser = H.div {} []
showConfig FolderPrivate = H.div {} [H.text "This folder will be private only"]
showConfig FolderShared = H.div {} [H.text "This folder will be shared"]
showConfig FolderPublic = H.div {} [H.text "This folder will be public"]
showConfig nt = H.div {} [H.h1 {} [H.text $ "Config of " <> show nt ]]
......
module Gargantext.Components.Forest.Action.Rename where
module Gargantext.Components.Forest.Tree.Node.Action.Rename where
import Data.Tuple.Nested ((/\))
import Effect.Aff (Aff, launchAff, runAff)
import Effect.Uncurried (mkEffectFn1)
import FFI.Simple ((..))
import Gargantext.Components.Forest.Action
import Gargantext.Components.Forest.Tree.Node.Action
import Prelude hiding (div)
import Reactix as R
import Reactix.DOM.HTML as H
......
module Gargantext.Components.Forest.Action.Upload where
module Gargantext.Components.Forest.Tree.Node.Action.Upload where
import Data.Newtype (class Newtype)
import Effect.Aff (Aff, launchAff, runAff)
......@@ -8,7 +8,7 @@ import Gargantext.Routes (AppRoute, SessionRoute(..))
import Prelude hiding (div)
import Data.Maybe (Maybe(..), fromJust)
import URI.Extra.QueryPairs as QP
import Gargantext.Components.Forest.Action
import Gargantext.Components.Forest.Tree.Node.Action
import Reactix as R
import Data.Tuple (Tuple)
import URI.Query as Q
......
module Gargantext.Components.Forest.Tree.HTML where
module Gargantext.Components.Forest.Tree.Node.Box where
import DOM.Simple.Console (log2)
import Data.Array (filter, null)
......@@ -8,11 +8,11 @@ import Effect.Aff (Aff, launchAff, runAff)
import Effect.Class (liftEffect)
import Effect.Uncurried (mkEffectFn1)
import FFI.Simple ((..))
import Gargantext.Components.Forest.Action
import Gargantext.Components.Forest.Action.Rename
import Gargantext.Components.Forest.Action.Add
import Gargantext.Components.Forest.Action.Upload
import Gargantext.Components.Forest.NodeActions
import Gargantext.Components.Forest.Tree.Node.Action
import Gargantext.Components.Forest.Tree.Node.Action.Rename
import Gargantext.Components.Forest.Tree.Node.Action.Add
import Gargantext.Components.Forest.Tree.Node.Action.Upload
import Gargantext.Components.Forest.Tree.Node
import Gargantext.Ends (Frontends, url)
import Gargantext.Routes (AppRoute, SessionRoute(..))
import Gargantext.Routes as Routes
......@@ -61,7 +61,9 @@ nodeMainSpan d p folderOpen session frontends = R.createElement el p []
[ nodeText { isSelected: (mCorpusId mCurrentRoute) == (Just id)
, name: name'} ]
, if showBox then popOverIcon popupOpen else H.div {} []
, if showBox then nodePopupView d {id, name:name', nodeType} popupOpen else H.div {} []
, if showBox
then nodePopupView d {id, name:name', nodeType} popupOpen
else H.div {} []
, addButton popupOpen
, fileTypeView d {id, nodeType} droppedFile isDragOver
]
......
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