Commit a1108e5b authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[CodeEditor] generic code editor, not only markdown will be supported

Also, html code element edits text properly (no state, just refs which
prevents cursor jumping).
parent cbe25d37
.markdown-editor {
.code-editor {
display: flex;
width: 100%;
}
.markdown-editor .md {
.code-editor .code {
width: 40%;
}
.markdown-editor .html {
.code-editor .code code {
background-color: #f7f7f9;
color: #000;
display: block;
height: 500px;
}
.code-editor .html {
margin-left: 25px;
padding-left: 25px;
width: 60%;
}
.markdown-editor .html ul li {
.code-editor .html ul li {
list-style: disc !important;
}
.markdown-editor .html ol li {
.code-editor .html ol li {
list-style: decimal !important;
}
......
.markdown-editor
.code-editor
display: flex
width: 100%
.md
.code
code
background-color: #f7f7f9
color: #000
display: block
height: 500px
width: 40%
.html
margin-left: 25px
......
module Gargantext.Components.MarkdownEditor where
module Gargantext.Components.CodeEditor where
import Data.Either (either, Either(..))
import Data.Maybe (Maybe(..))
import Data.Nullable (Nullable, null, toMaybe)
import Data.Tuple (fst)
import Data.Tuple.Nested ((/\))
import DOM.Simple.Console (log2)
import DOM.Simple.Console (log, log2)
import DOM.Simple.Types (Element)
import Effect (Effect)
import FFI.Simple ((.=), delay)
......@@ -19,9 +19,12 @@ import Text.Smolder.Renderer.String (render)
import Gargantext.Utils.Reactix as R2
data CodeType = Markdown
type Props =
( md :: String
, nodeId :: Int
( code :: String
, codeType :: CodeType
, onChange :: String -> Effect Unit
)
compileMd' :: forall e. MD.ToMarkupOptions e -> String -> String
......@@ -32,37 +35,61 @@ compileMd' options input =
compileMd :: String -> String
compileMd = compileMd' MD.defaultToMarkupOptions
markdownEditor :: Record Props -> R.Element
markdownEditor p = R.createElement markdownEditorCpt p []
codeEditor :: Record Props -> R.Element
codeEditor p = R.createElement codeEditorCpt p []
markdownEditorCpt :: R.Component Props
markdownEditorCpt = R.hooksComponent "G.C.MarkdownEditor" cpt
codeEditorCpt :: R.Component Props
codeEditorCpt = R.hooksComponent "G.C.CodeEditor" cpt
where
cpt {md, nodeId} _ = do
ref <- R.useRef null
editedMd <- R.useState' md
cpt {code, codeType, onChange} _ = do
htmlRef <- R.useRef null
codeRef <- R.useRef null
editorCodeRef <- R.useRef code
-- Note: delay is necessary here, otherwise initially the HTML won't get
-- rendered (mDiv is still null)
R.useEffect $ delay unit $ \_ -> do
let mDiv = toMaybe $ R.readRef ref
case mDiv of
let mHtmlEl = toMaybe $ R.readRef htmlRef
case mHtmlEl of
Nothing -> pure $ pure unit
Just htmlEl -> do
_ <- pure $ (htmlEl .= "innerHTML") $ compileMd code
pure $ pure unit
R.useEffectOnce $ delay unit $ \_ -> do
let mCodeEl = toMaybe $ R.readRef codeRef
case mCodeEl of
Nothing -> pure $ pure unit
Just d -> do
_ <- pure $ (d .= "innerHTML") $ compileMd $ fst editedMd
Just codeEl -> do
_ <- pure $ (codeEl .= "innerText") code
pure $ pure unit
pure $ H.div { className: "markdown-editor" } [
H.div { className: "md" } [
H.textarea { className: "form-control"
, rows: 30
, on: {change: onChange ref editedMd} } [ H.text $ fst editedMd ]
pure $ H.div { className: "code-editor" } [
H.div { className: "code" } [
H.code { className: ""
, contentEditable: "true"
, ref: codeRef
, rows: 30
, on: { change: onEditChange codeRef htmlRef editorCodeRef
, input: onEditChange codeRef htmlRef editorCodeRef }
} []
]
, H.div { ref, className: "html" } []
, H.div { ref: htmlRef, className: "html" } []
]
onChange :: forall e. R.Ref (Nullable Element) -> R.State String -> e -> Effect Unit
onChange ref (_ /\ setEditedMd) e = do
setEditedMd $ const value
where
value = R2.unsafeEventValue e
onEditChange :: forall e. R.Ref (Nullable Element) -> R.Ref (Nullable Element) -> R.Ref String -> e -> Effect Unit
onEditChange codeRef htmlRef editorCodeRef e = do
log2 "[onChange] e" e
let mCode = toMaybe $ R.readRef codeRef
case mCode of
Nothing -> log "[onChange] mCode = Nothing"
Just code -> do
R.setRef editorCodeRef $ R2.innerText code
pure unit
let mHtml = toMaybe $ R.readRef htmlRef
case mHtml of
Nothing -> pure unit
Just html -> do
_ <- pure $ (html .= "innerHTML") $ compileMd $ R.readRef editorCodeRef
pure unit
pure unit
......@@ -4,12 +4,13 @@ import Prelude ((<<<))
import Data.Argonaut (class DecodeJson, decodeJson, (.:), (.:?))
import Data.Array (head)
import Data.Maybe (Maybe(..))
import DOM.Simple.Console (log2)
import Effect.Aff (Aff, throwError)
import Effect.Exception (error)
import Reactix as R
import Reactix.DOM.HTML as H
import Gargantext.Prelude
import Gargantext.Components.MarkdownEditor (markdownEditor)
import Gargantext.Components.CodeEditor as CE
import Gargantext.Components.Node (NodePoly(..), HyperdataList)
import Gargantext.Types (NodeType(..), AffTableResult)
import Gargantext.Routes (SessionRoute(NodeAPI, Children))
......@@ -26,11 +27,13 @@ corpusLayoutCpt = R.staticComponent "G.P.Corpus.corpusLayout" cpt
cpt {nodeId} _ =
H.div {}
[
markdownEditor {md, nodeId}
CE.codeEditor {code, codeType: CE.Markdown, onChange}
--H.iframe { src: gargMd , width: "100%", height: "100%", style: {"border-style": "none"}} []
]
gargMd = "https://hackmd.iscpif.fr/g9Aah4iwQtCayIzsKQjA0Q#"
md = "# Hello world"
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
......
......@@ -7,4 +7,9 @@ function addRootElement(rootElem) {
);
}
function getSelection(_u) {
return window.getSelection();
}
exports._addRootElement = addRootElement;
exports._getSelection = getSelection;
......@@ -16,7 +16,7 @@ import Effect (Effect)
import Effect.Aff (Aff, launchAff, launchAff_, killFiber)
import Effect.Class (liftEffect)
import Effect.Exception (error)
import Effect.Uncurried (EffectFn1, runEffectFn1, mkEffectFn1, mkEffectFn2)
import Effect.Uncurried (EffectFn1, runEffectFn1, mkEffectFn1, EffectFn2, runEffectFn2, mkEffectFn2)
import FFI.Simple ((..), (...), defineProperty, delay, args2, args3)
import Partial.Unsafe (unsafePartial)
import React (class ReactPropFields, Children, ReactClass, ReactElement)
......@@ -232,3 +232,13 @@ row children = H.div { className: "row" } children
col12 :: Array R.Element -> R.Element
col12 children = H.div { className: "col-md-12" } children
innerText :: DOM.Element -> String
innerText e = e .. "innerText"
foreign import data Selection :: Type
getSelection :: Unit -> Effect Selection
getSelection = runEffectFn1 _getSelection
foreign import _getSelection :: EffectFn1 Unit Selection
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