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
142
Issues
142
List
Board
Labels
Milestones
Merge Requests
4
Merge Requests
4
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
gargantext
purescript-gargantext
Commits
c56d3283
Commit
c56d3283
authored
Jun 22, 2018
by
Sudhir Kumar
Browse files
Options
Browse Files
Download
Email Patches
Plain Diff
load initial node data
parent
bec1f38a
Changes
2
Hide whitespace changes
Inline
Side-by-side
Showing
2 changed files
with
78 additions
and
16 deletions
+78
-16
NTree.purs
src/NTree.purs
+44
-1
Navigation.purs
src/Navigation.purs
+34
-15
No files found.
src/NTree.purs
View file @
c56d3283
module NTree where
module NTree where
import Data.Tuple (Tuple(..))
import Prelude hiding (div)
import Prelude hiding (div)
import Control.Monad.Aff (Aff, attempt)
import Control.Monad.Aff.Class (liftAff)
import Control.Monad.Eff.Class (liftEff)
import Control.Monad.Eff.Console (CONSOLE, log)
import Data.Argonaut (class DecodeJson, decodeJson, (.?))
import Data.Either (Either(..))
import Data.HTTP.Method (Method(..))
import Data.Newtype (class Newtype)
import Data.Tuple (Tuple(..))
import Network.HTTP.Affjax (AJAX, affjax, defaultRequest)
import React (ReactElement)
import React (ReactElement)
import React.DOM (a, div, i, li, text, ul)
import React.DOM (a, div, i, li, text, ul)
import React.DOM.Props (Props, className, href, onClick)
import React.DOM.Props (Props, className, href, onClick)
...
@@ -106,3 +116,36 @@ toHtml d (NNode id open name ary) =
...
@@ -106,3 +116,36 @@ toHtml d (NNode id open name ary) =
fldr :: Boolean -> Props
fldr :: Boolean -> Props
fldr open = if open then className "fas fa-folder-open" else className "fas fa-folder"
fldr open = if open then className "fas fa-folder-open" else className "fas fa-folder"
newtype LNode = LNode {id :: Int, name :: String}
derive instance newtypeLNode :: Newtype LNode _
instance decodeJsonLNode :: DecodeJson LNode where
decodeJson json = do
obj <- decodeJson json
id_ <- obj .? "id"
name <- obj .? "name"
pure $ LNode {id : id_, name}
loadDefaultNode ::forall eff. Aff (ajax :: AJAX, console :: CONSOLE | eff) (Either String (Array LNode))
loadDefaultNode = do
res <- liftAff $ attempt $ affjax defaultRequest
{ url = "http://localhost:8008/user"
, method = Left GET
}
case res of
Left err -> do
_ <- liftEff $ log $ show err
pure $ Left $ show err
Right a -> do
_ <- liftEff $ log $ show a.status
_ <- liftEff $ log $ show a.headers
_ <- liftEff $ log $ show a.response
let resp = decodeJson a.response
pure resp
fnTransform :: LNode -> FTree
fnTransform (LNode r) = NNode r.id false r.name []
src/Navigation.purs
View file @
c56d3283
...
@@ -2,28 +2,31 @@ module Navigation where
...
@@ -2,28 +2,31 @@ module Navigation where
import DOM
import DOM
import Gargantext.Data.Lang
import Gargantext.Data.Lang
import Prelude hiding (div)
import AddCorpusview as AC
import AddCorpusview as AC
import AnnotationDocumentView as D
import AnnotationDocumentView as D
import Control.Monad.Cont.Trans (lift)
import Control.Monad.Cont.Trans (lift)
import Control.Monad.Eff (Eff)
import Control.Monad.Eff (Eff)
import Control.Monad.Eff.Class (liftEff)
import Control.Monad.Eff.Class (liftEff)
import Control.Monad.Eff.Console (CONSOLE)
import Control.Monad.Eff.Console (CONSOLE
, log
)
import CorpusAnalysis as CA
import CorpusAnalysis as CA
import Data.Array (concat)
import Data.Array (concat
, head, length
)
import Data.Either (Either(..))
import Data.Either (Either(..))
import Data.Foldable (fold, intercalate)
import Data.Foldable (fold, intercalate)
import Data.Lens (Lens', Prism', lens, over, prism)
import Data.Lens (Lens', Prism', lens, over, prism)
import Data.Maybe (Maybe(Nothing, Just))
import Data.Maybe (Maybe(Nothing, Just)
, fromJust
)
import Data.Tuple (Tuple(..))
import Data.Tuple (Tuple(..))
import DocView as DV
import DocView as DV
import GraphExplorer as GE
import Landing as L
import Landing as L
import Login as LN
import Login as LN
import Modal (modalShow)
import Modal (modalShow)
import NTree (fnTransform, loadDefaultNode)
import NTree as NT
import NTree as NT
import Network.HTTP.Affjax (AJAX)
import Network.HTTP.Affjax (AJAX)
import PageRouter (Routes(..))
import PageRouter (Routes(..))
import P
relude hiding (div
)
import P
artial.Unsafe (unsafePartial
)
import React (ReactElement)
import React (ReactElement)
import React.DOM (a, button, div, footer, form, hr, i, img, input, li, p, span, text, ul)
import React.DOM (a, button, div, footer, form, hr, i, img, input, li, p, span, text, ul)
import React.DOM.Props (Props, _data, _id, _type, aria, className, href, name, onChange, onClick, placeholder, role, src, style, tabIndex, target, title)
import React.DOM.Props (Props, _data, _id, _type, aria, className, href, name, onChange, onClick, placeholder, role, src, style, tabIndex, target, title)
...
@@ -34,7 +37,6 @@ import Tabview as TV
...
@@ -34,7 +37,6 @@ import Tabview as TV
import Thermite (PerformAction, Render, Spec, _render, cotransform, defaultPerformAction, defaultRender, focus, modifyState, simpleSpec, withState)
import Thermite (PerformAction, Render, Spec, _render, cotransform, defaultPerformAction, defaultRender, focus, modifyState, simpleSpec, withState)
import Unsafe.Coerce (unsafeCoerce)
import Unsafe.Coerce (unsafeCoerce)
import UserPage as UP
import UserPage as UP
import GraphExplorer as GE
type E e = (dom :: DOM, ajax :: AJAX, console :: CONSOLE | e)
type E e = (dom :: DOM, ajax :: AJAX, console :: CONSOLE | e)
...
@@ -54,6 +56,7 @@ type AppState =
...
@@ -54,6 +56,7 @@ type AppState =
, showLogin :: Boolean
, showLogin :: Boolean
, showCorpus :: Boolean
, showCorpus :: Boolean
, graphExplorer :: GE.State
, graphExplorer :: GE.State
, initialized :: Boolean
}
}
initAppState :: AppState
initAppState :: AppState
...
@@ -73,6 +76,7 @@ initAppState =
...
@@ -73,6 +76,7 @@ initAppState =
, showLogin : false
, showLogin : false
, showCorpus : false
, showCorpus : false
, graphExplorer : GE.initialState
, graphExplorer : GE.initialState
, initialized : false
}
}
data Action
data Action
...
@@ -97,6 +101,8 @@ data Action
...
@@ -97,6 +101,8 @@ data Action
performAction :: forall eff props. PerformAction ( dom :: DOM
performAction :: forall eff props. PerformAction ( dom :: DOM
, ajax :: AJAX
, console :: CONSOLE
| eff
| eff
) AppState props Action
) AppState props Action
performAction (SetRoute route) _ _ = void do
performAction (SetRoute route) _ _ = void do
...
@@ -121,7 +127,18 @@ performAction Go _ _ = void do
...
@@ -121,7 +127,18 @@ performAction Go _ _ = void do
-- _ <- lift $ setHash "/addCorpus"
-- _ <- lift $ setHash "/addCorpus"
--modifyState id
--modifyState id
performAction Initialize _ state = void do
_ <- liftEff $ log "loading Initial nodes"
case state.initialized of
false -> do
lnodes <- lift $ loadDefaultNode
case lnodes of
Left err -> do
modifyState id
Right d -> do
modifyState $ _ {initialized = true, ntreeView = if length d > 0 then fnTransform $ unsafePartial $ fromJust $ head d else NT.initialState}
_ -> do
modifyState id
performAction _ _ _ = void do
performAction _ _ _ = void do
modifyState id
modifyState id
...
@@ -272,7 +289,7 @@ pagesComponent s =
...
@@ -272,7 +289,7 @@ pagesComponent s =
selectSpec PGraphExplorer = focus _graphExplorerState _graphExplorerAction GE.spec
selectSpec PGraphExplorer = focus _graphExplorerState _graphExplorerAction GE.spec
selectSpec _ = simpleSpec defaultPerformAction defaultRender
selectSpec _ = simpleSpec defaultPerformAction defaultRender
routingSpec :: forall props eff. Spec (dom :: DOM |eff) AppState props Action
routingSpec :: forall props eff. Spec (
ajax :: AJAX, console :: CONSOLE,
dom :: DOM |eff) AppState props Action
routingSpec = simpleSpec performAction defaultRender
routingSpec = simpleSpec performAction defaultRender
...
@@ -456,7 +473,7 @@ liNav (LiNav { title : title'
...
@@ -456,7 +473,7 @@ liNav (LiNav { title : title'
-- TODO put the search form in the center of the navBar
-- TODO put the search form in the center of the navBar
divSearchBar :: forall props eff. Spec (dom :: DOM |eff) AppState props Action
divSearchBar :: forall props eff. Spec (
ajax :: AJAX, console :: CONSOLE,
dom :: DOM |eff) AppState props Action
divSearchBar = simpleSpec performAction render
divSearchBar = simpleSpec performAction render
where
where
render :: Render AppState props Action
render :: Render AppState props Action
...
@@ -502,7 +519,7 @@ divDropdownRight d =
...
@@ -502,7 +519,7 @@ divDropdownRight d =
layoutFooter :: forall props eff. Spec (dom :: DOM |eff) AppState props Action
layoutFooter :: forall props eff. Spec (
ajax :: AJAX, console :: CONSOLE,
dom :: DOM |eff) AppState props Action
layoutFooter = simpleSpec performAction render
layoutFooter = simpleSpec performAction render
where
where
render :: Render AppState props Action
render :: Render AppState props Action
...
@@ -548,18 +565,20 @@ dispatchAction :: forall t115 t445 t447.
...
@@ -548,18 +565,20 @@ dispatchAction :: forall t115 t445 t447.
Bind t445 => Applicative t445 =>
Bind t445 => Applicative t445 =>
(Action -> t445 t447) -> t115 -> Routes -> t445 Unit
(Action -> t445 t447) -> t115 -> Routes -> t445 Unit
dispatchAction dispatcher _ Home = do
dispatchAction dispatcher _ Home = do
_ <- dispatcher $ SetRoute $ Home
_ <- dispatcher Initialize
_ <- dispatcher $ LandingA $ L.NoOp
_ <- dispatcher $ SetRoute Home
_ <- dispatcher $ LandingA L.NoOp
pure unit
pure unit
dispatchAction dispatcher _ Login = do
dispatchAction dispatcher _ Login = do
_ <- dispatcher $ SetRoute $ Login
_ <- dispatcher Initialize
_ <- dispatcher $ LoginA $ LN.NoOp
_ <- dispatcher $ SetRoute Login
_ <- dispatcher $ LoginA LN.NoOp
pure unit
pure unit
dispatchAction dispatcher _ AddCorpus = do
dispatchAction dispatcher _ AddCorpus = do
_ <- dispatcher $ SetRoute
$
AddCorpus
_ <- dispatcher $ SetRoute AddCorpus
_ <- dispatcher $ AddCorpusA
$
AC.LoadDatabaseDetails
_ <- dispatcher $ AddCorpusA AC.LoadDatabaseDetails
pure unit
pure unit
dispatchAction dispatcher _ DocView = do
dispatchAction dispatcher _ DocView = do
...
...
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