Commit 31f523bf authored by Alexandre Delanoë's avatar Alexandre Delanoë

[FIX] warnings + node settings (NodeTexts)

parent 2cef948d
module Gargantext.Components.Forest.Tree.Node.Action.Share where module Gargantext.Components.Forest.Tree.Node.Action.Share where
import Data.Argonaut (class EncodeJson, jsonEmptyObject, (:=), (~>)) import Data.Argonaut as Argonaut
import Data.Maybe (Maybe(..)) import Data.Generic.Rep (class Generic)
import Effect.Aff (Aff) import Data.Generic.Rep.Show (genericShow)
import Prelude (($))
import Reactix as R
import Gargantext.Components.Forest.Tree.Node.Action (Action)
import Gargantext.Components.Forest.Tree.Node.Action as Action
import Gargantext.Types as GT
import Gargantext.Types (ID)
import Gargantext.Routes as GR
import Gargantext.Sessions (Session, post)
import Gargantext.Components.Forest.Tree.Node.Tools as Tools
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import Effect.Aff (Aff) import Effect.Aff (Aff)
import Gargantext.Components.Forest.Tree.Node.Action (Action) import Gargantext.Components.Forest.Tree.Node.Action (Action)
import Gargantext.Components.Forest.Tree.Node.Action as Action import Gargantext.Components.Forest.Tree.Node.Action as Action
import Gargantext.Components.Forest.Tree.Node.Tools (submitButton, panel) import Gargantext.Components.Forest.Tree.Node.Tools as Tools
import Gargantext.Components.Forest.Tree.Node.Tools.SubTree (subTreeView, SubTreeParamsIn) import Gargantext.Components.Forest.Tree.Node.Tools.SubTree (subTreeView, SubTreeParamsIn)
import Gargantext.Prelude import Gargantext.Prelude (class Eq, class Show, bind, pure)
import Gargantext.Routes (SessionRoute(..)) import Gargantext.Routes as GR
import Gargantext.Sessions (Session, put_) import Gargantext.Sessions (Session, post)
import Gargantext.Types (ID)
import Gargantext.Types as GT import Gargantext.Types as GT
import Gargantext.Utils.Argonaut (genericSumDecodeJson, genericSumEncodeJson)
import Prelude (($))
import Reactix as R import Reactix as R
import Reactix.DOM.HTML as H import Reactix.DOM.HTML as H
import Data.Argonaut as Argonaut
import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Show (genericShow)
import Gargantext.Utils.Argonaut (genericSumDecodeJson, genericSumEncodeJson, genericEnumDecodeJson, genericEnumEncodeJson)
import Data.Maybe (Maybe(..))
import Gargantext.Prelude (class Eq, class Read, class Show)
------------------------------------------------------------------------ ------------------------------------------------------------------------
shareReq :: Session -> ID -> ShareNodeParams -> Aff ID shareReq :: Session -> ID -> ShareNodeParams -> Aff ID
shareReq session nodeId = shareReq session nodeId =
...@@ -76,11 +62,11 @@ shareNodeCpt = R.hooksComponent "G.C.F.T.N.A.M.shareNode" cpt ...@@ -76,11 +62,11 @@ shareNodeCpt = R.hooksComponent "G.C.F.T.N.A.M.shareNode" cpt
let button = case valAction of let button = case valAction of
Action.SharePublic {params} -> case params of Action.SharePublic {params} -> case params of
Just val -> submitButton (Action.SharePublic {params: Just val}) dispatch Just val -> Tools.submitButton (Action.SharePublic {params: Just val}) dispatch
Nothing -> H.div {} [] Nothing -> H.div {} []
_ -> H.div {} [] _ -> H.div {} []
pure $ panel [ subTreeView { action pure $ Tools.panel [ subTreeView { action
, dispatch , dispatch
, id , id
, nodeType , nodeType
......
...@@ -188,7 +188,7 @@ settingsBox Texts = ...@@ -188,7 +188,7 @@ settingsBox Texts =
, buttons : [ Refresh , buttons : [ Refresh
, Upload , Upload
, Download , Download
-- , Delete , Delete
] ]
} }
......
...@@ -149,25 +149,30 @@ contactCellsCpt = R.hooksComponent "G.C.N.A.contactCells" cpt ...@@ -149,25 +149,30 @@ contactCellsCpt = R.hooksComponent "G.C.N.A.contactCells" cpt
, contact: (CT.Contact { id, hyperdata: (CT.HyperdataUser {shared: Nothing}) }) , contact: (CT.Contact { id, hyperdata: (CT.HyperdataUser {shared: Nothing}) })
, frontends , frontends
, session } _ = , session } _ =
pure $ T.makeRow [ pure $ T.makeRow [ H.text ""
H.text ""
, H.span {} [ H.text "name" ] , H.span {} [ H.text "name" ]
--, H.a { href, target: "blank" } [ H.text $ fromMaybe "name" contact.title ] --, H.a { href, target: "blank" } [ H.text $ fromMaybe "name" contact.title ]
, H.text "No ContactWhere" , H.text "No ContactWhere"
, H.text "No ContactWhereDept" , H.text "No ContactWhereDept"
, H.div {className: "nooverflow"} , H.div { className: "nooverflow"}
[ H.text "No ContactWhereRole" ] [ H.text "No ContactWhereRole" ]
] ]
cpt { annuaireId cpt { annuaireId
, contact: (CT.Contact { id , contact: (CT.Contact { id
, hyperdata: (CT.HyperdataUser {shared: Just (CT.HyperdataContact contact@{who, ou})}) }) , hyperdata: (CT.HyperdataUser {shared: Just (CT.HyperdataContact contact@{who, ou})}) })
, frontends , frontends
, session } _ = , session } _ = do
let
contactWho = fromMaybe CT.defaultContactWho who
CT.ContactWho {firstName} = contactWho
pure $ T.makeRow [ pure $ T.makeRow [
H.text "" H.text ""
, H.a { href } [ H.text $ fromMaybe "name" contact.title ] , H.text $ fromMaybe "First Name" firstName
-- , H.a { href } [ H.text $ fromMaybe "name" contact.title ]
--, H.a { href, target: "blank" } [ H.text $ fromMaybe "name" contact.title ] --, H.a { href, target: "blank" } [ H.text $ fromMaybe "name" contact.title ]
, H.text $ maybe "No ContactWhere" contactWhereOrg (A.head $ ou) --, H.text $ maybe "No ContactWhere" contactWhereOrg (A.head $ ou)
, H.text $ maybe "No ContactWhereDept" contactWhereDept (A.head $ ou) , H.text $ maybe "No ContactWhereDept" contactWhereDept (A.head $ ou)
, H.div {className: "nooverflow"} [ , H.div {className: "nooverflow"} [
H.text $ maybe "No ContactWhereRole" contactWhereRole (A.head $ ou) H.text $ maybe "No ContactWhereRole" contactWhereRole (A.head $ ou)
......
...@@ -53,7 +53,8 @@ newtype ContactWho = ...@@ -53,7 +53,8 @@ newtype ContactWho =
, firstName :: Maybe String , firstName :: Maybe String
, lastName :: Maybe String , lastName :: Maybe String
, keywords :: (Array String) , keywords :: (Array String)
, freetags :: (Array String) } , freetags :: (Array String)
}
derive instance newtypeContactWho :: Newtype ContactWho _ derive instance newtypeContactWho :: Newtype ContactWho _
......
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