Commit a6c23958 authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[CodeEditor] vertical sidebar

Not functional yet
parent 3ac42c25
...@@ -16,6 +16,14 @@ ...@@ -16,6 +16,14 @@
display: block; display: block;
height: 500px; height: 500px;
} }
.code-editor .editor .v-divider {
border-left: 1px solid gray;
cursor: sw-resize;
height: 100%;
margin-left: 5px;
margin-right: 5px;
width: 1px;
}
.code-editor .editor .html { .code-editor .editor .html {
flex-grow: 2; flex-grow: 2;
margin-left: 25px; margin-left: 25px;
......
...@@ -13,6 +13,13 @@ ...@@ -13,6 +13,13 @@
color: #000 color: #000
display: block display: block
height: 500px height: 500px
.v-divider
border-left: 1px solid gray
cursor: sw-resize
height: 100%
margin-left: 5px
margin-right: 5px
width: 1px
.html .html
flex-grow: 2 flex-grow: 2
margin-left: 25px margin-left: 25px
......
...@@ -2,22 +2,22 @@ module Gargantext.Components.CodeEditor where ...@@ -2,22 +2,22 @@ module Gargantext.Components.CodeEditor where
import Data.Argonaut.Parser (jsonParser) import Data.Argonaut.Parser (jsonParser)
import Data.Either (either, Either(..)) import Data.Either (either, Either(..))
import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Eq (genericEq)
import Data.Generic.Rep.Show (genericShow)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Data.Nullable (Nullable, null, toMaybe) import Data.Nullable (Nullable, null, toMaybe)
import Data.Tuple (fst, snd) import Data.Tuple (fst)
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import DOM.Simple.Console (log, log2) import DOM.Simple.Console (log, log2)
import DOM.Simple.Types (Element) import DOM.Simple.Types (Element)
import Effect (Effect) import Effect (Effect)
import FFI.Simple ((.=), delay) import FFI.Simple ((.=), delay)
import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Eq (genericEq)
import Data.Generic.Rep.Show (genericShow)
import Reactix as R import Reactix as R
import Reactix.DOM.HTML as H import Reactix.DOM.HTML as H
import Text.Markdown.SlamDown.Parser (parseMd) import Text.Markdown.SlamDown.Parser (parseMd)
import Text.Markdown.SlamDown.Smolder as MD import Text.Markdown.SlamDown.Smolder as MD
import Text.Markdown.SlamDown.Syntax (SlamDownP(..)) import Text.Markdown.SlamDown.Syntax (SlamDownP)
import Text.Smolder.Renderer.String (render) import Text.Smolder.Renderer.String (render)
import Gargantext.Prelude import Gargantext.Prelude
...@@ -113,6 +113,7 @@ codeEditorCpt = R.hooksComponent "G.C.CodeEditor" cpt ...@@ -113,6 +113,7 @@ codeEditorCpt = R.hooksComponent "G.C.CodeEditor" cpt
, on: { input: onEditChange (fst codeType) codeRef htmlRef editorCodeRef error } , on: { input: onEditChange (fst codeType) codeRef htmlRef editorCodeRef error }
} [] } []
] ]
, H.div { className: "v-divider " <> (dividerHidden $ fst viewType) } [ H.text " " ]
, H.div { ref: htmlRef, className: "html " <> (previewHidden $ fst viewType) } [] , H.div { ref: htmlRef, className: "html " <> (previewHidden $ fst viewType) } []
] ]
] ]
...@@ -122,6 +123,10 @@ codeEditorCpt = R.hooksComponent "G.C.CodeEditor" cpt ...@@ -122,6 +123,10 @@ codeEditorCpt = R.hooksComponent "G.C.CodeEditor" cpt
codeHidden Both = "" codeHidden Both = ""
codeHidden _ = "hidden" codeHidden _ = "hidden"
dividerHidden :: ViewType -> String
dividerHidden Both = ""
dividerHidden _ = "hidden"
previewHidden :: ViewType -> String previewHidden :: ViewType -> String
previewHidden Preview = "" previewHidden Preview = ""
previewHidden Both = "" previewHidden Both = ""
......
...@@ -6,7 +6,7 @@ import Data.Tuple.Nested ((/\)) ...@@ -6,7 +6,7 @@ import Data.Tuple.Nested ((/\))
import Effect.Timer (setTimeout) import Effect.Timer (setTimeout)
import Math (min) import Math (min)
import Partial.Unsafe (unsafePartial) import Partial.Unsafe (unsafePartial)
import Prelude ((+), ($), (<>), (<<<), pure, bind, discard, unit, show) import Prelude (bind, discard, pure, show, unit, ($), (+), (<>))
import Reactix as R import Reactix as R
import Reactix.DOM.HTML as H import Reactix.DOM.HTML as H
......
module Gargantext.Components.MarkdownEditor 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.Types (Element)
import Effect (Effect)
import FFI.Simple ((.=), delay)
import Prelude (($), (>>>), Unit, bind, const, discard, identity, pure, unit)
import Reactix as R
import Reactix.DOM.HTML as H
import Text.Markdown.SlamDown.Parser (parseMd)
import Text.Markdown.SlamDown.Smolder as MD
import Text.Markdown.SlamDown.Syntax (SlamDownP(..))
import Text.Smolder.Renderer.String (render)
import Gargantext.Utils.Reactix as R2
type Props =
( md :: String
, nodeId :: Int
)
compileMd' :: forall e. MD.ToMarkupOptions e -> String -> String
compileMd' options input =
either identity (MD.toMarkup' options >>> render)
(parseMd input :: Either String (SlamDownP String))
compileMd :: String -> String
compileMd = compileMd' MD.defaultToMarkupOptions
markdownEditor :: Record Props -> R.Element
markdownEditor p = R.createElement markdownEditorCpt p []
markdownEditorCpt :: R.Component Props
markdownEditorCpt = R.hooksComponent "G.C.MarkdownEditor" cpt
where
cpt {md, nodeId} _ = do
ref <- R.useRef null
editedMd <- R.useState' md
-- 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
Nothing -> pure $ pure unit
Just d -> do
_ <- pure $ (d .= "innerHTML") $ compileMd $ fst editedMd
pure $ pure unit
pure $ H.div { className: "markdown-editor" }
[ H.div { className: "row"}
[ H.div { className: "col-md-5" } [ H.div { ref, className: "html" } []]
, H.div { className: "col-md-5" }
[ H.div { className: "md" }
[ H.textarea { className: "form-control"
, rows: 10
, on: {change: onChange ref editedMd}
} [ H.text $ fst editedMd ]
]
]
]
]
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
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