Skip to content
Projects
Groups
Snippets
Help
Loading...
Help
Submit feedback
Contribute to GitLab
Sign in
Toggle navigation
P
purescript-gargantext
Project
Project
Details
Activity
Releases
Cycle Analytics
Repository
Repository
Files
Commits
Branches
Tags
Contributors
Graph
Compare
Charts
Issues
0
Issues
0
List
Board
Labels
Milestones
Merge Requests
0
Merge Requests
0
CI / CD
CI / CD
Pipelines
Jobs
Schedules
Charts
Wiki
Wiki
Snippets
Snippets
Members
Members
Collapse sidebar
Close sidebar
Activity
Graph
Charts
Create a new issue
Jobs
Commits
Issue Boards
Open sidebar
Grégoire Locqueville
purescript-gargantext
Commits
4209481a
Commit
4209481a
authored
Oct 15, 2019
by
Nicolas Pouillard
Browse files
Options
Browse Files
Download
Email Patches
Plain Diff
NgramsTable: fix and refactor (reactix/thermite, session, loader...)
parent
992172f4
Changes
3
Show whitespace changes
Inline
Side-by-side
Showing
3 changed files
with
92 additions
and
96 deletions
+92
-96
NgramsTable.purs
src/Gargantext/Components/NgramsTable.purs
+54
-46
Core.purs
src/Gargantext/Components/NgramsTable/Core.purs
+15
-27
Document.purs
src/Gargantext/Components/Nodes/Corpus/Document.purs
+23
-23
No files found.
src/Gargantext/Components/NgramsTable.purs
View file @
4209481a
...
...
@@ -26,7 +26,7 @@ import Data.Tuple.Nested ((/\))
import Effect (Effect)
import Reactix as R
import Reactix.DOM.HTML as H
import React (React
Element
)
import React (React
Class, ReactElement, Children
)
import React.DOM (a, i, input, li, span, text, ul)
import React.DOM.Props (_type, checked, className, onChange, onClick, style)
import React.DOM.Props as DOM
...
...
@@ -37,14 +37,14 @@ import Gargantext.Types
, readTermSize, termLists, termSizes)
import Gargantext.Components.AutoUpdate (autoUpdateElt)
import Gargantext.Components.NgramsTable.Core
( CoreState,
LoadedNgramsTableProps,
NgramsElement(..), NgramsPatch(..)
( CoreState, NgramsElement(..), NgramsPatch(..)
, NgramsTable, NgramsTerm, PageParams, Replace(..), Versioned(..)
, VersionedNgramsTable, _NgramsElement, _NgramsTable, _children
, _list, _ngrams, _occurrences, _root, addNewNgram, applyNgramsTablePatch
, applyPatchSet, commitPatch, convOrderBy, initialPageParams, loadNgramsTable
, patchSetFromMap, replace, singletonNgramsTablePatch )
import Gargantext.Components.Loader (loader)
import Gargantext.Components.Table as T
import Gargantext.Hooks.Loader (useLoader2)
import Gargantext.Sessions (Session)
import Gargantext.Utils.Reactix as R2
...
...
@@ -86,17 +86,15 @@ data Action
type Dispatch = Action -> Effect Unit
tableContainer :: { pa
geParams ::
PageParams
tableContainer :: { pa
th :: R.State
PageParams
, dispatch :: Dispatch
, setPath :: R2.Setter PageParams
, ngramsParent :: Maybe NgramsTerm
, ngramsChildren :: Map NgramsTerm Boolean
, ngramsTable :: NgramsTable
}
-> Record T.TableContainerProps -> R.Element
tableContainer { pa
geParams
tableContainer { pa
th: {searchQuery, termListFilter, termSizeFilter} /\ setPath
, dispatch
, setPath
, ngramsParent
, ngramsChildren
, ngramsTable: ngramsTableCache
...
...
@@ -116,26 +114,26 @@ tableContainer { pageParams
, name: "search"
, placeholder: "Search"
, type: "value"
, value:
pageParams.
searchQuery
, value: searchQuery
, on: {input: \e -> setSearchQuery (R2.unsafeEventValue e)}}
, H.div {} (
if A.null props.tableBody &&
pageParams.
searchQuery /= "" then [
if A.null props.tableBody && searchQuery /= "" then [
H.button { className: "btn btn-primary"
, on: {click: const $ dispatch $ AddNewNgram
pageParams.
searchQuery}}
[ H.text ("Add " <>
pageParams.
searchQuery) ]
, on: {click: const $ dispatch $ AddNewNgram searchQuery}}
[ H.text ("Add " <> searchQuery) ]
] else [])]
, H.div {className: "col-md-2", style: {marginTop : "6px"}}
[ H.li {className: " list-group-item"}
[ R2.select { id: "picklistmenu"
, className: "form-control custom-select"
, value: (maybe "" show
pageParams.
termListFilter)
, value: (maybe "" show termListFilter)
, on: {change: (\e -> setTermListFilter $ readTermList $ R2.unsafeEventValue e)}}
(map optps1 termLists)]]
, H.div {className: "col-md-2", style: {marginTop : "6px"}}
[ H.li {className: "list-group-item"}
[ R2.select {id: "picktermtype"
, className: "form-control custom-select"
, value: (maybe "" show
pageParams.
termSizeFilter)
, value: (maybe "" show termSizeFilter)
, on: {change: (\e -> setTermSizeFilter $ readTermSize $ R2.unsafeEventValue e)}}
(map optps1 termSizes)]]
, H.div {className: "col-md-4", style: {marginTop : "6px", marginBottom : "1px"}}
...
...
@@ -168,29 +166,32 @@ tableContainer { pageParams
[ H.thead {className: "tableHeader"} [props.tableHead]
, H.tbody {} props.tableBody]]]]]]
where
setPageParams f = setPath (const $ f pageParams
)
setSearchQuery x = setPa
geParams
$ _ { searchQuery = x }
setTermListFilter x = setPa
geParams
$ _ { termListFilter = x }
setTermSizeFilter x = setPa
geParams
$ _ { termSizeFilter = x }
-- WHY setPath f = origSetPageParams (const $ f path
)
setSearchQuery x = setPa
th
$ _ { searchQuery = x }
setTermListFilter x = setPa
th
$ _ { termListFilter = x }
setTermSizeFilter x = setPa
th
$ _ { termSizeFilter = x }
toggleMap :: forall a. a -> Maybe a -> Maybe a
toggleMap _ (Just _) = Nothing
toggleMap b Nothing = Just b
-- NEXT
data Action'
= SetParentResetChildren' (Maybe NgramsTerm)
| ToggleChild' (Maybe NgramsTerm) NgramsTerm
| Refresh'
-- NEXT
type Props =
( session :: Session
, tabNgramType :: CTabNgramType
( tabNgramType :: CTabNgramType
, path :: R.State PageParams
, versioned :: VersionedNgramsTable )
-- NEXT
loadedNgramsTable :: Record Props -> R.Element
loadedNgramsTable props = R.createElement loadedNgramsTableCpt props []
-- NEXT
loadedNgramsTableCpt :: R.Component Props
loadedNgramsTableCpt = R.hooksComponent "G.C.NgramsTable.loadedNgramsTable" cpt
where
...
...
@@ -206,8 +207,14 @@ loadedNgramsTableCpt = R.hooksComponent "G.C.NgramsTable.loadedNgramsTable" cpt
performNgramsAction (ToggleChild' b c) = pure -- TODO
performNgramsAction Refresh' = pure -- TODO
ngramsTableSpec :: Session -> CTabNgramType -> R2.Setter PageParams -> Thermite.Spec State (Record LoadedNgramsTableProps) Action
ngramsTableSpec session ntype setPath = Thermite.simpleSpec performAction render
type LoadedNgramsTableProps =
( tabNgramType :: CTabNgramType
, path :: R.State PageParams
, versioned :: VersionedNgramsTable
)
loadedNgramsTableSpec :: Thermite.Spec State (Record LoadedNgramsTableProps) Action
loadedNgramsTableSpec = Thermite.simpleSpec performAction render
where
setParentResetChildren :: Maybe NgramsTerm -> State -> State
setParentResetChildren p = _ { ngramsParent = p, ngramsChildren = mempty }
...
...
@@ -217,49 +224,49 @@ ngramsTableSpec session ntype setPath = Thermite.simpleSpec performAction render
modifyState_ $ setParentResetChildren p
performAction (ToggleChild b c) _ _ =
modifyState_ $ _ngramsChildren <<< at c %~ toggleMap b
performAction Refresh {path:
{nodeId, listIds, tabType}
} {ngramsVersion} = do
commitPatch
session {nodeId, listIds, tabType}
(Versioned {version: ngramsVersion, data: mempty})
performAction (SetTermListItem n pl) {path:
{nodeId, listIds, tabType}
} {ngramsVersion} =
commitPatch
session {nodeId, listIds, tabType}
(Versioned {version: ngramsVersion, data: pt})
performAction Refresh {path:
path /\ _
} {ngramsVersion} = do
commitPatch
path
(Versioned {version: ngramsVersion, data: mempty})
performAction (SetTermListItem n pl) {path:
path /\ _, tabNgramType
} {ngramsVersion} =
commitPatch
path
(Versioned {version: ngramsVersion, data: pt})
where
pe = NgramsPatch { patch_list: pl, patch_children: mempty }
pt = singletonNgramsTablePatch
nt
ype n pe
pt = singletonNgramsTablePatch
tabNgramT
ype n pe
performAction AddTermChildren _ {ngramsParent: Nothing} =
-- impossible but harmless
pure unit
performAction AddTermChildren {path:
{nodeId, listIds, tabType}
}
performAction AddTermChildren {path:
path /\ _, tabNgramType
}
{ ngramsParent: Just parent
, ngramsChildren
, ngramsVersion
} = do
modifyState_ $ setParentResetChildren Nothing
commitPatch
session {nodeId, listIds, tabType}
(Versioned {version: ngramsVersion, data: pt})
commitPatch
path
(Versioned {version: ngramsVersion, data: pt})
where
pc = patchSetFromMap ngramsChildren
pe = NgramsPatch { patch_list: mempty, patch_children: pc }
pt = singletonNgramsTablePatch
nt
ype parent pe
performAction (AddNewNgram ngram) {path:
{listIds, nodeId, tabType}
} {ngramsVersion} =
commitPatch
session {listIds, nodeId, tabType}
(Versioned {version: ngramsVersion, data: pt})
pt = singletonNgramsTablePatch
tabNgramT
ype parent pe
performAction (AddNewNgram ngram) {path:
path /\ _, tabNgramType
} {ngramsVersion} =
commitPatch
path
(Versioned {version: ngramsVersion, data: pt})
where
pt = addNewNgram
nt
ype ngram CandidateTerm
pt = addNewNgram
tabNgramT
ype ngram CandidateTerm
render :: Thermite.Render State (Record LoadedNgramsTableProps) Action
render dispatch { path: pa
geParams
,
load
ed: Versioned { data: initTable } }
render dispatch { path: pa
th@({params} /\ setPath)
,
version
ed: Versioned { data: initTable } }
{ ngramsTablePatch, ngramsParent, ngramsChildren }
_reactChildren =
[ autoUpdateElt { duration: 3000, effect: dispatch Refresh }
, R2.scuff $ T.table { rows, params, container, colNames, totalRecords}
, R2.scuff $ T.table { params: params /\ setParams -- TODO-LENS
, rows, container, colNames, totalRecords}
]
where
totalRecords = 47361 -- TODO
colNames = T.ColumnName <$> ["Map", "Stop", "Terms", "Score (Occurrences)"] -- see convOrderBy
container = tableContainer {pa
geParams, setPa
th, dispatch, ngramsParent, ngramsChildren, ngramsTable}
container = tableContainer {path, dispatch, ngramsParent, ngramsChildren, ngramsTable}
setParams f = setPath $ \p@{params: ps} -> p {params = f ps}
params = pageParams.params /\ setParams
ngramsTable = applyNgramsTablePatch ngramsTablePatch initTable
orderWith =
case convOrderBy <$> pa
geParams.pa
rams.orderBy of
case convOrderBy <$> params.orderBy of
Just ScoreAsc -> A.sortWith \x -> (snd x) ^. _NgramsElement <<< _occurrences
Just ScoreDesc -> A.sortWith \x -> Down $ (snd x) ^. _NgramsElement <<< _occurrences
_ -> identity -- the server ordering is enough here
...
...
@@ -289,11 +296,12 @@ ngramsTableSpec session ntype setPath = Thermite.simpleSpec performAction render
, delete: false
}
-- ngramsTableClass :: Session -> CTabNgramType -> R2.Setter PageParams -> Loader.InnerClass PageParams (Versioned NgramsTable)
-- ngramsTableClass session ct setPath = createClass "NgramsTable" (ngramsTableSpec session ct setPath) initialState
loadedNgramsTableClass :: ReactClass { children :: Children | LoadedNgramsTableProps }
loadedNgramsTableClass = Thermite.createClass "LoadedNgramsNgramsTable"
loadedNgramsTableSpec (\{versioned} -> initialState versioned)
-- ngramsTable' :: Session -> CTabNgramType -> R2.Setter PageParams ->
Record LoadedNgramsTableProps -> R.Element
-- ngramsTable' session ct setPath props = R2.createElement' (ngramsTableClass session ct setPath
) props []
loadedNgramsTable' ::
Record LoadedNgramsTableProps -> R.Element
loadedNgramsTable' props = R2.createElement' (loadedNgramsTableClass
) props []
type MainNgramsTableProps =
( nodeId :: Int
...
...
@@ -311,9 +319,9 @@ mainNgramsTableCpt :: R.Component MainNgramsTableProps
mainNgramsTableCpt = R.hooksComponent "MainNgramsTable" cpt
where
cpt {nodeId, defaultListId, tabType, session, tabNgramType} _ = do
path <- R.useState' $ initialPageParams session nodeId [defaultListId] tabType
useLoader2 path (loadNgramsTable session) $
\versioned -> loadedNgramsTable {session, tabNgramType, path, versioned}
path
/\ setPath
<- R.useState' $ initialPageParams session nodeId [defaultListId] tabType
let paint versioned = loadedNgramsTable' {tabNgramType, path: path /\ setPath, versioned}
pure $ loader path loadNgramsTable paint
type NgramsDepth = {ngrams :: NgramsTerm, depth :: Int}
type NgramsClick = NgramsDepth -> Maybe (Effect Unit)
...
...
src/Gargantext/Components/NgramsTable/Core.purs
View file @
4209481a
...
...
@@ -16,12 +16,9 @@ module Gargantext.Components.NgramsTable.Core
, Versioned(..)
, VersionedNgramsTable
, CoreState
, LoadedNgramsTableProps
, highlightNgrams
, initialPageParams
, loadNgramsTable
, ngramsLoader
, ngramsLoaderClass
, convOrderBy
, Replace(..) -- Ideally we should keep the constructors hidden
, replace
...
...
@@ -86,7 +83,6 @@ import Partial (crashWith)
import Partial.Unsafe (unsafePartial)
import Gargantext.Components.Table as T
import Gargantext.Components.OldLoader as Loader
import Gargantext.Ends (url)
import Gargantext.Routes (SessionRoute(..))
import Gargantext.Sessions (Session, get, put, post)
...
...
@@ -98,6 +94,7 @@ type CoreParams s =
-- ^ This node can be a corpus or contact.
, listIds :: Array Int
, tabType :: TabType
, session :: Session
| s
}
...
...
@@ -107,7 +104,6 @@ type PageParams =
, searchQuery :: String
, termListFilter :: Maybe TermList -- Nothing means all
, termSizeFilter :: Maybe TermSize -- Nothing means all
, session :: Session
)
initialPageParams :: Session -> Int -> Array Int -> TabType -> PageParams
...
...
@@ -564,41 +560,41 @@ type CoreState s =
| s
}
postNewNgrams :: forall s.
Session ->
Array NgramsTerm -> Maybe TermList -> CoreParams s -> Aff Unit
postNewNgrams
session newNgrams mayList {nodeId, listIds, tabType
} =
postNewNgrams :: forall s. Array NgramsTerm -> Maybe TermList -> CoreParams s -> Aff Unit
postNewNgrams
newNgrams mayList {nodeId, listIds, tabType, session
} =
when (not (A.null newNgrams)) $ do
(_ :: Array Unit) <- post session p newNgrams
pure unit
where p = PutNgrams tabType (head listIds) mayList (Just nodeId)
postNewElems :: forall s.
Session ->
NewElems -> CoreParams s -> Aff Unit
postNewElems
session
newElems params = void $ traverseWithIndex postNewElem newElems
postNewElems :: forall s. NewElems -> CoreParams s -> Aff Unit
postNewElems newElems params = void $ traverseWithIndex postNewElem newElems
where
postNewElem ngrams list = postNewNgrams
session
[ngrams] (Just list) params
postNewElem ngrams list = postNewNgrams [ngrams] (Just list) params
addNewNgram :: CTabNgramType -> NgramsTerm -> TermList -> NgramsTablePatch
addNewNgram ntype ngrams list = { ngramsPatches: mempty
, ngramsNewElems: Map.singleton (normNgram ntype ngrams) list }
putNgramsPatches ::
Session -> {nodeId :: Int, listIds :: Array Int, tabType :: TabType}
-> Versioned NgramsPatches -> Aff (Versioned NgramsPatches)
putNgramsPatches
session {
nodeId, listIds, tabType} = put session putNgrams
putNgramsPatches ::
forall s. CoreParams s
-> Versioned NgramsPatches -> Aff (Versioned NgramsPatches)
putNgramsPatches
{session,
nodeId, listIds, tabType} = put session putNgrams
where putNgrams = PutNgrams tabType (head listIds) Nothing (Just nodeId)
commitPatch :: forall
s. Session -> {nodeId :: Int, listIds :: Array Int, tabType :: TabType}
commitPatch :: forall
p s. CoreParams p
-> Versioned NgramsTablePatch -> StateCoTransformer (CoreState s) Unit
commitPatch
session
props (Versioned {version, data: tablePatch@{ngramsPatches, ngramsNewElems}}) = do
commitPatch props (Versioned {version, data: tablePatch@{ngramsPatches, ngramsNewElems}}) = do
let pt = Versioned { version, data: ngramsPatches }
lift $ postNewElems
session
ngramsNewElems props
Versioned {version: newVersion, data: newPatch} <- lift $ putNgramsPatches
session
props pt
lift $ postNewElems ngramsNewElems props
Versioned {version: newVersion, data: newPatch} <- lift $ putNgramsPatches props pt
modifyState_ $ \s ->
s { ngramsVersion = newVersion
, ngramsTablePatch = fromNgramsPatches newPatch <> tablePatch <> s.ngramsTablePatch
}
-- TODO: check that pt.version == s.ngramsTablePatch.version
loadNgramsTable ::
Session ->
PageParams -> Aff VersionedNgramsTable
loadNgramsTable
session
{ nodeId, listIds, termListFilter, termSizeFilter
loadNgramsTable :: PageParams -> Aff VersionedNgramsTable
loadNgramsTable
{ nodeId, listIds, termListFilter, termSizeFilter
, session
, searchQuery, tabType, params: {offset, limit, orderBy}}
= get session query
where query = GetNgrams { tabType, offset, limit, listIds
...
...
@@ -611,11 +607,3 @@ convOrderBy (T.ASC (T.ColumnName "Score (Occurrences)")) = ScoreAsc
convOrderBy (T.DESC (T.ColumnName "Score (Occurrences)")) = ScoreDesc
convOrderBy (T.ASC _) = TermAsc
convOrderBy (T.DESC _) = TermDesc
ngramsLoaderClass :: Session -> Loader.LoaderClass PageParams VersionedNgramsTable
ngramsLoaderClass session = Loader.createLoaderClass "NgramsTableLoader" (loadNgramsTable session)
ngramsLoader :: Session -> Loader.Props' PageParams VersionedNgramsTable -> ReactElement
ngramsLoader session props = React.createElement (ngramsLoaderClass session) props []
type LoadedNgramsTableProps = ( path :: PageParams, loaded :: VersionedNgramsTable )
src/Gargantext/Components/Nodes/Corpus/Document.purs
View file @
4209481a
module Gargantext.Components.Nodes.Corpus.Document where
import Prelude (class Show, bind, identity, mempty, pure, ($)
, (<<<)
)
import Prelude (class Show, bind, identity, mempty, pure, ($))
import Data.Argonaut (class DecodeJson, decodeJson, (.:), (.:?))
import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Show (genericShow)
...
...
@@ -19,14 +19,18 @@ import Gargantext.Components.NgramsTable.Core
, VersionedNgramsTable, addNewNgram, applyNgramsTablePatch, commitPatch
, loadNgramsTable, replace, singletonNgramsTablePatch )
import Gargantext.Components.Annotation.AnnotatedField as AnnotatedField
import Gargantext.Ends (url)
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Routes (SessionRoute(..))
import Gargantext.Sessions (Session, get)
import Gargantext.Types (CTabNgramType(..), NodeType(..), TabSubType(..), TabType(..), TermList)
import Gargantext.Utils.Reactix as R2
type DocPath = { nodeId :: Int, listIds :: Array Int, corpusId :: Maybe Int, tabType :: TabType }
type DocPath =
{ nodeId :: Int
, listIds :: Array Int
, corpusId :: Maybe Int
, tabType :: TabType
, session :: Session }
type NodeDocument = NodePoly Document
...
...
@@ -38,7 +42,6 @@ type LoadedData =
type Props =
{ loaded :: LoadedData
, path :: DocPath
, session :: Session
}
-- This is a subpart of NgramsTable.State.
...
...
@@ -286,15 +289,15 @@ docViewSpec :: Spec State Props Action
docViewSpec = simpleSpec performAction render
where
performAction :: PerformAction State Props Action
performAction Refresh {path
: {nodeId, listIds, tabType}, session
} {ngramsVersion} = do
commitPatch
session {nodeId, listIds, tabType}
(Versioned {version: ngramsVersion, data: mempty})
performAction (SetTermListItem n pl) {path
: {nodeId, listIds, tabType}, session
} {ngramsVersion} =
commitPatch
session {nodeId, listIds, tabType}
(Versioned {version: ngramsVersion, data: pt})
performAction Refresh {path} {ngramsVersion} = do
commitPatch
path
(Versioned {version: ngramsVersion, data: mempty})
performAction (SetTermListItem n pl) {path} {ngramsVersion} =
commitPatch
path
(Versioned {version: ngramsVersion, data: pt})
where
pe = NgramsPatch { patch_list: pl, patch_children: mempty }
pt = singletonNgramsTablePatch CTabTerms n pe
performAction (AddNewNgram ngram termList) {path
: {nodeId, listIds, tabType},session
} {ngramsVersion} =
commitPatch
session {nodeId, listIds, tabType}
(Versioned {version: ngramsVersion, data: pt})
performAction (AddNewNgram ngram termList) {path} {ngramsVersion} =
commitPatch
path
(Versioned {version: ngramsVersion, data: pt})
where
pt = addNewNgram CTabTerms ngram termList
...
...
@@ -342,10 +345,7 @@ docViewSpec = simpleSpec performAction render
badge s = span [className "badge badge-default badge-pill"] [text s]
NodePoly {hyperdata : Document doc} = document
docViewClass
:: ReactClass
{ session :: Session
, children :: Children
docViewClass :: ReactClass { children :: Children
, loaded :: LoadedData
, path :: DocPath }
docViewClass = createClass "DocumentView" docViewSpec initialState
...
...
@@ -359,24 +359,24 @@ documentLayoutCpt :: R.Component LayoutProps
documentLayoutCpt = R.hooksComponent "G.P.Corpus.Document.documentLayout" cpt
where
cpt {session, nodeId, listId, corpusId} _ = do
useLoader path
(loadData session)
$ \loaded ->
R2.createElement' docViewClass {
session,
path, loaded} []
useLoader path
loadData
$ \loaded ->
R2.createElement' docViewClass {path, loaded} []
where
tabType = TabDocument (TabNgramType CTabTerms)
path = {nodeId, listIds: [listId], corpusId, tabType}
path = {
session,
nodeId, listIds: [listId], corpusId, tabType}
------------------------------------------------------------------------
loadDocument :: Session -> Int -> Aff NodeDocument
loadDocument session nodeId = get session $ NodeAPI Node (Just nodeId) ""
loadData ::
Session ->
DocPath -> Aff LoadedData
loadData
session {
nodeId, listIds, tabType} = do
loadData :: DocPath -> Aff LoadedData
loadData
{session,
nodeId, listIds, tabType} = do
document <- loadDocument session nodeId
ngramsTable <- loadNgramsTable
session
ngramsTable <- loadNgramsTable
{ session
, nodeId
, listIds
: listIds
, listIds
, params: { offset : 0, limit : 100, orderBy: Nothing}
, tabType
, searchQuery : ""
...
...
Write
Preview
Markdown
is supported
0%
Try again
or
attach a new file
Attach a file
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Cancel
Please
register
or
sign in
to comment