Commit 77683cc7 authored by Karen Konou's avatar Karen Konou

Merge branch 'dev' into 548-dev-node-url-share

parents 8c77a71b ea54fd82
{ {
"name": "Gargantext", "name": "Gargantext",
"version": "0.0.7", "version": "0.0.7.1",
"scripts": { "scripts": {
"generate-purs-packages-nix": "./nix/generate-purs-packages.nix", "generate-purs-packages-nix": "./nix/generate-purs-packages.nix",
"generate-psc-packages-nix": "./nix/generate-packages-json.bash", "generate-psc-packages-nix": "./nix/generate-packages-json.bash",
......
...@@ -5,16 +5,18 @@ module Gargantext.Components.Forest.Breadcrumb ...@@ -5,16 +5,18 @@ module Gargantext.Components.Forest.Breadcrumb
where where
import Data.Array as A import Data.Array as A
import Data.Either (Either(..), either)
import Data.Int (fromString) import Data.Int (fromString)
import Data.Maybe (Maybe(..), fromMaybe) import Data.Maybe (Maybe(..), fromMaybe, maybe)
import Data.String (Pattern(..), split) import Data.String (Pattern(..), split)
import Gargantext.Components.App.Store as Store import Gargantext.Components.App.Store as Store
import Gargantext.Components.Bootstrap as B import Gargantext.Components.Bootstrap as B
import Gargantext.Components.GraphQL.Endpoints (getBreadcrumb) import Gargantext.Components.GraphQL.Endpoints (getBreadcrumb, getNodeChildren, getNodeParent)
import Gargantext.Components.GraphQL.Tree (BreadcrumbInfo, TreeNode) import Gargantext.Components.GraphQL.Tree (BreadcrumbInfo, TreeNode)
import Gargantext.Config.REST (AffRESTError) import Gargantext.Config.REST (AffRESTError)
import Gargantext.Ends (Backend(..))
import Gargantext.Hooks.Loader (useLoader) import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Routes (AppRoute(Home), appPath, nodeTypeAppRoute) import Gargantext.Routes (AppRoute(..), appPath, nodeTypeAppRoute)
import Gargantext.Sessions.Types import Gargantext.Sessions.Types
import Gargantext.Types (NodeType, SessionId) import Gargantext.Types (NodeType, SessionId)
import Gargantext.Types as GT import Gargantext.Types as GT
...@@ -30,25 +32,17 @@ import Toestand as T ...@@ -30,25 +32,17 @@ import Toestand as T
here :: R2.Here here :: R2.Here
here = R2.here "Gargantext.Components.Forest.Breadcrumb" here = R2.here "Gargantext.Components.Forest.Breadcrumb"
type PropsBoxes = ( boxes :: Store.Boxes )
type Props = component :: R2.Leaf ()
( nodeId :: Int
, session :: Maybe Session
, format :: String
)
-- maybeToSession :: Maybe Session -> Session
-- maybeToSession s = fromMaybe Nothing s
component :: R2.Leaf PropsBoxes
component = R2.leaf componentCpt component = R2.leaf componentCpt
componentCpt :: R.Component PropsBoxes componentCpt :: R.Component ()
componentCpt = here.component "breadcrumb" cpt where componentCpt = here.component "breadcrumb" cpt where
cpt { boxes: { session } } _ = do cpt { } _ = do
{ route, session } <- Store.use
-- | States -- | States
-- | -- |
route' <- T.useLive T.unequal route
session' <- T.useLive T.unequal session session' <- T.useLive T.unequal session
-- R.provideContext SessionContext.context session' -- R.provideContext SessionContext.context session'
...@@ -67,10 +61,10 @@ componentCpt = here.component "breadcrumb" cpt where ...@@ -67,10 +61,10 @@ componentCpt = here.component "breadcrumb" cpt where
case session' of case session' of
Nothing -> pure $ H.div {} [] Nothing -> pure $ H.div {} []
Just _session'' -> do Just session'' -> do
url <- R.unsafeHooksEffect GU.href -- url <- R.unsafeHooksEffect GU.href
let nodeId = fromMaybe 0 $ fromString $ getLastUrlElement url -- let nodeId = fromMaybe 0 $ fromString $ getLastUrlElement url
-- breadcrumbData <- R2.useLayoutEffect1' $ getBreadcrumb session' currentNodeId -- breadcrumbData <- R2.useLayoutEffect1' $ getBreadcrumb session' currentNodeId
pure $ pure $
...@@ -91,10 +85,10 @@ componentCpt = here.component "breadcrumb" cpt where ...@@ -91,10 +85,10 @@ componentCpt = here.component "breadcrumb" cpt where
] ]
] ]
, ,
breadcrumbView { nodeId: nodeId breadcrumbView { format: "default"
, session: session' , route: route'
, format: "default" , session: session''
} }
] ]
-- , -- ,
-- H.nav -- H.nav
...@@ -146,40 +140,42 @@ componentCpt = here.component "breadcrumb" cpt where ...@@ -146,40 +140,42 @@ componentCpt = here.component "breadcrumb" cpt where
-- ] -- ]
] ]
type BreadcrumbViewProps =
( format :: String
, route :: AppRoute
, session :: Session
)
breadcrumbView :: R2.Leaf Props breadcrumbView :: R2.Leaf BreadcrumbViewProps
breadcrumbView = R2.leaf breadcrumbViewCpt breadcrumbView = R2.leaf breadcrumbViewCpt
breadcrumbViewCpt :: R.Component Props breadcrumbViewCpt :: R.Component BreadcrumbViewProps
breadcrumbViewCpt = R2.hereComponent here "breadcrumbViewCpt" hCpt where breadcrumbViewCpt = R2.hereComponent here "breadcrumbViewCpt" hCpt where
hCpt hp { nodeId, session, format } _ = do hCpt hp { format, route, session } _ = do
case session of useLoader { errorHandler: Nothing
Nothing -> pure $ H.div {} [] , herePrefix: hp
Just session' -> do , loader: loadBreadcrumbData
useLoader { errorHandler: Nothing , path: { route
, herePrefix: hp , session
, loader: loadBreadcrumbData }
, path: { nodeId: nodeId , render: \items -> breadcrumbViewMain { format: format
, session: session' , items
-- , reload: reload' , session
} -- , reload: reload
, render: \items -> breadcrumbViewMain { items: items } []
, session: session' }
-- , reload: reload
, format: format type BreadcrumbViewMainProps =
} [] ( format :: String
} , items :: BreadcrumbInfo
type BreadcrumbViewProps =
( items :: BreadcrumbInfo
, session :: Session , session :: Session
-- , reload :: T.Box T2.Reload -- , reload :: T.Box T2.Reload
, format :: String
) )
breadcrumbViewMain :: R2.Component BreadcrumbViewProps breadcrumbViewMain :: R2.Component BreadcrumbViewMainProps
breadcrumbViewMain = R.createElement breadcrumbViewMainCpt breadcrumbViewMain = R.createElement breadcrumbViewMainCpt
breadcrumbViewMainCpt :: R.Component BreadcrumbViewProps breadcrumbViewMainCpt :: R.Component BreadcrumbViewMainProps
breadcrumbViewMainCpt = here.component "breadcrumbViewMainCpt" cpt where breadcrumbViewMainCpt = here.component "breadcrumbViewMainCpt" cpt where
cpt { items: { parents }, session, format } _ = do cpt { items: { parents }, session, format } _ = do
...@@ -234,8 +230,6 @@ breadcrumbItemCpt = here.component "breadcrumbItemCpt" cpt where ...@@ -234,8 +230,6 @@ breadcrumbItemCpt = here.component "breadcrumbItemCpt" cpt where
boxes@{ forestOpen } <- Store.use boxes@{ forestOpen } <- Store.use
url <- R.unsafeHooksEffect GU.href
let sid = sessionId session let sid = sessionId session
let rootId = treeId session let rootId = treeId session
...@@ -249,7 +243,7 @@ breadcrumbItemCpt = here.component "breadcrumbItemCpt" cpt where ...@@ -249,7 +243,7 @@ breadcrumbItemCpt = here.component "breadcrumbItemCpt" cpt where
H.span { className: "node-path-item" } H.span { className: "node-path-item" }
[ [
if show nodeType == "NodeUser" if nodeType == GT.NodeUser
then then
H.text "" H.text ""
else else
...@@ -260,10 +254,7 @@ breadcrumbItemCpt = here.component "breadcrumbItemCpt" cpt where ...@@ -260,10 +254,7 @@ breadcrumbItemCpt = here.component "breadcrumbItemCpt" cpt where
H.li { className: "breadcrumb-item" } H.li { className: "breadcrumb-item" }
[ [
if show nodeType == "NodeFolderPrivate" if nodeType `A.elem` [ GT.FolderPrivate, GT.FolderPublic, GT.FolderShared, GT.NodeUser ]
|| show nodeType == "NodeFolderPublic"
|| show nodeType == "NodeFolderShared"
|| show nodeType == "NodeUser"
then then
H.span { className: "" } H.span { className: "" }
[ [
...@@ -275,17 +266,17 @@ breadcrumbItemCpt = here.component "breadcrumbItemCpt" cpt where ...@@ -275,17 +266,17 @@ breadcrumbItemCpt = here.component "breadcrumbItemCpt" cpt where
} }
] ]
, ,
if show nodeType == "NodeUser" if nodeType == GT.NodeUser
then then
H.text $ getUserText url H.text $ getUserText session
else else
H.text text H.text text
, H.span { className: "text-small" } , H.span { className: "text-small" }
[ [
if show nodeType == "NodeUser" if nodeType == GT.NodeUser
then then
H.text $ " (" <> getInstanceText url <> ")" H.text $ " (" <> getInstanceText session <> ")"
else else
H.text "" H.text ""
] ]
...@@ -322,25 +313,84 @@ breadcrumbItemCpt = here.component "breadcrumbItemCpt" cpt where ...@@ -322,25 +313,84 @@ breadcrumbItemCpt = here.component "breadcrumbItemCpt" cpt where
treeId :: Session -> Int treeId :: Session -> Int
treeId (Session {treeId: tId}) = tId treeId (Session {treeId: tId}) = tId
getLastUrlElement :: String -> String getInstanceText :: Session -> String
getLastUrlElement str = fromMaybe "" $ A.last $ split (Pattern "/") str getInstanceText (Session { backend }) = cleanBackendUrl backend
getFirstUrlElement :: String -> String
getFirstUrlElement str = fromMaybe "" $ A.head $ split (Pattern "/") str
getInstanceText :: String -> String getUserText :: Session -> String
getInstanceText str = getFirstUrlElement $ fromMaybe "" $ A.last $ split (Pattern "@") str getUserText (Session { username }) = username
-- getLastUrlElement $ fromMaybe "" $ A.head $ split (Pattern "@") str
getUserText :: String -> String
getUserText str = getLastUrlElement $ fromMaybe "" $ A.head $ split (Pattern "@") str
type LoadProps = type LoadRawProps =
( (
session :: Session nodeId :: Int
, nodeId :: Int , session :: Session
-- , reload :: T.Box T2.Reload -- , reload :: T.Box T2.Reload
) )
loadBreadcrumbDataRaw :: Record LoadRawProps -> AffRESTError BreadcrumbInfo
loadBreadcrumbDataRaw { nodeId, session } = getBreadcrumb session nodeId
type LoadProps =
( route :: AppRoute
, session :: Session )
loadBreadcrumbData :: Record LoadProps -> AffRESTError BreadcrumbInfo loadBreadcrumbData :: Record LoadProps -> AffRESTError BreadcrumbInfo
loadBreadcrumbData {nodeId, session} = getBreadcrumb session nodeId loadBreadcrumbData { route: Annuaire _s nodeId, session } = do
loadBreadcrumbDataRaw { nodeId, session }
loadBreadcrumbData { route: ContactPage _s nodeId annuaireId, session } = do
loadBreadcrumbDataRaw { nodeId: annuaireId, session }
loadBreadcrumbData { route: Corpus _s nodeId, session } = do
loadBreadcrumbDataRaw { nodeId, session }
loadBreadcrumbData { route: CorpusCode _s nodeId, session } = do
loadBreadcrumbDataRaw { nodeId, session }
loadBreadcrumbData { route: CorpusDocument _s corpusId listId documentId, session } = do
texts <- getNodeChildren session corpusId GT.NodeTexts
let docId = maybe corpusId _.id $ either (const Nothing) A.head texts
loadBreadcrumbDataRaw { nodeId: docId, session }
loadBreadcrumbData { route: Dashboard _s nodeId, session } = do
loadBreadcrumbDataRaw { nodeId, session }
loadBreadcrumbData { route: Document _s listId documentId, session } = do
corpora <- getNodeParent session listId GT.Corpus
let nodeId = maybe listId _.id $ either (const Nothing) A.head corpora
loadBreadcrumbDataRaw { nodeId, session }
loadBreadcrumbData { route: Folder _s nodeId, session } = do
loadBreadcrumbDataRaw { nodeId, session }
loadBreadcrumbData { route: FolderPrivate _s nodeId, session } = do
loadBreadcrumbDataRaw { nodeId, session }
loadBreadcrumbData { route: FolderPublic _s nodeId, session } = do
loadBreadcrumbDataRaw { nodeId, session }
loadBreadcrumbData { route: FolderShared _s nodeId, session } = do
loadBreadcrumbDataRaw { nodeId, session }
loadBreadcrumbData { route: Lists _s nodeId, session } = do
loadBreadcrumbDataRaw { nodeId, session }
loadBreadcrumbData { route: NodeTexts _s nodeId, session } = do
loadBreadcrumbDataRaw { nodeId, session }
loadBreadcrumbData { route: PGraphExplorer _s nodeId, session } = do
loadBreadcrumbDataRaw { nodeId, session }
loadBreadcrumbData { route: PhyloExplorer _s nodeId, session } = do
loadBreadcrumbDataRaw { nodeId, session }
loadBreadcrumbData { route: RouteFile _s nodeId, session } = do
loadBreadcrumbDataRaw { nodeId, session }
loadBreadcrumbData { route: RouteFrameCalc _s nodeId, session } = do
loadBreadcrumbDataRaw { nodeId, session }
loadBreadcrumbData { route: RouteFrameCode _s nodeId, session } = do
loadBreadcrumbDataRaw { nodeId, session }
loadBreadcrumbData { route: RouteFrameVisio _s nodeId, session } = do
loadBreadcrumbDataRaw { nodeId, session }
loadBreadcrumbData { route: RouteFrameWrite _s nodeId, session } = do
loadBreadcrumbDataRaw { nodeId, session }
loadBreadcrumbData { route: Team _s nodeId, session } = do
loadBreadcrumbDataRaw { nodeId, session }
loadBreadcrumbData { route: TreeFlat _s nodeId _q, session } = do
loadBreadcrumbDataRaw { nodeId, session }
loadBreadcrumbData { route: UserPage _s nodeId, session } = do
loadBreadcrumbDataRaw { nodeId, session }
loadBreadcrumbData { route: ForgotPassword _s } = do
pure $ Right { parents: [] }
loadBreadcrumbData { route: Home } = do
pure $ Right { parents: [] }
loadBreadcrumbData { route: Login } = do
pure $ Right { parents: [] }
...@@ -17,9 +17,11 @@ instance JSON.ReadForeign AddContactParams where readImpl = GUSJ.taggedSumRep ...@@ -17,9 +17,11 @@ instance JSON.ReadForeign AddContactParams where readImpl = GUSJ.taggedSumRep
instance JSON.WriteForeign AddContactParams where instance JSON.WriteForeign AddContactParams where
writeImpl (AddContactParams { firstname, lastname }) = writeImpl (AddContactParams { firstname, lastname }) =
JSON.writeImpl { type: "AddContactParams" JSON.writeImpl { type: "AddContactParams"
, values: { firstname, lastname } } , firstname
, lastname }
writeImpl (AddContactParamsAdvanced { firstname, lastname }) = writeImpl (AddContactParamsAdvanced { firstname, lastname }) =
JSON.writeImpl { type: "AddContactParamsAdvanced" JSON.writeImpl { type: "AddContactParamsAdvanced"
, values: { firstname, lastname } } , firstname
, lastname }
...@@ -44,8 +44,9 @@ getCompletionsReq { session } = ...@@ -44,8 +44,9 @@ getCompletionsReq { session } =
------------------------------------------------------------------------ ------------------------------------------------------------------------
data ShareNodeParams = ShareTeamParams { username :: String } data ShareNodeParams =
| SharePublicParams { node_id :: Int } ShareTeamParams { username :: String }
| SharePublicParams { node_id :: Int }
derive instance Eq ShareNodeParams derive instance Eq ShareNodeParams
derive instance Generic ShareNodeParams _ derive instance Generic ShareNodeParams _
instance JSON.ReadForeign ShareNodeParams where readImpl = GUSJ.taggedSumRep instance JSON.ReadForeign ShareNodeParams where readImpl = GUSJ.taggedSumRep
......
...@@ -21,7 +21,9 @@ import Gargantext.Components.GraphQL.User (User, UserInfo, UserInfoM, UserPubmed ...@@ -21,7 +21,9 @@ import Gargantext.Components.GraphQL.User (User, UserInfo, UserInfoM, UserPubmed
import Gargantext.Config.REST as REST import Gargantext.Config.REST as REST
import Gargantext.Ends (Backend(..)) import Gargantext.Ends (Backend(..))
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Routes (AppRoute)
import Gargantext.Sessions (Session(..)) import Gargantext.Sessions (Session(..))
import Gargantext.Types (NodeType)
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import GraphQL.Client.Args (type (==>)) import GraphQL.Client.Args (type (==>))
import GraphQL.Client.BaseClients.Urql (UrqlClient, createClient) import GraphQL.Client.BaseClients.Urql (UrqlClient, createClient)
...@@ -150,7 +152,8 @@ type Schema ...@@ -150,7 +152,8 @@ type Schema
, contexts_for_ngrams :: { corpus_id :: Int, ngrams_terms :: Array String } ==> Array GQLCTX.Context , contexts_for_ngrams :: { corpus_id :: Int, ngrams_terms :: Array String } ==> Array GQLCTX.Context
, imt_schools :: {} ==> Array GQLIMT.School , imt_schools :: {} ==> Array GQLIMT.School
, languages :: {} ==> Array GQLNLP.Language , languages :: {} ==> Array GQLNLP.Language
, node_parent :: { node_id :: Int, parent_type :: String } ==> Array GQLNode.Node -- TODO: parent_type :: NodeType , node_children :: { node_id :: Int, child_type :: NodeType } ==> Array GQLNode.Node
, node_parent :: { node_id :: Int, parent_type :: NodeType } ==> Array GQLNode.Node
, nodes :: { node_id :: Int } ==> Array GQLNode.Node , nodes :: { node_id :: Int } ==> Array GQLNode.Node
, nodes_corpus :: { corpus_id :: Int } ==> Array GQLNode.Corpus , nodes_corpus :: { corpus_id :: Int } ==> Array GQLNode.Corpus
, user_infos :: { user_id :: Int } ==> Array UserInfo , user_infos :: { user_id :: Int } ==> Array UserInfo
......
...@@ -12,7 +12,7 @@ import Gargantext.Components.GraphQL.Contact (AnnuaireContact, annuaireContactQu ...@@ -12,7 +12,7 @@ import Gargantext.Components.GraphQL.Contact (AnnuaireContact, annuaireContactQu
import Gargantext.Components.GraphQL.Context as GQLCTX import Gargantext.Components.GraphQL.Context as GQLCTX
import Gargantext.Components.GraphQL.IMT as GQLIMT import Gargantext.Components.GraphQL.IMT as GQLIMT
import Gargantext.Components.GraphQL.NLP as GQLNLP import Gargantext.Components.GraphQL.NLP as GQLNLP
import Gargantext.Components.GraphQL.Node (Corpus, Node, nodeParentQuery, nodesQuery, nodesCorpusQuery) import Gargantext.Components.GraphQL.Node (Corpus, Node, nodeChildrenQuery, nodeParentQuery, nodesQuery, nodesCorpusQuery)
import Gargantext.Components.GraphQL.Team (Team, teamQuery) import Gargantext.Components.GraphQL.Team (Team, teamQuery)
import Gargantext.Components.GraphQL.Tree (TreeFirstLevel, treeFirstLevelQuery, BreadcrumbInfo, breadcrumbQuery) import Gargantext.Components.GraphQL.Tree (TreeFirstLevel, treeFirstLevelQuery, BreadcrumbInfo, breadcrumbQuery)
import Gargantext.Components.GraphQL.User (UserInfo, userInfoQuery, User, userQuery) import Gargantext.Components.GraphQL.User (UserInfo, userInfoQuery, User, userQuery)
...@@ -20,6 +20,7 @@ import Gargantext.Components.Lang (Lang) ...@@ -20,6 +20,7 @@ import Gargantext.Components.Lang (Lang)
import Gargantext.Config.REST (RESTError(..), AffRESTError) import Gargantext.Config.REST (RESTError(..), AffRESTError)
import Gargantext.Core.NgramsTable.Types (NgramsTerm(..)) import Gargantext.Core.NgramsTable.Types (NgramsTerm(..))
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Routes (AppRoute(..))
import Gargantext.Sessions (Session(..)) import Gargantext.Sessions (Session(..))
import Gargantext.Types (CorpusId, NodeType) import Gargantext.Types (CorpusId, NodeType)
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
...@@ -64,11 +65,20 @@ getNodeParent :: Session -> Int -> NodeType -> AffRESTError (Array Node) ...@@ -64,11 +65,20 @@ getNodeParent :: Session -> Int -> NodeType -> AffRESTError (Array Node)
getNodeParent session nodeId parentType = do getNodeParent session nodeId parentType = do
eRes <- queryGql session "get node parent" $ eRes <- queryGql session "get node parent" $
nodeParentQuery `withVars` { id: nodeId nodeParentQuery `withVars` { id: nodeId
, parent_type: show parentType } -- TODO: remove "show" , parent_type: parentType }
-- liftEffect $ here.log2 "[getNodeParent] node_parent" node_parent -- liftEffect $ here.log2 "[getNodeParent] node_parent" node_parent
--pure node_parent --pure node_parent
pure $ rmap _.node_parent eRes pure $ rmap _.node_parent eRes
getNodeChildren :: Session -> Int -> NodeType -> AffRESTError (Array Node)
getNodeChildren session nodeId childType = do
eRes <- queryGql session "get node child" $
nodeChildrenQuery `withVars` { id: nodeId
, child_type: childType }
-- liftEffect $ here.log2 "[getNodeParent] node_parent" node_parent
--pure node_parent
pure $ rmap _.node_children eRes
getUser :: Session -> Int -> AffRESTError User getUser :: Session -> Int -> AffRESTError User
getUser session id = do getUser session id = do
eRes <- queryGql session "get user" $ userQuery `withVars` { id } eRes <- queryGql session "get user" $ userQuery `withVars` { id }
...@@ -218,7 +228,7 @@ getContextNgrams session context_id list_id = do ...@@ -218,7 +228,7 @@ getContextNgrams session context_id list_id = do
pure $ rmap (\{ context_ngrams } -> NormNgramsTerm <$> context_ngrams) eRes pure $ rmap (\{ context_ngrams } -> NormNgramsTerm <$> context_ngrams) eRes
getBreadcrumb :: Session -> Int -> AffRESTError BreadcrumbInfo getBreadcrumb :: Session -> Int -> AffRESTError BreadcrumbInfo
getBreadcrumb session id = do getBreadcrumb session node_id = do
eRes <- queryGql session "get breadcrumb branch" $ breadcrumbQuery `withVars` { id } eRes <- queryGql session "get breadcrumb branch" $ breadcrumbQuery `withVars` { node_id }
-- liftEffect $ here.log2 "[getBreadcrumb] breadcrumb" tree_branch -- liftEffect $ here.log2 "[getBreadcrumb] breadcrumb" tree_branch
pure $ rmap _.tree_branch eRes pure $ rmap _.tree_branch eRes
...@@ -2,6 +2,7 @@ module Gargantext.Components.GraphQL.Node where ...@@ -2,6 +2,7 @@ module Gargantext.Components.GraphQL.Node where
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Utils.GraphQL as GGQL import Gargantext.Utils.GraphQL as GGQL
import Gargantext.Types (NodeType)
import GraphQL.Client.Args (Args, (=>>)) import GraphQL.Client.Args (Args, (=>>))
import GraphQL.Client.Variable (Var(..)) import GraphQL.Client.Variable (Var(..))
import Type.Proxy (Proxy(..)) import Type.Proxy (Proxy(..))
...@@ -46,6 +47,11 @@ nodesCorpusQuery = { nodes_corpus: { corpus_id: Var :: _ "id" Int } =>> ...@@ -46,6 +47,11 @@ nodesCorpusQuery = { nodes_corpus: { corpus_id: Var :: _ "id" Int } =>>
} }
nodeParentQuery = { node_parent: { node_id: Var :: _ "id" Int nodeParentQuery = { node_parent: { node_id: Var :: _ "id" Int
, parent_type: Var :: _ "parent_type" String } =>> -- TODO parent_type :: NodeType , parent_type: Var :: _ "parent_type" NodeType } =>>
GGQL.getFieldsStandard (Proxy :: _ Node) GGQL.getFieldsStandard (Proxy :: _ Node)
} }
nodeChildrenQuery = { node_children: { node_id: Var :: _ "id" Int
, child_type: Var :: _ "child_type" NodeType } =>>
GGQL.getFieldsStandard (Proxy :: _ Node)
}
...@@ -3,6 +3,7 @@ module Gargantext.Components.GraphQL.Tree where ...@@ -3,6 +3,7 @@ module Gargantext.Components.GraphQL.Tree where
import Gargantext.Prelude import Gargantext.Prelude
import Data.Maybe (Maybe) import Data.Maybe (Maybe)
import Gargantext.Routes (AppRoute)
import Gargantext.Types (NodeType) import Gargantext.Types (NodeType)
import GraphQL.Client.Args ((=>>)) import GraphQL.Client.Args ((=>>))
import GraphQL.Client.Variable (Var(..)) import GraphQL.Client.Variable (Var(..))
...@@ -42,7 +43,7 @@ treeFirstLevelQuery = { tree: { root_id: Var :: _ "id" Int} =>> ...@@ -42,7 +43,7 @@ treeFirstLevelQuery = { tree: { root_id: Var :: _ "id" Int} =>>
} }
} }
breadcrumbQuery = { tree_branch: { node_id: Var :: _ "id" Int} =>> breadcrumbQuery = { tree_branch: { node_id: Var :: _ "node_id" Int } =>>
{ parents: { parents:
{ name: unit { name: unit
, node_type: unit , node_type: unit
...@@ -50,4 +51,4 @@ breadcrumbQuery = { tree_branch: { node_id: Var :: _ "id" Int} =>> ...@@ -50,4 +51,4 @@ breadcrumbQuery = { tree_branch: { node_id: Var :: _ "id" Int} =>>
, parent_id: unit , parent_id: unit
} }
} }
} }
\ No newline at end of file
...@@ -182,8 +182,7 @@ mainPageCpt = here.component "mainPage" cpt where ...@@ -182,8 +182,7 @@ mainPageCpt = here.component "mainPage" cpt where
H.div { className: "router__body main-page" } H.div { className: "router__body main-page" }
[ [
Breadcrumb.component Breadcrumb.component { }
{ boxes }
, ,
H.div H.div
{ className: intercalate " " { className: intercalate " "
...@@ -487,7 +486,6 @@ type CorpusDocumentProps = ...@@ -487,7 +486,6 @@ type CorpusDocumentProps =
corpusDocument :: R2.Component CorpusDocumentProps corpusDocument :: R2.Component CorpusDocumentProps
corpusDocument = R.createElement corpusDocumentCpt corpusDocument = R.createElement corpusDocumentCpt
corpusDocumentCpt :: R.Component CorpusDocumentProps corpusDocumentCpt :: R.Component CorpusDocumentProps
corpusDocumentCpt = here.component "corpusDocument" cpt where corpusDocumentCpt = here.component "corpusDocument" cpt where
cpt props@{ corpusId, listId, nodeId } _ = do cpt props@{ corpusId, listId, nodeId } _ = do
...@@ -496,16 +494,16 @@ corpusDocumentCpt = here.component "corpusDocument" cpt where ...@@ -496,16 +494,16 @@ corpusDocumentCpt = here.component "corpusDocument" cpt where
authedProps = authedProps =
Record.merge Record.merge
{ content: { content:
\session -> \session ->
Document.node Document.node
{ mCorpusId: Just corpusId { mCorpusId: Just corpusId
, listId , listId
, nodeId , nodeId
, key: show (sessionId session) <> "-" <> show nodeId , key: show (sessionId session) <> "-" <> show nodeId
} }
} }
sessionProps sessionProps
pure $ authed authedProps [] pure $ authed authedProps []
...@@ -530,7 +528,6 @@ type DocumentProps = ...@@ -530,7 +528,6 @@ type DocumentProps =
document :: R2.Component DocumentProps document :: R2.Component DocumentProps
document = R.createElement documentCpt document = R.createElement documentCpt
documentCpt :: R.Component DocumentProps documentCpt :: R.Component DocumentProps
documentCpt = here.component "document" cpt where documentCpt = here.component "document" cpt where
cpt props@{ listId, nodeId } _ = do cpt props@{ listId, nodeId } _ = do
......
...@@ -169,14 +169,15 @@ treeSearchRenderContainerCpt = here.component "treeSearchRenderContainer" cpt wh ...@@ -169,14 +169,15 @@ treeSearchRenderContainerCpt = here.component "treeSearchRenderContainer" cpt wh
treeSearchRender :: R2.Leaf RenderProps treeSearchRender :: R2.Leaf RenderProps
treeSearchRender = R2.leaf treeSearchRenderCpt treeSearchRender = R2.leaf treeSearchRenderCpt
treeSearchRenderCpt :: R.Component RenderProps treeSearchRenderCpt :: R.Component RenderProps
treeSearchRenderCpt = here.component "treeSearchRenderCpt" cpt where treeSearchRenderCpt = here.component "treeSearchRenderCpt" cpt where
cpt { visible, session, searchData, goToRoute } _ = do cpt { visible, session, searchData, goToRoute } _ = do
{ route } <- AppStore.use
route' <- T.useLive T.unequal route
pure $ H.div {className: "search-modal__results"} (results searchData) pure $ H.div {className: "search-modal__results"} (results route' searchData)
where where
results s = map searchResult s results route' s = map searchResult s
where where
searchResult sd = H.div searchResult sd = H.div
{ className: "result py-1"} { className: "result py-1"}
...@@ -195,9 +196,9 @@ treeSearchRenderCpt = here.component "treeSearchRenderCpt" cpt where ...@@ -195,9 +196,9 @@ treeSearchRenderCpt = here.component "treeSearchRenderCpt" cpt where
, H.div {} , H.div {}
[ [
H.text " Path: " H.text " Path: "
, breadcrumbView { nodeId: sd.id , breadcrumbView { format: "text"
, session: Just session , route: route'
, format: "text" , session
} }
] ]
] ]
...@@ -218,10 +219,10 @@ treeSearchRenderCpt = here.component "treeSearchRenderCpt" cpt where ...@@ -218,10 +219,10 @@ treeSearchRenderCpt = here.component "treeSearchRenderCpt" cpt where
H.span { className: "node-path small" } H.span { className: "node-path small" }
[ [
H.text " — " H.text " — "
, breadcrumbView { nodeId: sd.id , breadcrumbView { format: "text"
, session: Just session , route: route'
, format: "text" , session: session
} }
] ]
] ]
......
...@@ -2,11 +2,16 @@ module Gargantext.Routes where ...@@ -2,11 +2,16 @@ module Gargantext.Routes where
import Prelude import Prelude
import Data.Argonaut as Argonaut
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Data.UUID (UUID) import Data.UUID (UUID)
import Data.Map as M import Data.Map as M
import Gargantext.Types (ChartOpts, ChartType, CorpusMetricOpts, CTabNgramType, Id, Limit, ListId, DocId, NgramsGetOpts, NgramsGetTableAllOpts, NodeType, Offset, OrderBy, SearchOpts, SessionId, TabSubType, TabType, TermList) import Gargantext.Types (ChartOpts, ChartType, CorpusMetricOpts, CTabNgramType, Id, Limit, ListId, DocId, NgramsGetOpts, NgramsGetTableAllOpts, NodeType, Offset, OrderBy, SearchOpts, SessionId, TabSubType, TabType, TermList)
import Gargantext.Types as GT import Gargantext.Types as GT
import Gargantext.Utils.SimpleJSON (encodeJsonArgonaut)
import GraphQL.Client.Args (class ArgGql)
import GraphQL.Client.Variables.TypeName (class VarTypeName)
import Simple.JSON as JSON
data AppRoute data AppRoute
= Annuaire SessionId Int = Annuaire SessionId Int
...@@ -25,7 +30,6 @@ data AppRoute ...@@ -25,7 +30,6 @@ data AppRoute
| Lists SessionId Int | Lists SessionId Int
| Login | Login
| NodeTexts SessionId Int | NodeTexts SessionId Int
| TreeFlat SessionId Int String
| PGraphExplorer SessionId Int | PGraphExplorer SessionId Int
| PhyloExplorer SessionId Int | PhyloExplorer SessionId Int
| RouteFile SessionId Int | RouteFile SessionId Int
...@@ -34,6 +38,7 @@ data AppRoute ...@@ -34,6 +38,7 @@ data AppRoute
| RouteFrameVisio SessionId Int | RouteFrameVisio SessionId Int
| RouteFrameWrite SessionId Int | RouteFrameWrite SessionId Int
| Team SessionId Int | Team SessionId Int
| TreeFlat SessionId Int String
| UserPage SessionId Int | UserPage SessionId Int
| Share String Int | Share String Int
...@@ -120,6 +125,7 @@ nodeTypeAppRoute GT.NodeFrameVisio s i = Just $ RouteFrameVisio s i ...@@ -120,6 +125,7 @@ nodeTypeAppRoute GT.NodeFrameVisio s i = Just $ RouteFrameVisio s i
nodeTypeAppRoute _ _ _ = Nothing nodeTypeAppRoute _ _ _ = Nothing
data SessionRoute data SessionRoute
= Tab TabType (Maybe Id) = Tab TabType (Maybe Id)
| Children NodeType Offset Limit (Maybe OrderBy) (Maybe Id) | Children NodeType Offset Limit (Maybe OrderBy) (Maybe Id)
......
...@@ -62,9 +62,7 @@ instance JSON.WriteForeign Session where ...@@ -62,9 +62,7 @@ instance JSON.WriteForeign Session where
JSON.writeImpl { backend, caches: caches', token, treeId, username, userId } JSON.writeImpl { backend, caches: caches', token, treeId, username, userId }
where where
caches' = JSON.writeImpl $ Object.fromFoldable (GUT.first show <$> Map.toUnfoldable caches :: Array (Tuple String NT.CacheState)) caches' = JSON.writeImpl $ Object.fromFoldable (GUT.first show <$> Map.toUnfoldable caches :: Array (Tuple String NT.CacheState))
instance Eq Session where eq = genericEq instance Eq Session where eq = genericEq
instance Show Session where instance Show Session where
show (Session {backend, username}) = username <> "@" <> (cleanBackendUrl backend) show (Session {backend, username}) = username <> "@" <> (cleanBackendUrl backend)
...@@ -74,7 +72,6 @@ cleanBackendUrl (Backend {baseUrl}) = ...@@ -74,7 +72,6 @@ cleanBackendUrl (Backend {baseUrl}) =
$ DST.replace (DST.Pattern "https://") (DST.Replacement "") baseUrl $ DST.replace (DST.Pattern "https://") (DST.Replacement "") baseUrl
instance ToUrl Session SessionRoute where toUrl (Session {backend}) r = backendUrl backend (sessionPath r) instance ToUrl Session SessionRoute where toUrl (Session {backend}) r = backendUrl backend (sessionPath r)
instance ToUrl Session NodePath where toUrl (Session {backend}) np = backendUrl backend (nodePath np) instance ToUrl Session NodePath where toUrl (Session {backend}) np = backendUrl backend (nodePath np)
instance ToUrl Session String where toUrl = sessionUrl instance ToUrl Session String where toUrl = sessionUrl
......
...@@ -2,6 +2,7 @@ module Gargantext.Types where ...@@ -2,6 +2,7 @@ module Gargantext.Types where
import Gargantext.Prelude import Gargantext.Prelude
import Data.Argonaut as Argonaut
import Data.Array as A import Data.Array as A
import Data.Eq.Generic (genericEq) import Data.Eq.Generic (genericEq)
import Data.Generic.Rep (class Generic) import Data.Generic.Rep (class Generic)
...@@ -16,6 +17,7 @@ import Foreign as F ...@@ -16,6 +17,7 @@ import Foreign as F
import Gargantext.Components.Lang (class Translate, Lang(..)) import Gargantext.Components.Lang (class Translate, Lang(..))
import Gargantext.Config.REST (RESTError, AffRESTError) import Gargantext.Config.REST (RESTError, AffRESTError)
import Gargantext.Utils.Glyphicon (classNamePrefix, glyphiconToCharCode) import Gargantext.Utils.Glyphicon (classNamePrefix, glyphiconToCharCode)
import Gargantext.Utils.SimpleJSON (encodeJsonArgonaut)
import GraphQL.Client.Args (class ArgGql) import GraphQL.Client.Args (class ArgGql)
import GraphQL.Client.Variables.TypeName (class VarTypeName) import GraphQL.Client.Variables.TypeName (class VarTypeName)
import Prim.Row (class Union) import Prim.Row (class Union)
...@@ -169,6 +171,8 @@ instance JSON.ReadForeign NodeType where ...@@ -169,6 +171,8 @@ instance JSON.ReadForeign NodeType where
Nothing -> F.fail $ F.ErrorAtProperty s $ F.ForeignError "unknown property" Nothing -> F.fail $ F.ErrorAtProperty s $ F.ForeignError "unknown property"
Just nt -> pure nt Just nt -> pure nt
instance JSON.WriteForeign NodeType where writeImpl = JSON.writeImpl <<< show instance JSON.WriteForeign NodeType where writeImpl = JSON.writeImpl <<< show
instance Argonaut.EncodeJson NodeType where encodeJson = encodeJsonArgonaut
instance ArgGql String NodeType
instance ArgGql NodeType NodeType instance ArgGql NodeType NodeType
instance VarTypeName NodeType where instance VarTypeName NodeType where
varTypeName _ = "NodeType!" varTypeName _ = "NodeType!"
...@@ -237,32 +241,31 @@ prettyNodeType Url_Document = "Document" ...@@ -237,32 +241,31 @@ prettyNodeType Url_Document = "Document"
instance Read NodeType where instance Read NodeType where
read "NodeUser" = Just NodeUser read "Calc" = Just Calc
read "Context" = Just Context
read "Document" = Just Url_Document
read "Individu" = Just Individu
read "Node" = Just Node
read "NodeAnnuaire" = Just Annuaire
read "NodeContact" = Just NodeContact
read "NodeCorpus" = Just Corpus
read "NodeDashboard" = Just Dashboard
read "NodeFile" = Just NodeFile
read "NodeFolder" = Just Folder read "NodeFolder" = Just Folder
read "NodeFolderPrivate" = Just FolderPrivate read "NodeFolderPrivate" = Just FolderPrivate
read "NodeFolderShared" = Just FolderShared
read "NodeFolderPublic" = Just FolderPublic read "NodeFolderPublic" = Just FolderPublic
read "NodeAnnuaire" = Just Annuaire read "NodeFolderShared" = Just FolderShared
read "NodeDashboard" = Just Dashboard read "NodeFrameNotebook" = Just NodeFrameNotebook
read "Document" = Just Url_Document read "NodeFrameVisio" = Just NodeFrameVisio
read "NodeGraph" = Just Graph read "NodeGraph" = Just Graph
read "NodeList" = Just NodeList
read "NodePhylo" = Just Phylo read "NodePhylo" = Just Phylo
read "Individu" = Just Individu
read "Node" = Just Node
read "Nodes" = Just Nodes
read "Context" = Just Context
read "NodeCorpus" = Just Corpus
read "NodeContact" = Just NodeContact
read "Tree" = Just Tree
read "NodeTeam" = Just Team read "NodeTeam" = Just Team
read "NodeList" = Just NodeList
read "NodeTexts" = Just NodeTexts read "NodeTexts" = Just NodeTexts
read "Annuaire" = Just Annuaire read "NodeUser" = Just NodeUser
read "Notes" = Just Notes read "Nodes" = Just Nodes
read "Calc" = Just Calc read "Notes" = Just Notes
read "NodeFrameNotebook" = Just NodeFrameNotebook read "Tree" = Just Tree
read "NodeFrameVisio" = Just NodeFrameVisio
read "NodeFile" = Just NodeFile
-- TODO NodePublic read ? -- TODO NodePublic read ?
read _ = Nothing read _ = Nothing
......
...@@ -4,6 +4,8 @@ import Prelude ...@@ -4,6 +4,8 @@ import Prelude
import Control.Alt ((<|>)) import Control.Alt ((<|>))
import Control.Monad.Except (throwError, withExcept) import Control.Monad.Except (throwError, withExcept)
import Data.Argonaut as Argonaut
import Data.Either (fromRight)
import Data.Generic.Rep as GR import Data.Generic.Rep as GR
import Data.List as L import Data.List as L
import Data.List.Types (NonEmptyList(..)) import Data.List.Types (NonEmptyList(..))
...@@ -96,3 +98,8 @@ instance untaggedSumRepArgument :: ...@@ -96,3 +98,8 @@ instance untaggedSumRepArgument ::
throwJSONError :: forall a. Foreign.ForeignError -> Foreign.F a throwJSONError :: forall a. Foreign.ForeignError -> Foreign.F a
throwJSONError err = throwJSONError err =
throwError $ NonEmptyList $ NonEmpty err L.Nil throwError $ NonEmptyList $ NonEmpty err L.Nil
-- A SimpleJSON.ReadForeign instance should is also compatible with argonaut
encodeJsonArgonaut :: forall a. JSON.WriteForeign a => a -> Argonaut.Json
encodeJsonArgonaut x = fromRight Argonaut.jsonEmptyObject $ Argonaut.jsonParser $ JSON.writeJSON x
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