Commit cf0352d6 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[REFACT] G.C.F.T.N.B.A.Tools easy HTML inputTextBox to be reused

parent aa768a9a
module Gargantext.Components.Forest.Tree.Node.Action.Rename where module Gargantext.Components.Forest.Tree.Node.Action.Rename where
import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, jsonEmptyObject, (.:), (:=), (~>)) import Data.Argonaut (class EncodeJson, jsonEmptyObject, (:=), (~>))
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Data.Tuple.Nested ((/\)) import Effect.Aff (Aff)
import Effect.Aff (Aff, launchAff) import Prelude (($))
import Effect.Uncurried (mkEffectFn1)
import Prelude (Unit, bind, const, discard, pure, ($), (<<<), (<>))
import Reactix as R import Reactix as R
import Reactix.DOM.HTML as H
import Gargantext.Components.Forest.Tree.Node.Action import Gargantext.Components.Forest.Tree.Node.Action
import Gargantext.Types as GT import Gargantext.Types as GT
import Gargantext.Types (ID) import Gargantext.Types (ID)
import Gargantext.Routes as GR import Gargantext.Routes as GR
import Gargantext.Utils.Reactix as R2 import Gargantext.Sessions (Session, put)
import Gargantext.Sessions (Session, get, put, post, delete) import Gargantext.Components.Forest.Tree.Node.Tools.TextInputBox as Tools
------------------------------------------------------------------------ ------------------------------------------------------------------------
rename :: Session -> ID -> RenameValue -> Aff (Array ID) rename :: Session -> ID -> RenameValue -> Aff (Array ID)
...@@ -35,57 +30,6 @@ instance encodeJsonRenameValue :: EncodeJson RenameValue where ...@@ -35,57 +30,6 @@ instance encodeJsonRenameValue :: EncodeJson RenameValue where
~> jsonEmptyObject ~> jsonEmptyObject
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- | START Rename Box textInputBox :: Record Tools.TextInputBoxProps -> R.Element
type TextInputBoxProps = textInputBox = Tools.textInputBox
( id :: ID
, dispatch :: Action -> Aff Unit
, text :: String
, isOpen :: R.State Boolean
, boxName :: String
, boxAction :: String -> Action
)
textInputBox :: Record TextInputBoxProps -> R.Element
textInputBox p@{ boxName, boxAction, dispatch, isOpen: (true /\ setIsOpen) } = R.createElement el p []
where
el = R.hooksComponent (boxName <> "Box") cpt
cpt {id, text} _ = do
renameNodeName <- R.useState' text
pure $ H.div {className: "from-group row-no-padding"}
[ textInput renameNodeName
, submitBtn renameNodeName
, cancelBtn
]
where
textInput (_ /\ setRenameNodeName) =
H.div {className: "col-md-8"}
[ H.input { type: "text"
, placeholder: (boxName <> " Node")
, defaultValue: text
, className: "form-control"
, onInput: mkEffectFn1 $ setRenameNodeName
<<< const
<<< R2.unsafeEventValue
}
]
submitBtn (newName /\ _) =
H.a {className: "btn glyphitem glyphicon glyphicon-ok col-md-2 pull-left"
, type: "button"
, onClick: mkEffectFn1 $ \_ -> do
setIsOpen $ const false
launchAff $ dispatch ( boxAction newName )
, title: "Submit"
} []
cancelBtn =
H.a {className: "btn text-danger glyphitem glyphicon glyphicon-remove col-md-2 pull-left"
, type: "button"
, onClick: mkEffectFn1 $ \_ -> setIsOpen $ const false
, title: "Cancel"
} []
textInputBox p@{ boxName, isOpen: (false /\ _) } = R.createElement el p []
where
el = R.hooksComponent (boxName <> "Box") cpt
cpt {text} _ = pure $ H.div {} []
-- | END Rename Box
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