Commit df5c9252 authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[CodeEditor] support corpus hypertext fields with markdown/json etc

parent 5d8de4c3
...@@ -57,7 +57,7 @@ appCpt = R.hooksComponent "G.C.App.app" cpt where ...@@ -57,7 +57,7 @@ appCpt = R.hooksComponent "G.C.App.app" cpt where
Home -> forested $ homeLayout EN Home -> forested $ homeLayout EN
Login -> login { sessions, backends, visible: showLogin } Login -> login { sessions, backends, visible: showLogin }
Folder sid _ -> withSession sid $ \_ -> forested (folder {}) Folder sid _ -> withSession sid $ \_ -> forested (folder {})
Corpus sid nodeId -> withSession sid $ \_ -> forested $ corpusLayout { nodeId } Corpus sid nodeId -> withSession sid $ \session -> forested $ corpusLayout { nodeId, session }
Texts sid nodeId -> withSession sid $ \session -> forested $ textsLayout { nodeId, session, frontends } Texts sid nodeId -> withSession sid $ \session -> forested $ textsLayout { nodeId, session, frontends }
Lists sid nodeId -> withSession sid $ \session -> forested $ listsLayout { nodeId, session } Lists sid nodeId -> withSession sid $ \session -> forested $ listsLayout { nodeId, session }
Dashboard sid _nodeId -> withSession sid $ \session -> forested $ dashboardLayout {} Dashboard sid _nodeId -> withSession sid $ \session -> forested $ dashboardLayout {}
......
module Gargantext.Components.Nodes.Corpus where module Gargantext.Components.Nodes.Corpus where
import Prelude ((<<<)) import Data.Argonaut (class DecodeJson, encodeJson)
import Data.Argonaut (class DecodeJson, decodeJson, (.:), (.:?))
import Data.Array (head) import Data.Array (head)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import DOM.Simple.Console (log2) import DOM.Simple.Console (log2)
...@@ -11,78 +10,79 @@ import Reactix as R ...@@ -11,78 +10,79 @@ import Reactix as R
import Reactix.DOM.HTML as H import Reactix.DOM.HTML as H
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Components.CodeEditor as CE import Gargantext.Components.CodeEditor as CE
import Gargantext.Components.Node (NodePoly(..), HyperdataList) import Gargantext.Components.Node (NodePoly(..), HyperdataList)
import Gargantext.Components.Nodes.Corpus.Types
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Routes (SessionRoute(NodeAPI, Children)) import Gargantext.Routes (SessionRoute(NodeAPI, Children))
import Gargantext.Sessions (Session, get) import Gargantext.Sessions (Session, get)
import Gargantext.Types (NodeType(..), AffTableResult) import Gargantext.Types (NodeType(..), AffTableResult)
import Gargantext.Utils.Reactix as R2
type Props = ( nodeId :: Int ) type Props = (
nodeId :: Int
, session :: Session
)
corpusLayout :: Record Props -> R.Element corpusLayout :: Record Props -> R.Element
corpusLayout props = R.createElement corpusLayoutCpt props [] corpusLayout props = R.createElement corpusLayoutCpt props []
corpusLayoutCpt :: R.Component Props corpusLayoutCpt :: R.Component Props
corpusLayoutCpt = R.hooksComponent "G.P.Corpus.corpusLayout" cpt corpusLayoutCpt = R.hooksComponent "G.C.N.C.corpusLayout" cpt
where
cpt props@{nodeId, session} _ =
useLoader props loadCorpus' $
\corpus -> corpusLayoutView {corpus, nodeId, session}
type ViewProps = (
corpus :: NodePoly CorpusHyperdata
| Props
)
corpusLayoutView :: Record ViewProps -> R.Element
corpusLayoutView props = R.createElement corpusLayoutViewCpt props []
corpusLayoutViewCpt :: R.Component ViewProps
corpusLayoutViewCpt = R.hooksComponent "G.C.N.C.corpusLayoutView" cpt
where where
cpt {nodeId} _ = do cpt {corpus: (NodePoly {hyperdata: CorpusHyperdata {fields}}), nodeId, session} _ = do
pure $ H.div {} pure $ H.div {}
[ (corpusFieldCodeEditor {nodeId, session} <$> fields)
CE.codeEditor {code, defaultCodeType: CE.Markdown, onChange}
--H.iframe { src: gargMd , width: "100%", height: "100%", style: {"border-style": "none"}} [] --H.iframe { src: gargMd , width: "100%", height: "100%", style: {"border-style": "none"}} []
]
--gargMd = "https://hackmd.iscpif.fr/g9Aah4iwQtCayIzsKQjA0Q#" --gargMd = "https://hackmd.iscpif.fr/g9Aah4iwQtCayIzsKQjA0Q#"
code = "# Hello world\n\n## subtitle\n\n- item 1\n- item 2\n\n1. num 1\n2. num 2\n\n[purescript link](https://purescript.org)"
onChange c = do
log2 "[corpusLayoutCpt] c" c
newtype CorpusInfo =
CorpusInfo
{ title :: String
, desc :: String
, query :: String
, authors :: String
, chart :: (Maybe (Array Number))
, totalRecords :: Int }
hyperdataDefault :: CorpusInfo corpusFieldCodeEditor :: Record LoadProps -> CorpusField CorpusFieldType -> R.Element
hyperdataDefault = corpusFieldCodeEditor p (CorpusField {name, typ}) =
CorpusInfo H.div { className: "row panel panel-default" } [
{ title : "Default title" H.div { className: "panel-heading" } [ H.text name ]
, desc : " Default desc" , H.div { className: "panel-body" } [
, query : " Default Query" corpusFieldCodeEditor' typ
, authors : " Author(s): default" ]
, chart : Nothing ]
, totalRecords : 0 } corpusFieldCodeEditor' :: CorpusFieldType -> R.Element
corpusFieldCodeEditor' (Markdown {text}) =
corpusInfoDefault :: NodePoly CorpusInfo CE.codeEditor {code: text, defaultCodeType: CE.Markdown, onChange}
corpusInfoDefault = where
NodePoly onChange c = do
{ id : 0 log2 "[corpusFieldCodeEditor'] Markdown c" c
, typename : 0 corpusFieldCodeEditor' (JSON j) = do
, userId : 0 CE.codeEditor {code, defaultCodeType: CE.JSON, onChange}
, parentId : 0 where
, name : "Default name" code = R2.stringify (encodeJson j) 2
, date : " Default date" onChange c = do
, hyperdata : hyperdataDefault } log2 "[corpusFieldCodeEditor'] JSON c" c
instance decodeCorpusInfo :: DecodeJson CorpusInfo where type LoadProps = (
decodeJson json = do nodeId :: Int
obj <- decodeJson json , session :: Session
title <- obj .: "title" )
desc <- obj .: "desc"
query <- obj .: "query"
authors <- obj .: "authors"
chart <- obj .:? "chart"
let totalRecords = 47361 -- TODO
pure $ CorpusInfo {title, desc, query, authors, chart, totalRecords}
type CorpusData = { corpusId :: Int loadCorpus' :: Record LoadProps -> Aff (NodePoly CorpusHyperdata)
, corpusNode :: NodePoly CorpusInfo loadCorpus' {nodeId, session} = get session $ NodeAPI Corpus (Just nodeId) ""
, defaultListId :: Int}
loadCorpus :: { session :: Session, nodeId :: Int } -> Aff CorpusData loadCorpus :: Record LoadProps -> Aff CorpusData
loadCorpus {session, nodeId: listId} = do loadCorpus {nodeId, session} = do
-- fetch corpus via lists parentId -- fetch corpus via lists parentId
(NodePoly {parentId: corpusId} :: NodePoly {}) <- get session nodePolyRoute (NodePoly {parentId: corpusId} :: NodePoly {}) <- get session nodePolyRoute
corpusNode <- get session $ corpusNodeRoute corpusId "" corpusNode <- get session $ corpusNodeRoute corpusId ""
...@@ -93,6 +93,6 @@ loadCorpus {session, nodeId: listId} = do ...@@ -93,6 +93,6 @@ loadCorpus {session, nodeId: listId} = do
Nothing -> Nothing ->
throwError $ error "Missing default list" throwError $ error "Missing default list"
where where
nodePolyRoute = NodeAPI Corpus (Just listId) "" nodePolyRoute = NodeAPI Corpus (Just nodeId) ""
corpusNodeRoute = NodeAPI Corpus <<< Just corpusNodeRoute = NodeAPI Corpus <<< Just
defaultListIdsRoute = Children NodeList 0 1 Nothing <<< Just defaultListIdsRoute = Children NodeList 0 1 Nothing <<< Just
module Gargantext.Components.Nodes.Corpus.Types where
import Data.Argonaut (class DecodeJson, decodeJson, (.:), (.:?))
import Data.Either (Either(..))
import Data.Maybe (Maybe)
import Gargantext.Prelude
import Gargantext.Components.Node (NodePoly)
type Author = String
type Description = String
type Query = String
type Tag = String
type Title = String
type MarkdownText = String
newtype CorpusHyperdata =
CorpusHyperdata
{
fields :: Array (CorpusField CorpusFieldType)
}
instance decodeCorpusHyperdata :: DecodeJson CorpusHyperdata where
decodeJson json = do
obj <- decodeJson json
fields <- obj .: "fields"
pure $ CorpusHyperdata {fields}
newtype CorpusField a = CorpusField {
name :: String
, typ :: a
}
data CorpusFieldType = JSON {
authors :: Author
, desc :: Description
, query :: Query
, tag :: Tag
, title :: Title
}
| Markdown {
tag :: Tag
, text :: MarkdownText
}
instance decodeCorpusField :: DecodeJson (CorpusField CorpusFieldType) where
decodeJson json = do
obj <- decodeJson json
name <- obj .: "name"
type_ <- obj .: "type"
data_ <- obj .: "data"
typ <- case type_ of
"JSON" -> do
authors <- data_ .: "authors"
desc <- data_ .: "desc"
query <- data_ .: "query"
tag <- data_ .: "tag"
title <- data_ .: "title"
pure $ JSON {authors, desc, query, tag, title}
"Markdown" -> do
tag <- data_ .: "tag"
text <- data_ .: "text"
pure $ Markdown {tag, text}
_ -> Left $ "Unsupported 'type' " <> type_
pure $ CorpusField {name, typ}
newtype CorpusInfo =
CorpusInfo
{ title :: String
, desc :: String
, query :: String
, authors :: String
, chart :: (Maybe (Array Number))
, totalRecords :: Int }
instance decodeCorpusInfo :: DecodeJson CorpusInfo where
decodeJson json = do
obj <- decodeJson json
title <- obj .: "title"
desc <- obj .: "desc"
query <- obj .: "query"
authors <- obj .: "authors"
chart <- obj .:? "chart"
let totalRecords = 47361 -- TODO
pure $ CorpusInfo {title, desc, query, authors, chart, totalRecords}
type CorpusData = { corpusId :: Int
, corpusNode :: NodePoly CorpusInfo
, defaultListId :: Int}
...@@ -3,7 +3,8 @@ module Gargantext.Components.Nodes.Lists where ...@@ -3,7 +3,8 @@ module Gargantext.Components.Nodes.Lists where
import Reactix as R import Reactix as R
-------------------------------------------------------- --------------------------------------------------------
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Components.Nodes.Corpus (CorpusInfo(..), loadCorpus) import Gargantext.Components.Nodes.Corpus (loadCorpus)
import Gargantext.Components.Nodes.Corpus.Types (CorpusInfo(..))
import Gargantext.Components.Node (NodePoly(..)) import Gargantext.Components.Node (NodePoly(..))
import Gargantext.Components.Table as Table import Gargantext.Components.Table as Table
import Gargantext.Hooks.Loader (useLoader) import Gargantext.Hooks.Loader (useLoader)
......
...@@ -6,7 +6,7 @@ import Data.Tuple.Nested ((/\)) ...@@ -6,7 +6,7 @@ import Data.Tuple.Nested ((/\))
import Reactix as R import Reactix as R
import Gargantext.Components.NgramsTable as NT import Gargantext.Components.NgramsTable as NT
import Gargantext.Components.Tab as Tab import Gargantext.Components.Tab as Tab
import Gargantext.Components.Nodes.Corpus (CorpusData) import Gargantext.Components.Nodes.Corpus.Types (CorpusData)
import Gargantext.Components.Nodes.Corpus.Chart.Metrics (metrics) import Gargantext.Components.Nodes.Corpus.Chart.Metrics (metrics)
import Gargantext.Components.Nodes.Corpus.Chart.Pie (pie, bar) import Gargantext.Components.Nodes.Corpus.Chart.Pie (pie, bar)
import Gargantext.Components.Nodes.Corpus.Chart.Tree (tree) import Gargantext.Components.Nodes.Corpus.Chart.Tree (tree)
......
...@@ -12,7 +12,8 @@ import Reactix.DOM.HTML as H ...@@ -12,7 +12,8 @@ import Reactix.DOM.HTML as H
import Gargantext.Components.DocsTable as DT import Gargantext.Components.DocsTable as DT
import Gargantext.Components.Loader (loader) import Gargantext.Components.Loader (loader)
import Gargantext.Components.Node (NodePoly(..)) import Gargantext.Components.Node (NodePoly(..))
import Gargantext.Components.Nodes.Corpus (CorpusData, CorpusInfo(..), loadCorpus) import Gargantext.Components.Nodes.Corpus (loadCorpus)
import Gargantext.Components.Nodes.Corpus.Types (CorpusData, CorpusInfo(..))
import Gargantext.Components.Nodes.Corpus.Chart.Histo (histo) import Gargantext.Components.Nodes.Corpus.Chart.Histo (histo)
import Gargantext.Components.Tab as Tab import Gargantext.Components.Tab as Tab
import Gargantext.Components.Table as Table import Gargantext.Components.Table as Table
......
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