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
140
Issues
140
List
Board
Labels
Milestones
Merge Requests
6
Merge Requests
6
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
203ea8dd
Commit
203ea8dd
authored
Jun 24, 2018
by
Alexandre Delanoë
Browse files
Options
Browse Files
Download
Email Patches
Plain Diff
[DOCview][REST] rest added, loaded but does not appear.
parent
4d66dce9
Changes
3
Hide whitespace changes
Inline
Side-by-side
Showing
3 changed files
with
145 additions
and
98 deletions
+145
-98
DocView.purs
src/DocView.purs
+129
-95
NTree.purs
src/NTree.purs
+2
-2
Navigation.purs
src/Navigation.purs
+14
-1
No files found.
src/DocView.purs
View file @
203ea8dd
module DocView where
import Data.Argonaut
import Data.Generic (class Generic, gShow)
import Chart (histogram2, p'')
import Control.Monad.Eff.Class (liftEff)
import Control.Monad.Aff (Aff, attempt)
import Control.Monad.Aff.Class (liftAff)
import Control.Monad.Cont.Trans (lift)
import Control.Monad.Eff (Eff)
import Control.Monad.Eff.Console (CONSOLE)
import Control.Monad.Eff.Console (CONSOLE
, log
)
import DOM (DOM)
import DOM.HTML (window) as DOM
import DOM.HTML.Types (htmlDocumentToParentNode) as DOM
...
...
@@ -52,26 +54,61 @@ import Gargantext.REST (get)
-- TODO: Filter is Pending
-- TODO: When a pagination link is clicked, reload data. Right now it doesn't make sense to reload mock data.
data Action
= LoadData
| ChangePageSize PageSizes
| ChangePage Int
type State = CorpusTableData
type CorpusTableData = TableData Corpus
newtype TableData a
= TableData
{ rows :: Array { row :: a
, delete :: Boolean
}
, totalPages :: Int
, currentPage :: Int
, pageSize :: PageSizes
, totalRecords :: Int
, title :: String
-- , tree :: FTree
}
newtype Corpus
= Corpus
{ _id :: Int
, url :: String
, date :: String
, title :: String
, source :: String
, fav :: Boolean
, ngramCount :: Int
}
derive instance genericCorpus :: Generic Corpus
instance showCorpus :: Show Corpus where
show = gShow
newtype Response = Response
{ cid :: Int
, created :: String
, hyperdata :: Hyperdata
, favorite :: Boolean
, ngramCount :: Int
, hyperdata :: Hyperdata
}
newtype Hyperdata = Hyperdata
{ title :: String
, source :: String
}
type State = CorpusTableData
data Action
= ChangePageSize PageSizes
| ChangePage Int
| LoadData
instance decodeHyperdata :: DecodeJson Hyperdata where
...
...
@@ -82,7 +119,6 @@ instance decodeHyperdata :: DecodeJson Hyperdata where
pure $ Hyperdata { title,source }
instance decodeResponse :: DecodeJson Response where
decodeJson json = do
obj <- decodeJson json
...
...
@@ -93,6 +129,7 @@ instance decodeResponse :: DecodeJson Response where
hyperdata <- obj .? "hyperdata"
pure $ Response { cid, created, favorite, ngramCount, hyperdata }
-- | Filter
filterSpec :: forall eff props. Spec eff State props Action
filterSpec = simpleSpec defaultPerformAction render
where
...
...
@@ -142,23 +179,94 @@ performAction (ChangePageSize ps) _ _ = void (cotransform (\state -> changePage
performAction (ChangePage p) _ _ = void (cotransform (\(TableData td) -> TableData $ td { currentPage = p} ))
performAction LoadData _ _ = void do
res <- lift $ get "http://localhost:8008/corpus/452132/facet/documents/table"
--res <- lift $ loadData "http://localhost:8009/corpus/1/facet/documents/table"
res <- lift $ loadPage
case res of
Left err -> cotransform $ \(state) -> state
Left err -> cotransform $ \state -> state
Right resData -> modifyState (\s -> resData)
loadPage :: forall eff. Aff (ajax :: AJAX, console :: CONSOLE | eff) (Either String CorpusTableData)
loadPage = do
res <- get "http://localhost:8008/corpus/472764/facet/documents/table"
case res of
Left err -> do
_ <- liftEff $ log $ show err
pure $ Left $ show err
Right resData -> do
modifyState (\s -> tdata' $ data' (res2corpus <$> resData))
let docs = toTableData (res2corpus $ resData)
_ <- liftEff $ log $ show $ map (\({ row: r, delete :_}) -> show r) ((\(TableData docs') -> docs'.rows) docs)
_ <- liftEff $ log $ show "loading"
pure $ Right docs
where
res2corpus (Response res) =
Corpus { _id : res.cid
res2corpus :: Array Response -> Array Corpus
res2corpus rs = map (\(Response r) ->
Corpus { _id : r.cid
, url : ""
, date : res.created
, title : (\(Hyperdata r) -> r.title) res.hyperdata
, source : (\(Hyperdata r) -> r.source)res.hyperdata
, fav : res.favorite
}
, date : r.created
, title : (\(Hyperdata r) -> r.title) r.hyperdata
, source : (\(Hyperdata r) -> r.source) r.hyperdata
, fav : r.favorite
, ngramCount : r.ngramCount
}) rs
toTableData :: Array Corpus -> CorpusTableData
toTableData ds = TableData
{ rows : map (\d -> { row : d , delete : false}) ds
, totalPages : 10
, currentPage : 1
, pageSize : PS10
, totalRecords : 100
, title : "Documents"
-- , tree : exampleTree
}
---------------------------------------------------------
sampleData' :: Corpus
sampleData' = Corpus {_id : 1, url : "", date : "date3", title : "title", source : "source", fav : false, ngramCount : 1}
--
sampleData :: Array Corpus
sampleData = replicate 10 sampleData'
data' :: Array Corpus -> Array {row :: Corpus, delete :: Boolean}
data' = map {row : _, delete : false}
sdata :: Array { row :: Corpus, delete :: Boolean }
sdata = data' sampleData
tdata = TableData
{ rows : sdata
, totalPages : 10
, currentPage : 1
, pageSize : PS10
, totalRecords : 100
, title : "Documents"
-- , tree : exampleTree
}
showRow :: {row :: Corpus, delete :: Boolean} -> ReactElement
showRow {row : (Corpus c), delete} =
tr []
[ td [] [div [className $ fa <> "fa-star"][]]
-- TODO show date: Year-Month-Day only
, td [] [text c.date]
, td [] [ a [ href "#/documentView/1"] [ text c.title ] ]
, td [] [text c.source]
, td [] [input [ _type "checkbox"] []]
]
where
fa = case c.fav of
true -> "fas "
false -> "far "
--------------------------------------------------------------
-- | Action
-- ChangePageSize
changePageSize :: PageSizes -> CorpusTableData -> CorpusTableData
changePageSize ps (TableData td) =
TableData $ td { pageSize = ps
...
...
@@ -304,78 +412,4 @@ lessthan x y = x < y
greaterthan :: forall t28. Ord t28 => t28 -> t28 -> Boolean
greaterthan x y = x > y
newtype TableData a
= TableData
{ rows :: Array { row :: a
, delete :: Boolean
}
, totalPages :: Int
, currentPage :: Int
, pageSize :: PageSizes
, totalRecords :: Int
, title :: String
-- , tree :: FTree
}
newtype Corpus
= Corpus
{ _id :: Int
, url :: String
, date :: String
, title :: String
, source :: String
, fav :: Boolean
}
type CorpusTableData = TableData Corpus
sampleData' :: Corpus
sampleData' = Corpus {_id : 1, url : "", date : "date", title : "title", source : "source", fav : false}
sampleData :: Array Corpus
sampleData = replicate 10 sampleData'
data' :: Array Corpus -> Array {row :: Corpus, delete :: Boolean}
data' = map {row : _, delete : false}
sdata :: Array { row :: Corpus, delete :: Boolean }
sdata = data' sampleData
tdata :: CorpusTableData
tdata = TableData
{ rows : sdata
, totalPages : 10
, currentPage : 1
, pageSize : PS10
, totalRecords : 100
, title : "Documents"
-- , tree : exampleTree
}
tdata' :: _ -> CorpusTableData
tdata' d = TableData
{ rows : d
, totalPages : 10
, currentPage : 1
, pageSize : PS10
, totalRecords : 100
, title : "Documents"
-- , tree : exampleTree
}
showRow :: {row :: Corpus, delete :: Boolean} -> ReactElement
showRow {row : (Corpus c), delete} =
tr []
[ td [] [div [className $ fa <> "fa-star"][]]
-- TODO show date: Year-Month-Day only
, td [] [text c.date]
, td [] [ a [ href "#/documentView/1"] [ text c.title ] ]
, td [] [text c.source]
, td [] [input [ _type "checkbox"] []]
]
where
fa = case c.fav of
true -> "fas "
false -> "far "
src/NTree.purs
View file @
203ea8dd
...
...
@@ -120,7 +120,7 @@ fldr open = if open then className "fas fa-folder-open" else className "fas fa-f
newtype LNode = LNode {id :: Int, name :: String}
derive instance newtypeLNode :: Newtype LNode _
--
derive instance newtypeLNode :: Newtype LNode _
instance decodeJsonLNode :: DecodeJson LNode where
decodeJson json = do
...
...
@@ -129,7 +129,7 @@ instance decodeJsonLNode :: DecodeJson LNode where
name <- obj .? "name"
pure $ LNode {id : id_, name}
loadDefaultNode ::forall eff. Aff (ajax :: AJAX, console :: CONSOLE | eff) (Either String (Array LNode))
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"
...
...
src/Navigation.purs
View file @
203ea8dd
...
...
@@ -139,12 +139,25 @@ 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}
page <- lift $ DV.loadPage
case page of
Left err -> do
modifyState id
Right docs -> do
modifyState $ _ { initialized = true
, ntreeView = if length d > 0
then fnTransform $ unsafePartial $ fromJust $ head d
else NT.initialState
, docViewState = docs
}
_ -> do
modifyState id
...
...
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