Commit 63c4610a authored by Mael NICOLAS's avatar Mael NICOLAS

merged

parents 9a6d8cc0 7da3fe09
......@@ -9,34 +9,49 @@ import Data.Tuple (Tuple(..))
import React (ReactElement)
import React.DOM (a, div, nav, text)
import React.DOM.Props (className, onClick)
import Thermite (PerformAction, Render, Spec, _render, modifyState, focus, simpleSpec, withState)
import Thermite ( PerformAction, Render, Spec
, _render, modifyState, focus
, simpleSpec, withState)
type State = Int
data Action = ChangeTab Int
tabs :: forall state props action . Lens' state State -> Prism' action Action -> List (Tuple String (Spec state props action)) -> Spec state props action
tabs :: forall state props action.
Lens' state State -> Prism' action Action
-> List (Tuple String (Spec state props action))
-> Spec state props action
tabs l p ls = withState \st ->
fold
[ focus l p $ simpleSpec performAction (render (activeTab st) ls)
, wrapper $ fold $ mapWithIndex (tab (activeTab st)) ls
[ focus l p $ simpleSpec performAction (render (activeTab st) ls)
, wrapper $ fold $ mapWithIndex ( tab (activeTab st)) ls
]
where
activeTab = view l
wrapper = over _render \render d p s c ->
[div [className "tab-content"] $ render d p s c]
tab :: forall state props action. Int -> Int -> Tuple String (Spec state props action) -> Spec state props action
tab :: forall state props action.
Int -> Int -> Tuple String (Spec state props action)
-> Spec state props action
tab sid iid (Tuple name spec) = over _render tabRender spec
where
tabRender renderer d p s c =
[div [ className $ "tab-pane " <> if sid ==iid then " show active" else " fade"] $ renderer d p s c]
[ div [ className $ "tab-pane " <>
if sid ==iid
then " show active"
else " fade"] $ renderer d p s c
]
performAction :: forall props. PerformAction State props Action
performAction (ChangeTab i) _ _ = void $ modifyState $ const i
performAction :: forall props.
PerformAction State props Action
performAction (ChangeTab i) _ _ =
void $ modifyState $ const i
render :: forall state props action. State -> List (Tuple String (Spec state props action)) -> Render State props Action
render :: forall state props action.
State -> List (Tuple String (Spec state props action))
-> Render State props Action
render at ls d p s c =
[ nav []
[ div [className "nav nav-tabs"]
......@@ -46,4 +61,7 @@ render at ls d p s c =
where
item :: forall a. Int -> Int -> (Tuple String a) -> ReactElement
item sid iid (Tuple name _) =
a [className $ "nav-item nav-link" <> if sid == iid then " active" else "", onClick \e -> d $ ChangeTab iid] [text name]
a [className $ "nav-item nav-link" <>
if sid == iid
then " active"
else "", onClick \e -> d $ ChangeTab iid] [text name]
This diff is collapsed.
......@@ -9,9 +9,8 @@ toUrl Front Corpus 1 == "http://localhost:2015/#/corpus/1"
-}
module Gargantext.Config where
import Prelude ( class Eq, class Ord, class Show
, compare, eq, show, (<>), identity)
import Prelude
import Data.Argonaut (class DecodeJson, decodeJson)
import Data.Map (Map)
import Data.Map as DM
import Data.Maybe (maybe)
......@@ -180,3 +179,7 @@ instance ordNodeType :: Ord NodeType where
instance eqNodeType :: Eq NodeType where
eq n1 n2 = eq (show n1) (show n2)
------------------------------------------------------------
instance decodeJsonNodeType :: DecodeJson NodeType where
decodeJson json = do
obj <- decodeJson json
pure $ readNodeType obj
module Gargantext.Pages.Corpus.Annuaire where
module Gargantext.Pages.Annuaire where
import Prelude
......@@ -9,34 +9,58 @@ import Data.Either (Either(..))
import Data.Lens (Lens', Prism', lens, prism, (?~))
import Data.Maybe (Maybe(..), maybe)
import Effect.Class (liftEffect)
import React.DOM (div, h1, h3, hr, i, p, text)
import React.DOM.Props (className, style)
import React (ReactElement)
import React.DOM (div, h1, h3, hr, i, p, text, thead, tbody, input, br', b, b', tr, th, table, td, a)
import React.DOM.Props (_type, className, href, onChange, onClick, scope, selected, value, style)
import Thermite (Render, Spec
, simpleSpec, defaultPerformAction
, PerformAction, modifyState)
import Effect.Console (log)
import Effect.Aff (Aff)
import Gargantext.Config (toUrl, NodeType(..), End(..))
import Gargantext.Config.REST (get)
import Gargantext.Pages.Corpus.User.Users.Types.Types (User(..))
import Gargantext.Pages.Annuaire.User.Users.Types.Types (User(..), HyperData(..))
import Gargantext.Utils.DecodeMaybe ((.?|))
import Data.Argonaut (class DecodeJson, decodeJson, (.?))
------------------------------------------------------------------------------
type State = { info :: Maybe AnnuaireInfo
, table :: Maybe AnnuaireTable
, stable :: Maybe AnnuaireTable
}
type Offset = Int
type Limit = Int
type PageSize = Int
data Action = Load Int
-- | ChangePageSize PageSizes
-- | ChangePage Int
| ChangePageSize PageSize -- TODO
| ChangePage Int -- TODO
type AnnuaireTable' = Table IndividuView
newtype Table a
= Table
{ rows :: Array { row :: a }
, totalPages :: Int
, currentPage :: Int
, pageSize :: PageSize
, totalRecords :: Int
, title :: String
}
newtype IndividuView
= CorpusView
{ id :: Int
, name :: String
, role :: String
, company :: String
}
------------------------------------------------------------------------------
initialState :: State
initialState = { info : Nothing, table : Nothing }
initialState = { info : Nothing, stable : Nothing }
defaultAnnuaireTable :: AnnuaireTable
defaultAnnuaireTable = AnnuaireTable { annuaireTable : [Nothing] }
......@@ -70,18 +94,50 @@ render dispatch _ state _ = [ div [className "row"]
]
, div [ className "col-md-4 content"]
[ p [] [ i [className "fa fa-calendar"] []
, text info.date
, text ("Last update: " <> info.date)
]
]
]
]
, p [] [text $ foldl (<>) " "
$ map (maybe "Nothing" (\(User u) -> show u.name))
$ maybe (toRows defaultAnnuaireTable) toRows state.table]
, p [] []
, div [] [ text " Filter ", input []]
, br'
, div [className "row"]
[ div [className "col-md-1"] [b [] [text "title"]]
--, div [className "col-md-2"] [sizeDD d.pageSize dispatch]
--, div [className "col-md-3"] [textDescription d.currentPage d.pageSize d.totalRecords]
--, div [className "col-md-3"] [pagination dispatch d.totalPages d.currentPage]
]
, table [ className "table"]
[thead [ className "thead-dark"]
[tr [] [ th [scope "col"] [ b' [text ""] ]
, th [scope "col"] [ b' [text "Name"] ]
, th [scope "col"] [ b' [text "Role"] ]
, th [scope "col"] [ b' [text "Service"] ]
, th [scope "col"] [ b' [text "Company"] ]
]
]
, tbody [] $ map showRow individuals
]
]
where
(AnnuaireInfo info) = maybe defaultAnnuaireInfo identity state.info
(AnnuaireTable table) = maybe defaultAnnuaireTable identity state.table
(AnnuaireInfo info) = maybe defaultAnnuaireInfo identity state.info
(AnnuaireTable stable) = maybe defaultAnnuaireTable identity state.stable
individuals = maybe (toRows defaultAnnuaireTable) toRows state.stable
showRow :: Maybe User -> ReactElement
showRow Nothing = tr [][]
showRow (Just (User { id : id, hyperdata : (HyperData user) })) =
tr []
[ td [] [ a [ href (toUrl Back NodeUser id) ] [ text $ maybe' user.nom <> " " <> maybe' user.prenom ] ]
, td [] [text $ maybe' user.fonction]
, td [] [text $ maybe' user.service]
, td [] [text $ maybe' user.groupe]
]
where
maybe' = maybe "" identity
------------------------------------------------------------------------------
newtype AnnuaireInfo = AnnuaireInfo { id :: Int
......@@ -118,24 +174,24 @@ instance decodeAnnuaireTable :: DecodeJson AnnuaireTable where
decodeJson json = do
rows <- decodeJson json
pure $ AnnuaireTable { annuaireTable : rows}
------------------------------------------------------------------------
performAction :: PerformAction State {} Action
performAction (Load aId) _ _ = do
eitherInfo <- lift $ getInfo aId
_ <- case eitherInfo of
(Right info') -> void $ modifyState $ _info ?~ info'
(Left err) -> do
liftEffect $ log err
eitherTable <- lift $ getTable aId
liftEffect $ log "Feching Table"
_ <- case eitherTable of
(Right table') -> void $ modifyState $ _table ?~ table'
(Left err) -> do
liftEffect $ log err
liftEffect <<< log $ "Annuaire page fetched."
eitherInfo <- lift $ getInfo aId
_ <- case eitherInfo of
(Right info') -> void $ modifyState $ _info ?~ info'
(Left err) -> do
liftEffect $ log err
liftEffect <<< log $ "Fetching annuaire page..."
performAction _ _ _ = pure unit
------------------------------------------------------------------------
getTable :: Int -> Aff (Either String AnnuaireTable)
......@@ -145,7 +201,7 @@ getInfo :: Int -> Aff (Either String AnnuaireInfo)
getInfo id = get $ toUrl Back Node id
------------------------------------------------------------------------------
_table :: Lens' State (Maybe AnnuaireTable)
_table = lens (\s -> s.table) (\s ss -> s{table = ss})
_table = lens (\s -> s.stable) (\s ss -> s{stable = ss})
_info :: Lens' State (Maybe AnnuaireInfo)
_info = lens (\s -> s.info) (\s ss -> s{info = ss})
......
module Gargantext.Pages.Corpus.User.Brevets where
module Gargantext.Pages.Annuaire.User.Brevets where
import Prelude
import Thermite (Render, Spec, defaultPerformAction, simpleSpec)
......
module Gargantext.Pages.Annuaire.User.Users
(module Gargantext.Pages.Annuaire.User.Users.Types,
module Gargantext.Pages.Annuaire.User.Users.Specs)
where
import Gargantext.Pages.Annuaire.User.Users.Types
import Gargantext.Pages.Annuaire.User.Users.Specs
module Gargantext.Pages.Corpus.User.Users.API where
module Gargantext.Pages.Annuaire.User.Users.API where
import Prelude
......@@ -12,7 +12,7 @@ import Effect.Console (log)
import Gargantext.Config (toUrl, NodeType(..), End(..))
import Gargantext.Config.REST (get)
import Gargantext.Pages.Corpus.User.Users.Types (Action(..), State, User, _user)
import Gargantext.Pages.Annuaire.User.Users.Types (Action(..), State, User, _user)
import Thermite (PerformAction, modifyState)
getUser :: Int -> Aff (Either String User)
......
module Gargantext.Pages.Annuaire.User.Users.Specs
(module Gargantext.Pages.Annuaire.User.Users.Specs.Renders,
layoutUser)
where
import Gargantext.Pages.Annuaire.User.Users.Specs.Renders
import Thermite (Spec, simpleSpec)
import Gargantext.Pages.Annuaire.User.Users.Types (Action, State)
import Gargantext.Pages.Annuaire.User.Users.API (performAction)
layoutUser :: Spec State {} Action
layoutUser = simpleSpec performAction render
module Gargantext.Pages.Corpus.User.Users.Specs.Documents where
module Gargantext.Pages.Annuaire.User.Users.Specs.Documents where
import Prelude
import React.DOM (table, tbody, td, text, th, thead, tr)
......
module Gargantext.Pages.Corpus.User.Users.Specs.Renders
module Gargantext.Pages.Annuaire.User.Users.Specs.Renders
where
import Gargantext.Pages.Corpus.User.Users.Actions
import Gargantext.Pages.Corpus.User.Users.States
import Gargantext.Pages.Corpus.User.Users.Types
import Gargantext.Pages.Annuaire.User.Users.Types
import Data.List (List, toUnfoldable, zip)
import Data.Map (Map, empty, keys, values)
......
module Gargantext.Pages.Corpus.User.Users.Types
(module Gargantext.Pages.Corpus.User.Users.Types.Types,
module Gargantext.Pages.Corpus.User.Users.Types.Lens,
module Gargantext.Pages.Corpus.User.Users.Types.States,
module Gargantext.Pages.Annuaire.User.Users.Types
(module Gargantext.Pages.Annuaire.User.Users.Types.Types,
module Gargantext.Pages.Annuaire.User.Users.Types.Lens,
module Gargantext.Pages.Annuaire.User.Users.Types.States,
brevetSpec,
projectSpec,
facets
......@@ -10,10 +10,10 @@ module Gargantext.Pages.Corpus.User.Users.Types
import Prelude
import Gargantext.Pages.Corpus.User.Users.Types.Lens
import Gargantext.Pages.Corpus.User.Users.Types.Types
import Gargantext.Pages.Corpus.User.Users.Types.States
import Gargantext.Pages.Corpus.User.Brevets as B
import Gargantext.Pages.Annuaire.User.Users.Types.Lens
import Gargantext.Pages.Annuaire.User.Users.Types.Types
import Gargantext.Pages.Annuaire.User.Users.Types.States
import Gargantext.Pages.Annuaire.User.Brevets as B
import Data.List (fromFoldable)
import Data.Tuple (Tuple(..))
import Gargantext.Components.Tab (tabs)
......
module Gargantext.Pages.Corpus.User.Users.Types.Lens where
module Gargantext.Pages.Annuaire.User.Users.Types.Lens where
import Gargantext.Pages.Corpus.User.Brevets as B
import Gargantext.Pages.Annuaire.User.Brevets as B
import Data.Either (Either(..))
import Data.Lens (Lens', Prism', lens, prism)
import Data.Maybe (Maybe)
import Gargantext.Pages.Corpus.User.Users.Types.States (Action(..), State)
import Gargantext.Pages.Corpus.User.Users.Types.Types (User)
import Gargantext.Pages.Corpus.User.Users.Specs.Documents as P
import Gargantext.Pages.Annuaire.User.Users.Types.States (Action(..), State)
import Gargantext.Pages.Annuaire.User.Users.Types.Types (User)
import Gargantext.Pages.Annuaire.User.Users.Specs.Documents as P
import Gargantext.Components.Tab as Tab
import Thermite (Spec, noState)
......
module Gargantext.Pages.Corpus.User.Users.Types.States where
module Gargantext.Pages.Annuaire.User.Users.Types.States where
import Data.Maybe (Maybe(..))
import Gargantext.Pages.Corpus.User.Users.Types.Types (User)
import Gargantext.Pages.Corpus.User.Users.Specs.Documents as P
import Gargantext.Pages.Annuaire.User.Users.Types.Types (User)
import Gargantext.Pages.Annuaire.User.Users.Specs.Documents as P
import Gargantext.Components.Tab as Tab
data Action
......
module Gargantext.Pages.Corpus.User.Users.Types.Types where
module Gargantext.Pages.Annuaire.User.Users.Types.Types where
import Prelude
......
module Gargantext.Pages.Corpus where
import Data.Maybe (Maybe(..), maybe)
import Prelude hiding (div)
import Data.Argonaut (class DecodeJson, decodeJson, (.?))
import Gargantext.Components.Charts.Options.ECharts (chart)
import Gargantext.Pages.Corpus.Doc.Facets.Dashboard (globalPublis)
import Gargantext.Pages.Corpus.Doc.Facets as Tab
......@@ -9,51 +10,111 @@ import React.DOM (div, h3, hr, i, p, text)
import React.DOM.Props (className, style)
import Thermite (Render, Spec, defaultPerformAction, simpleSpec)
type Corpus = { title :: String
, desc :: String
, query :: String
, date :: String
, authors :: String
}
-------------------------------------------------------------------
type State = { info :: Maybe CorpusInfo
}
initialState :: State
initialState = { info : Nothing }
data Action = Load Int
newtype Node a = Node { id :: Int
, typename :: Int
, userId :: Int
, parentId :: Int
, name :: String
, date :: String
, hyperdata :: a
}
newtype CorpusInfo = CorpusInfo { title :: String
, desc :: String
, query :: String
, date :: String
, authors :: String
, chart :: (Maybe (Array Number))
}
corpusInfoDefault :: CorpusInfo
corpusInfoDefault = CorpusInfo
{ title : "Global Publications"
, desc : " Hal Database"
, query : " Query: all publications"
, date : " June. 26 2018, 10:59 am"
, authors : " Author(s): first.last name"
, chart : Nothing
}
spec' :: Spec {} {} Void
spec' = corpusSpec <> Tab.pureTab1
instance decodeCorpusInfo :: DecodeJson CorpusInfo where
decodeJson json = do
obj <- decodeJson json
title <- obj .? "title"
desc <- obj .? "desc"
query <- obj .? "query"
date <- obj .? "date"
authors <- obj .? "authors"
chart <- obj .? "chart"
pure $ CorpusInfo {title, desc, query, date, authors, chart}
corpusSpec :: Spec {} {} Void
instance decodeNode :: (DecodeJson a) => DecodeJson (Node a) where
decodeJson json = do
obj <- decodeJson json
id <- obj .? "id"
typename <- obj .? "typename"
userId <- obj .? "userId"
parentId <- obj .? "parentId"
name <- obj .? "name"
date <- obj .? "date"
hyperdata <- obj .? "hyperdata"
hyperdata' <- decodeJson hyperdata
pure $ Node { id : id
, typename : typename
, userId : userId
, parentId : parentId
, name : name
, date : date
, hyperdata: hyperdata'
}
layout :: Spec State {} Action
layout = corpusSpec -- <> Tab.pureTab1
corpusSpec :: Spec State {} Action
corpusSpec = simpleSpec defaultPerformAction render
where
render :: Render {} {} Void
render _ _ _ _ =
[ div [className "row"]
[ div [className "col-md-3"] [ h3 [] [text corpus.title] ]
, div [className "col-md-9"] [ hr [style {height : "2px",backgroundColor : "black"}] ]
]
, div [className "row"] [ div [className "jumbotron1", style {padding : "12px 0px 20px 12px"}]
[ div [ className "col-md-8 content"]
[ p [] [ i [className "fa fa-globe"] []
, text corpus.desc
]
, p [] [ i [className "fab fa-searchengin"] []
, text corpus.query
]
]
, div [ className "col-md-4 content"]
[ p [] [ i [className "fa fa-calendar"] []
, text corpus.date
]
, p [] [ i [className "fa fa-user"] []
, text corpus.authors
]
]
]
render :: Render State {} Action
render dispatch _ state _ =
[ div [className "row"]
[ div [className "col-md-3"] [ h3 [] [text corpus.title] ]
, div [className "col-md-9"] [ hr [style {height : "2px",backgroundColor : "black"}] ]
]
, div [className "row"] [ div [className "jumbotron1", style {padding : "12px 0px 20px 12px"}]
[ div [ className "col-md-8 content"]
[ p [] [ i [className "fa fa-globe"] []
, text corpus.desc
]
, p [] [ i [className "fab fa-searchengin"] []
, text corpus.query
]
]
, div [ className "col-md-4 content"]
[ p [] [ i [className "fa fa-calendar"] []
, text corpus.date
]
, p [] [ i [className "fa fa-user"] []
, text corpus.authors
]
]
]
]
-- , chart globalPublis TODO add chart data in state
]
, chart globalPublis
]
where
corpus :: Corpus
corpus = { title : "IMT Global Publications"
, desc : " Hal Database"
, query : " Query: all publications"
, date : " June. 26 2018, 10:59 am"
, authors : " Author(s): françois.pineau"
}
where
CorpusInfo corpus = maybe corpusInfoDefault identity state.info
......@@ -17,7 +17,7 @@ import Effect.Aff (Aff)
import Effect.Class (liftEffect)
import Effect.Console (log)
import Gargantext.Config (NodeType(..), toUrl, End(Back))
import Gargantext.Config (NodeType(..), toUrl, End(..))
import Gargantext.Config.REST (get)
import Gargantext.Utils.DecodeMaybe ((.|))
......@@ -83,6 +83,7 @@ derive instance genericCorpus :: Generic CorpusView _
instance showCorpus :: Show CorpusView where
show = genericShow
newtype Response = Response
{ cid :: Int
, created :: String
......@@ -91,6 +92,7 @@ newtype Response = Response
, ngramCount :: Int
}
newtype Hyperdata = Hyperdata
{ title :: String
, source :: String
......@@ -163,10 +165,7 @@ layoutDocview = simpleSpec performAction render
[thead [ className "thead-dark"]
[tr [] [ th [scope "col"] [ b' [text ""] ]
, th [scope "col"] [ b' [text "Date"]]
, th [scope "col"] [ b' [text "Name"] ]
--, th [scope "col"] [ b' [text "Title"] ]
--, th [scope "col"] [ b' [text "Source"] ]
, th [scope "col"] [ b' [text "Fonction"] ]
, th [scope "col"] [ b' [text "Title"] ]
, th [scope "col"] [ b' [text "Delete"] ]
]
]
......@@ -270,7 +269,7 @@ showRow {row : (CorpusView c), delete} =
[ td [] [div [className $ fa <> "fa-star"][]]
-- TODO show date: Year-Month-Day only
, td [] [text c.date]
, td [] [ a [ href (toUrl Back Document 1) ] [ text c.title ] ]
, td [] [ a [ href (toUrl Front Document c._id) ] [ text c.title ] ]
, td [] [text c.source]
, td [] [input [ _type "checkbox"]]
]
......
module Gargantext.Pages.Corpus.User.Users
(module Gargantext.Pages.Corpus.User.Users.Types,
module Gargantext.Pages.Corpus.User.Users.Specs)
where
import Gargantext.Pages.Corpus.User.Users.Types
import Gargantext.Pages.Corpus.User.Users.Specs
module Gargantext.Pages.Corpus.User.Users.Specs
(module Gargantext.Pages.Corpus.User.Users.Specs.Renders,
layoutUser)
where
import Gargantext.Pages.Corpus.User.Users.Specs.Renders
import Thermite (Spec, simpleSpec)
import Gargantext.Pages.Corpus.User.Users.Actions
import Gargantext.Pages.Corpus.User.Users.States
import Gargantext.Pages.Corpus.User.Users.API (performAction)
layoutUser :: Spec State {} Action
layoutUser = simpleSpec performAction render
publicationSpec :: forall eff props. Spec (dom :: DOM, console :: CONSOLE, ajax :: AJAX | eff) State props Action
publicationSpec = focus _publens _pubAction P.publicationSpec
brevetSpec :: forall eff props. Spec (dom :: DOM, console::CONSOLE, ajax :: AJAX | eff) State props Action
brevetSpec = focus _brevetslens _brevetsAction B.brevetsSpec
projectSpec :: forall eff props. Spec (dom :: DOM, console :: CONSOLE, ajax :: AJAX | eff) State props Action
projectSpec = focus _projectslens _projectsAction PS.projets
facets :: forall eff props. Spec ( dom :: DOM, console :: CONSOLE, ajax :: AJAX| eff) State props Action
facets = tabs _tablens _tabAction $ fromFoldable
[ Tuple "Publications (12)" publicationSpec
, Tuple "Brevets (2)" brevetSpec
, Tuple "Projets IMT (5)" projectSpec
]
......@@ -7,12 +7,13 @@ import Gargantext.Pages.Layout.Specs.AddCorpus as AC
-- import Gargantext.Pages.Corpus.Doc.Facets as TV
-- import Gargantext.Pages.Corpus.Doc.Annotation as D
import Gargantext.Pages.Corpus as Corpus
import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV
import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE
-- import Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsTable as NG
import Gargantext.Pages.Corpus.User.Users as U
import Gargantext.Pages.Corpus.Annuaire as Annuaire
import Gargantext.Pages.Annuaire.User.Users as U
import Gargantext.Pages.Annuaire as Annuaire
-- import Gargantext.Pages.Home as L
-- import Gargantext.Pages.Layout.Specs.Search as S
import Gargantext.Router (Routes(..))
......@@ -39,6 +40,10 @@ dispatchAction dispatcher _ (DocView n) = do
dispatcher $ SetRoute (DocView n)
dispatcher $ DocViewA $ DV.LoadData n
dispatchAction dispatcher _ (Corpus n) = do
dispatcher $ SetRoute $ Corpus n
dispatcher $ CorpusAction $ Corpus.Load n
dispatchAction dispatcher _ SearchView = do
dispatcher $ SetRoute SearchView
-- dispatcher $ SearchA TODO
......@@ -63,10 +68,6 @@ dispatchAction dispatcher _ Tabview = do
dispatcher $ SetRoute Tabview
-- dispatcher $ TabViewA TODO
dispatchAction dispatcher _ CorpusAnalysis = do
dispatcher $ SetRoute CorpusAnalysis
-- dispatcher $ CorpusAnalysisA TODO
dispatchAction dispatcher _ PGraphExplorer = do
dispatcher $ SetRoute PGraphExplorer
dispatcher $ GraphExplorerA $ GE.LoadGraph "imtNew.json"
......
......@@ -12,11 +12,13 @@ import Effect.Console (log)
import Gargantext.Components.Login as LN
import Gargantext.Components.Modals.Modal (modalShow)
import Gargantext.Components.Tree as Tree
import Gargantext.Pages.Corpus as Corpus
import Gargantext.Pages.Corpus.Doc.Annotation as D
import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV
import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE
import Gargantext.Pages.Corpus.User.Users as U
import Gargantext.Pages.Corpus.Annuaire as Annuaire
import Gargantext.Pages.Annuaire.User.Users as U
import Gargantext.Pages.Annuaire as Annuaire
import Gargantext.Pages.Layout.Specs.AddCorpus as AC
import Gargantext.Pages.Layout.Specs.Search as S
import Gargantext.Pages.Layout.States (AppState)
......@@ -32,12 +34,13 @@ data Action
| AddCorpusA AC.Action
| DocViewA DV.Action
| SearchA S.Action
| UserPageA U.Action
| DocAnnotationViewA D.Action
| TreeViewA Tree.Action
| GraphExplorerA GE.Action
| Search String
| TreeViewA Tree.Action
| CorpusAction Corpus.Action
| GraphExplorerA GE.Action
| DocAnnotationViewA D.Action
| AnnuaireAction Annuaire.Action
| UserPageA U.Action
| Go
| ShowLogin
| ShowAddcorpus
......@@ -53,6 +56,8 @@ performAction (ShowLogin) _ _ = void do
liftEffect $ modalShow "loginModal"
modifyState $ _ {showLogin = true}
---------------------------------------------------------
-- TODO chose one of them
performAction (ShowAddcorpus) _ _ = void do
liftEffect $ modalShow "addCorpus"
modifyState $ _ {showCorpus = true}
......@@ -62,6 +67,7 @@ performAction Go _ _ = void do
modifyState $ _ {showCorpus = true}
-- _ <- lift $ setHash "/addCorpus"
--modifyState id
---------------------------------------------------------
performAction Initialize _ state = void do
_ <- liftEffect $ log "loading Initial nodes"
......@@ -93,6 +99,7 @@ performAction Initialize _ state = void do
performAction (LoginA _) _ _ = pure unit
performAction (AddCorpusA _) _ _ = pure unit
performAction (CorpusAction _) _ _ = pure unit
performAction (DocViewA _) _ _ = pure unit
performAction (SearchA _) _ _ = pure unit
performAction (UserPageA _) _ _ = pure unit
......@@ -115,6 +122,12 @@ _addCorpusAction = prism AddCorpusA \action ->
AddCorpusA caction -> Right caction
_-> Left action
_corpusAction :: Prism' Action Corpus.Action
_corpusAction = prism CorpusAction \action ->
case action of
CorpusAction caction -> Right caction
_-> Left action
_docViewAction :: Prism' Action DV.Action
_docViewAction = prism DocViewA \action ->
case action of
......
......@@ -9,21 +9,21 @@ import Effect (Effect)
import Gargantext.Components.Data.Lang (Lang(..))
import Gargantext.Components.Login as LN
import Gargantext.Components.Tree as Tree
import Gargantext.Pages.Corpus.Annuaire as A
import Gargantext.Pages.Annuaire as A
import Gargantext.Folder as F
import Gargantext.Pages.Corpus as CA
import Gargantext.Pages.Corpus.Doc.Annotation as D
import Gargantext.Pages.Corpus as Corpus
import Gargantext.Pages.Corpus.Doc.Annotation as Annotation
import Gargantext.Pages.Corpus.Doc.Facets as TV
import Gargantext.Pages.Corpus.Doc.Facets.Dashboard as Dsh
import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV
import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE
import Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsTable as NG
import Gargantext.Pages.Corpus.User.Users as U
import Gargantext.Pages.Annuaire.User.Users as U
import Gargantext.Pages.Home as L
import Gargantext.Pages.Layout.Actions (Action(..), _addCorpusAction, _docAnnotationViewAction, _docViewAction, _graphExplorerAction, _loginAction, _searchAction, _treeAction, _userPageAction, performAction, _annuaireAction)
import Gargantext.Pages.Layout.Actions (Action(..), _corpusAction, _addCorpusAction, _docAnnotationViewAction, _docViewAction, _graphExplorerAction, _loginAction, _searchAction, _treeAction, _userPageAction, performAction, _annuaireAction)
import Gargantext.Pages.Layout.Specs.AddCorpus as AC
import Gargantext.Pages.Layout.Specs.Search as S
import Gargantext.Pages.Layout.States (AppState, _addCorpusState, _docAnnotationViewState, _docViewState, _graphExplorerState, _loginState, _searchState, _treeState, _userPageState, _annuaireState)
import Gargantext.Pages.Layout.States (AppState, _corpusState, _addCorpusState, _docAnnotationViewState, _docViewState, _graphExplorerState, _loginState, _searchState, _treeState, _userPageState, _annuaireState)
import Gargantext.Router (Routes(..))
import React (ReactElement)
import React.DOM (a, button, div, footer, hr', img, input, li, p, span, text, ul)
......@@ -54,15 +54,16 @@ pagesComponent s =
Nothing -> selectSpec Home
where
selectSpec :: Routes -> Spec AppState {} Action
selectSpec CorpusAnalysis = layout0 $ noState CA.spec'
selectSpec (Corpus i) = layout0 $ focus _corpusState _corpusAction Corpus.layout
selectSpec Login = focus _loginState _loginAction LN.renderSpec
selectSpec Home = layout0 $ noState (L.layoutLanding EN)
selectSpec AddCorpus = layout0 $ focus _addCorpusState _addCorpusAction AC.layoutAddcorpus
selectSpec (DocView i) = layout0 $ focus _docViewState _docViewAction DV.layoutDocview
selectSpec (UserPage i) = layout0 $ focus _userPageState _userPageAction U.layoutUser
selectSpec (DocAnnotation i) = layout0 $ focus _docAnnotationViewState _docAnnotationViewAction D.docview
selectSpec Tabview = layout0 $ noState TV.pureTab1
selectSpec (DocAnnotation i) = layout0 $ focus _docAnnotationViewState
_docAnnotationViewAction Annotation.docview
-- To be removed
selectSpec Tabview = layout0 $ noState TV.pureTab1
selectSpec SearchView = layout0 $ focus _searchState _searchAction S.searchSpec
selectSpec NGramsTable = layout0 $ noState NG.ngramsTableSpec
selectSpec PGraphExplorer = focus _graphExplorerState _graphExplorerAction GE.specOld
......
......@@ -6,11 +6,13 @@ import Data.Lens (Lens', lens)
import Data.Maybe (Maybe(Just))
import Gargantext.Components.Login as LN
import Gargantext.Components.Tree as Tree
import Gargantext.Pages.Corpus as Corpus
import Gargantext.Pages.Corpus.Doc.Annotation as D
import Gargantext.Pages.Corpus.Annuaire as Annuaire
import Gargantext.Pages.Annuaire as Annuaire
import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV
import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE
import Gargantext.Pages.Corpus.User.Users as U
import Gargantext.Pages.Annuaire.User.Users as U
import Gargantext.Pages.Layout.Specs.AddCorpus as AC
import Gargantext.Pages.Layout.Specs.Search as S
import Gargantext.Router (Routes(..))
......@@ -18,6 +20,7 @@ import Gargantext.Router (Routes(..))
type AppState =
{ currentRoute :: Maybe Routes
, loginState :: LN.State
, corpus :: Corpus.State
, addCorpusState :: AC.State
, docViewState :: DV.State
, searchState :: S.State
......@@ -35,6 +38,7 @@ type AppState =
initAppState :: AppState
initAppState =
{ currentRoute : Just Home
, corpus : Corpus.initialState
, loginState : LN.initialState
, addCorpusState : AC.initialState
, docViewState : DV.tdata
......@@ -57,6 +61,9 @@ _loginState = lens (\s -> s.loginState) (\s ss -> s{loginState = ss})
_addCorpusState :: Lens' AppState AC.State
_addCorpusState = lens (\s -> s.addCorpusState) (\s ss -> s{addCorpusState = ss})
_corpusState :: Lens' AppState Corpus.State
_corpusState = lens (\s -> s.corpus) (\s ss -> s{corpus = ss})
_docViewState :: Lens' AppState DV.State
_docViewState = lens (\s -> s.docViewState) (\s ss -> s{docViewState = ss})
......
......@@ -16,66 +16,71 @@ import Web.Storage.Storage (getItem)
data Routes
= Home
| Login
| AddCorpus
| DocView Int
| SearchView
| UserPage Int
| DocAnnotation Int
| Tabview
| CorpusAnalysis
| PGraphExplorer
| NGramsTable
| Dashboard
| Annuaire Int
| Folder Int
| Folder Int
| Corpus Int
| AddCorpus
| Tabview
| DocView Int
| DocAnnotation Int
| PGraphExplorer
| NGramsTable
| Dashboard
| Annuaire Int
| UserPage Int
routing :: Match Routes
routing =
Login <$ route "login"
<|> SearchView <$ route "search"
<|> AddCorpus <$ route "addCorpus"
<|> Folder <$> (route "folder" *> int)
<|> Corpus <$> (route "corpus" *> int)
<|> Tabview <$ route "tabview"
<|> DocView <$> (route "docView" *> int)
<|> NGramsTable <$ route "ngrams"
<|> DocAnnotation <$> (route "document" *> int)
<|> Dashboard <$ route "dashboard"
<|> PGraphExplorer <$ route "graph"
<|> Annuaire <$> (route "annuaire" *> int)
<|> UserPage <$> (route "user" *> int)
<|> Home <$ lit ""
where
route str = lit "" *> lit str
int :: Match Int
int = floor <$> num
instance showRoutes :: Show Routes where
show Login = "Login"
show AddCorpus = "AddCorpus"
show (DocView i) = "DocView"
show SearchView = "Search"
show (UserPage i) = "User"
show (UserPage i) = "User" <> show i
show (DocAnnotation i)= "Document"
show (Corpus i) = "Corpus" <> show i
show Tabview = "Tabview"
show CorpusAnalysis = "Corpus"
show PGraphExplorer = "graphExplorer"
show (DocView i) = "DocView"
show NGramsTable = "NGramsTable"
show (Annuaire i) = "Annuaire" <> show i
show (Folder i) = "Folder" <> show i
show Dashboard = "Dashboard"
show (Annuaire i) = "Annuaire"
show (Folder i) = "Folder"
show PGraphExplorer = "graphExplorer"
show Home = "Home"
int :: Match Int
int = floor <$> num
routing :: Match Routes
routing =
Login <$ route "login"
<|> Tabview <$ route "tabview"
<|> DocAnnotation <$> (route "document" *> int)
<|> UserPage <$> (route "user" *> int)
<|> SearchView <$ route "search"
<|> DocView <$> (route "docView" *> int)
<|> AddCorpus <$ route "addCorpus"
<|> CorpusAnalysis <$ route "corpus"
<|> PGraphExplorer <$ route "graph"
<|> NGramsTable <$ route "ngrams"
<|> Dashboard <$ route "dashboard"
<|> Annuaire <$> (route "annuaire" *> int)
<|> Folder <$> (route "folder" *> int)
<|> Home <$ lit ""
where
route str = lit "" *> lit str
routeHandler :: (Maybe Routes -> Routes -> Effect Unit) -> Maybe Routes -> Routes -> Effect Unit
routeHandler :: (Maybe Routes -> Routes -> Effect Unit)
-> Maybe Routes -> Routes -> Effect Unit
routeHandler dispatchAction old new = do
liftEffect $ log $ "change route : " <> show new
w <- window
ls <- localStorage w
token <- getItem "accessToken" ls
let tkn = token
liftEffect $ log $ "JWToken : " <> show tkn
case tkn of
Nothing -> do
dispatchAction old new
......
......@@ -9,7 +9,8 @@ import Foreign.Object (Object)
foreign import isNull :: forall a. a -> Boolean
getFieldOptional' :: forall a. DecodeJson a => Object Json -> String -> Either String (Maybe a)
getFieldOptional' :: forall a. DecodeJson a =>
Object Json -> String -> Either String (Maybe a)
getFieldOptional' o s = (case _ of
Just v -> if isNull v then Nothing else v
Nothing -> Nothing
......@@ -17,7 +18,9 @@ getFieldOptional' o s = (case _ of
infix 7 getFieldOptional' as .?|
getFieldOptionalAsMempty :: forall a. DecodeJson a => Monoid a => Object Json -> String -> Either String a
getFieldOptionalAsMempty o s = fromMaybe mempty <$> (getFieldOptional' o s)
getFieldOptionalAsMempty :: forall a. DecodeJson a =>
Monoid a => Object Json -> String -> Either String a
getFieldOptionalAsMempty o s =
fromMaybe mempty <$> (getFieldOptional' o s)
infix 7 getFieldOptionalAsMempty as .|
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