Copy the Corpus page (Docs&Ngrams) for Contacts

parent d898d51d
......@@ -13,7 +13,7 @@ import Thermite ( PerformAction, Render, Spec
, _render, modifyState, focus
, simpleSpec, withState)
type State = Int
type State = { activeTab :: Int }
data Action = ChangeTab Int
......@@ -22,16 +22,16 @@ tabs :: forall state props action.
-> List (Tuple String (Spec state props action))
-> Spec state props action
tabs l p ls = withState \st ->
let {activeTab} = view l st in
fold
[ focus l p $ simpleSpec performAction (render (activeTab st) ls)
, wrapper $ fold $ mapWithIndex ( tab (activeTab st)) ls
[ focus l p $ simpleSpec performAction (render activeTab ls)
, wrapper $ fold $ mapWithIndex ( tab activeTab) ls
]
where
performAction :: forall props.
PerformAction State props Action
performAction (ChangeTab i) _ _ =
void $ modifyState $ const i
activeTab = view l
performAction (ChangeTab activeTab) _ _ =
void $ modifyState $ const {activeTab}
wrapper = over _render \render d p s c ->
[div [className "tab-content"] $ render d p s c]
......@@ -49,7 +49,7 @@ tab sid iid (Tuple name spec) = over _render tabRender spec
render :: forall state props action.
State -> List (Tuple String (Spec state props action))
Int -> List (Tuple String (Spec state props action))
-> Render State props Action
render at ls d p s c =
[ nav []
......
......@@ -98,10 +98,18 @@ endBaseUrl end c = (endOf end c).baseUrl
endPathUrl :: End -> EndConfig -> Path -> Maybe Id -> UrlPath
endPathUrl end = pathUrl <<< endOf end
tabTypeDocs :: TabType -> UrlPath
tabTypeDocs (TabCorpus t) = "table?view=" <> show t
tabTypeDocs (TabPairing t) = "pairing?view=" <> show t
tabTypeNgrams :: TabType -> UrlPath
tabTypeNgrams (TabCorpus t) = "listGet?ngramsType=" <> show t
tabTypeNgrams (TabPairing t) = "listGet?ngramsType=" <> show t -- TODO
pathUrl :: Config -> Path -> Maybe Id -> UrlPath
pathUrl c (Tab t o l s) i =
pathUrl c (NodeAPI Node) i <>
"/" <> "table?view=" <> show t <> "&offset=" <> show o
"/" <> tabTypeDocs t <> "&offset=" <> show o
<> "&limit=" <> show l <> os
where
os = maybe "" (\x -> "&order=" <> show x) s
......@@ -112,7 +120,7 @@ pathUrl c (Children n o l s) i =
where
os = maybe "" (\x -> "&order=" <> show x) s
pathUrl c (Ngrams t listid) i =
pathUrl c (NodeAPI Node) i <> "/" <> "listGet?ngramsType=" <> show t <> listid'
pathUrl c (NodeAPI Node) i <> "/" <> tabTypeNgrams t <> listid'
where
listid' = maybe "" (\x -> "&list=" <> show x) listid
pathUrl c Auth Nothing = c.prePath <> "auth"
......@@ -171,13 +179,11 @@ instance showNodeType :: Show NodeType where
show Nodes = "Nodes"
show Tree = "NodeTree"
data Path
= Auth
| Tab TabType Offset Limit (Maybe OrderBy)
| Children NodeType Offset Limit (Maybe OrderBy)
| Ngrams TabType (Maybe TermList)
| Ngrams TabType (Maybe TermList)
| NodeAPI NodeType
data End = Back | Front
......@@ -201,15 +207,31 @@ instance showApiVersion :: Show ApiVersion where
show V11 = "v1.1"
------------------------------------------------------------
data TabType = TabDocs | TabTerms | TabSources | TabAuthors | TabInstitutes | TabTrash
data CTabNgramType = CTabTerms | CTabSources | CTabAuthors | CTabInstitutes
instance showCTabNgramType :: Show CTabNgramType where
show CTabTerms = "Terms"
show CTabSources = "Sources"
show CTabAuthors = "Authors"
show CTabInstitutes = "Institutes"
data PTabNgramType = PTabPatents | PTabBooks | PTabCommunication
instance showPTabNgramType :: Show PTabNgramType where
show PTabPatents = "Patents"
show PTabBooks = "Books"
show PTabCommunication = "Communication"
data TabSubType a = TabDocs | TabNgramType a | TabTrash
instance showTabSubType :: Show a => Show (TabSubType a) where
show TabDocs = "Docs"
show (TabNgramType a) = show a
show TabTrash = "Trash"
instance showTabType :: Show TabType where
show TabDocs = "Docs"
show TabTerms = "Terms"
show TabSources = "Sources"
show TabAuthors = "Authors"
show TabInstitutes = "Institutes"
show TabTrash = "Trash"
data TabType
= TabCorpus (TabSubType CTabNgramType)
| TabPairing (TabSubType PTabNgramType)
------------------------------------------------------------
nodeTypeUrl :: NodeType -> Url
......
module Gargantext.Pages.Annuaire.User.Brevets where
import Prelude
import Thermite (Render, Spec, defaultPerformAction, simpleSpec)
brevetsSpec :: Spec {} {} Void
brevetsSpec = simpleSpec defaultPerformAction render
where
render :: Render {} {} Void
render dispatch _ state _ =
[]
module Gargantext.Pages.Annuaire.User.Contacts.API where
import Control.Monad.Trans.Class (lift)
import Data.Either (Either(..))
import Data.Lens ((?~))
import Data.Maybe (Maybe(..))
import Effect.Aff (Aff)
import Effect.Class (liftEffect)
import Effect.Console (log)
import Thermite (StateCoTransformer, modifyState)
import Gargantext.Config (toUrl, NodeType(..), End(..))
import Gargantext.Config.REST (get)
import Gargantext.Prelude
import Gargantext.Pages.Annuaire.User.Contacts.Types (Action(..), State, Contact, _contact)
import Thermite (PerformAction, modifyState)
getContact :: Maybe Int -> Aff Contact
getContact id = get $ toUrl Back Node id
fetchContact :: Int -> StateCoTransformer State Unit
fetchContact contactId = do
contact <- lift $ getContact (Just contactId)
void $ modifyState $ _contact ?~ contact
logs "Fetching contact..."
module Gargantext.Pages.Annuaire.User.Contacts.Specs
(module Gargantext.Pages.Annuaire.User.Contacts.Specs.Renders,
brevetSpec,
projectSpec,
facets,
layoutUser)
(layoutUser)
where
import Data.List (fromFoldable)
import Data.Tuple (Tuple(..))
import Thermite (Render, PerformAction, Spec, focus, noState, defaultPerformAction, simpleSpec)
import Data.List (List, zipWith, catMaybes, toUnfoldable)
import Data.Map (Map, empty, keys, values, lookup)
import Data.Array (head)
import Data.Semigroup ((<>))
import Data.Maybe (Maybe(..), fromMaybe, maybe)
import Data.Set (toUnfoldable) as S
import Data.Tuple (Tuple(..), uncurry)
import Data.Unfoldable (class Unfoldable)
import Data.Maybe (Maybe(..))
import Data.Newtype (unwrap)
import Data.String (joinWith)
import Effect.Aff (Aff)
import Thermite (Render, Spec, defaultPerformAction, simpleSpec, createClass)
import React as React
import React (ReactClass, ReactElement)
import React.DOM (div, h3, img, li, span, text, ul, text)
import React.DOM.Props (_id, className, src)
import Gargantext.Prelude
import Gargantext.Components.Tab as Tab
import Gargantext.Pages.Annuaire.User.Brevets as B
import Gargantext.Pages.Annuaire.User.Contacts.Specs.Documents as P
import Gargantext.Pages.Annuaire.User.Contacts.Types (Action(..), State, _tablens, _tabAction)
import Gargantext.Pages.Annuaire.User.Contacts.API (fetchContact)
import Gargantext.Pages.Annuaire.User.Contacts.Specs.Renders (render)
layoutUser :: Spec State {} Action
layoutUser = simpleSpec performAction render
import Gargantext.Config (toUrl, End(..), NodeType(..))
import Gargantext.Config.REST (get)
import Gargantext.Components.Loader as Loader
import Gargantext.Pages.Annuaire.User.Contacts.Types
import Gargantext.Pages.Annuaire.User.Contacts.Tabs.Specs as Tabs
--type Props = Loader.InnerProps Int Contact
display :: String -> Array ReactElement -> Array ReactElement
display title elems =
[ div [className "container-fluid"]
[ div [className "row", _id "contact-page-header"]
[ div [className "col-md-6"] [ h3 [] [text title] ]
, div [className "col-md-8"] []
, div [className "col-md-2"] [ span [] [text ""] ]
]
, div [className "row", _id "contact-page-info"]
[ div [className "col-md-12"]
[ div [className "row"]
[ div [className "col-md-2"]
--[ ]
[ img [src "/images/Gargantextuel-212x300.jpg"] ]
, div [className "col-md-1"] []
, div [className "col-md-8"] elems
]
]
]
]
]
mapMyMap :: forall k v x f. Ord k => Unfoldable f => (k -> v -> x) -> Map k v -> f x
mapMyMap f m = toUnfoldable
$ zipWith f mapKeys
(catMaybes $ flip lookup m <$> mapKeys)
where mapKeys = S.toUnfoldable $ keys m
infixl 4 mapMyMap as <.~$>
getFirstName obj = fromMaybe "Empty title" $ getFirstName' <$> obj
getFirstName' = fromMaybe "Empty first name" <<< _.firstName <<< unwrap
getLastName obj = fromMaybe "Empty title" $ getLastName' <$> obj
getLastName' = fromMaybe "Empty last name" <<< _.lastName <<< unwrap
-- | ContactWhere infos
-- TODO factor below
getRole :: Array ContactWhere -> String
getRole obj = joinWith ", " $ getRole' <$> obj
getRole' = fromMaybe "no role" <<< _.role <<< unwrap
getOrga :: Array ContactWhere -> String
getOrga = maybe "Emtpy Contact-Where" getOrga' <<< head
where
getOrga' :: ContactWhere -> String
getOrga' obj = joinWith ", " $ (\(ContactWhere {organization: o}) ->o) obj
getDept :: Array ContactWhere -> String
getDept = maybe "Empty Department" getDept' <<< head
where
getDept' :: ContactWhere -> String
getDept' obj = joinWith ", " $ (\(ContactWhere {labTeamDepts: l}) ->l) obj
getOffice :: Array ContactWhere -> String
getOffice = fromMaybe "Empty Office"
<<< maybe Nothing (\(ContactWhere {office:x}) -> x)
<<< head
getCity :: Array ContactWhere -> String
getCity = fromMaybe "Empty City"
<<< maybe Nothing (\(ContactWhere {city:x}) -> x)
<<< head
getCountry :: Array ContactWhere -> String
getCountry = fromMaybe "Empty Country"
<<< maybe Nothing (\(ContactWhere {country:x}) -> x)
<<< head
-- | ContactWhere / Touch infos
getTouch :: Array ContactWhere -> Maybe ContactTouch
getTouch = maybe Nothing (\(ContactWhere {touch:x}) -> x) <<< head
getPhone :: Array ContactWhere -> String
getPhone obj = fromMaybe "" $ getPhone' <$> (getTouch obj)
getPhone' :: ContactTouch -> String
getPhone' = fromMaybe "no phone" <<< _.phone <<< unwrap
getMail :: Array ContactWhere -> String
getMail obj = fromMaybe "" $ getMail' <$> (getTouch obj)
getMail' :: ContactTouch -> String
getMail' = fromMaybe "no mail" <<< _.mail <<< unwrap
-- | TODO format data in better design (UI) shape
contactInfos :: HyperdataContact -> Array ReactElement
contactInfos (HyperdataContact {who:who, ou:ou}) =
[ ul [className "list-group"] (infoRender (Tuple "Last Name" $ " " <> getLastName who))
, ul [className "list-group"] (infoRender (Tuple "First name" $ " " <> getFirstName who))
, ul [className "list-group"] (infoRender (Tuple "Organization" $ " " <> getOrga ou ))
, ul [className "list-group"] (infoRender (Tuple "Lab/Team/Dept"$ " " <> getOrga ou ))
, ul [className "list-group"] (infoRender (Tuple "Office" $ " " <> getOffice ou ))
, ul [className "list-group"] (infoRender (Tuple "City" $ " " <> getCity ou ))
, ul [className "list-group"] (infoRender (Tuple "Country" $ " " <> getCountry ou ))
, ul [className "list-group"] (infoRender (Tuple "Role" $ " " <> getRole ou ))
, ul [className "list-group"] (infoRender (Tuple "Phone" $ " " <> getPhone ou ))
, ul [className "list-group"] (infoRender (Tuple "Mail" $ " " <> getMail ou ))
]
{- $
listInfo <.~$> hyperdata
where
performAction :: PerformAction State {} Action
performAction (FetchContact contactId) _ _ = fetchContact contactId
performAction (TabA _) _ _ = pure unit
checkMaybe (Nothing) = empty
checkMaybe (Just (HyperData a)) = a
-}
listInfo :: Tuple String String -> ReactElement
listInfo s = listElement $ infoRender s
brevetSpec :: Spec State {} Action
brevetSpec = noState B.brevetsSpec
listElement :: Array ReactElement -> ReactElement
listElement = li [className "list-group-item justify-content-between"]
projets :: Spec {} {} Void
projets = simpleSpec defaultPerformAction render
infoRender :: Tuple String String -> Array ReactElement
infoRender (Tuple title content) =
[ span [className "badge badge-default badge-pill"] [text title]
, span [] [text content]
]
layoutUser :: Spec {} {nodeId :: Int} Void
layoutUser = simpleSpec defaultPerformAction render
where
render :: Render {} {nodeId :: Int} Void
render _ {nodeId} _ _ =
[ contactLoader { path: nodeId
, component: createClass "LayoutUser" layoutUser' (const {})
} ]
layoutUser' :: Spec {} Props Void
layoutUser' = simpleSpec defaultPerformAction render
<> Tabs.pureTabs
where
render :: Render {} {} Void
render dispatch _ state _ =
[]
projectSpec :: Spec State {} Action
projectSpec = noState projets
publicationSpec :: Spec State {} Action
publicationSpec = noState P.publicationSpec
facets :: Spec State {} Action
facets = Tab.tabs _tablens _tabAction $ fromFoldable
[ Tuple "Publications (12)" publicationSpec
, Tuple "Brevets (2)" brevetSpec
, Tuple "Projets IMT (5)" projectSpec
]
render :: Render {} Props Void
render dispatch {loaded: Contact {name, hyperdata}} _ _ =
[ div [className "col-md-12"] $
display (fromMaybe "no name" name) (contactInfos hyperdata)
]
getContact :: Int -> Aff Contact
getContact id = get $ toUrl Back Node $ Just id
contactLoaderClass :: ReactClass (Loader.Props Int Contact)
contactLoaderClass = Loader.createLoaderClass "ContactLoader" getContact
contactLoader :: Loader.Props' Int Contact -> ReactElement
contactLoader props = React.createElement contactLoaderClass props []
module Gargantext.Pages.Annuaire.User.Contacts.Specs.Documents where
import Prelude
import React.DOM (table, tbody, td, text, th, thead, tr)
import React.DOM.Props (className, scope)
import Thermite (Render, Spec, defaultPerformAction, simpleSpec)
publicationSpec :: Spec {} {} Void
publicationSpec = simpleSpec defaultPerformAction render
where
render :: Render {} {} Void
render dispatch _ state _ =
[ table [ className "table"]
[ thead [ className "thead-dark"]
[ tr []
[ th [ scope "col"] [ text "Date" ]
, th [ scope "col"] [ text "Description" ]
, th [ scope "col"] [ text "Projects" ]
, th [ scope "col"] [ text "Favorite" ]
, th [ scope "col"] [ text "Delete" ]
]
]
, tbody []
[ tr [] [ td [] [ text "2012/03/06"]
, td [] [ text "Big data and text mining"]
, td [] [ text "European funds"]
, td [] [ text "True"]
, td [] [ text "False"]
]
, tr [] [ td [] [ text "2013/03/06"]
, td [] [ text "Cryptography"]
, td [] [ text "French funds"]
, td [] [ text "True"]
, td [] [ text "False"]
]
, tr [] [ td [] [ text "2013/03/06"]
, td [] [ text "Artificial Intelligence"]
, td [] [ text "Not found"]
, td [] [ text "True"]
, td [] [ text "False"]
]
]
]
]
module Gargantext.Pages.Annuaire.User.Contacts.Specs.Renders
where
import Gargantext.Pages.Annuaire.User.Contacts.Types
import Prelude (map)
import Data.List (List, zipWith, catMaybes, toUnfoldable)
import Data.Map (Map, empty, keys, values, lookup)
import Data.Array (head)
import Data.Semigroup ((<>))
import Data.Maybe (Maybe(..), fromMaybe, maybe)
import Data.Set (toUnfoldable) as S
import Data.Tuple (Tuple(..), uncurry)
import Data.Unfoldable (class Unfoldable)
import Prelude (identity)
import Prelude (($), (<<<), (<$>), flip, class Ord)
import React (ReactElement)
import React.DOM (div, h3, img, li, span, text, ul, text)
import React.DOM.Props (_id, className, src)
import Thermite (Render)
import Data.Newtype (unwrap)
import Data.String
render :: Render State {} Action
render dispatch _ state _ =
[
div [className "col-md-12"]
$ case state.contact of
(Just (Contact contact)) -> display (fromMaybe "no name" contact.name) (contactInfos contact.hyperdata)
Nothing -> display "Contact not found" []
]
display :: String -> Array ReactElement -> Array ReactElement
display title elems =
[ div [className "container-fluid"]
[ div [className "row", _id "contact-page-header"]
[ div [className "col-md-6"] [ h3 [] [text title] ]
, div [className "col-md-8"] []
, div [className "col-md-2"] [ span [] [text ""] ]
]
, div [className "row", _id "contact-page-info"]
[ div [className "col-md-12"]
[ div [className "row"]
[ div [className "col-md-2"]
--[ ]
[ img [src "/images/Gargantextuel-212x300.jpg"] ]
, div [className "col-md-1"] []
, div [className "col-md-8"] elems
]
]
]
]
]
mapMyMap :: forall k v x f. Ord k => Unfoldable f => (k -> v -> x) -> Map k v -> f x
mapMyMap f m = toUnfoldable
$ zipWith f mapKeys
(catMaybes $ flip lookup m <$> mapKeys)
where mapKeys = S.toUnfoldable $ keys m
infixl 4 mapMyMap as <.~$>
getFirstName obj = fromMaybe "Empty title" $ getFirstName' <$> obj
getFirstName' = fromMaybe "Empty first name" <<< _.firstName <<< unwrap
getLastName obj = fromMaybe "Empty title" $ getLastName' <$> obj
getLastName' = fromMaybe "Empty last name" <<< _.lastName <<< unwrap
-- | ContactWhere infos
-- TODO factor below
getRole :: Array ContactWhere -> String
getRole obj = joinWith ", " $ getRole' <$> obj
getRole' = fromMaybe "no role" <<< _.role <<< unwrap
getOrga :: Array ContactWhere -> String
getOrga = maybe "Emtpy Contact-Where" getOrga' <<< head
where
getOrga' :: ContactWhere -> String
getOrga' obj = joinWith ", " $ (\(ContactWhere {organization: o}) ->o) obj
getDept :: Array ContactWhere -> String
getDept = maybe "Empty Department" getDept' <<< head
where
getDept' :: ContactWhere -> String
getDept' obj = joinWith ", " $ (\(ContactWhere {labTeamDepts: l}) ->l) obj
getOffice :: Array ContactWhere -> String
getOffice = fromMaybe "Empty Office"
<<< maybe Nothing (\(ContactWhere {office:x}) -> x)
<<< head
getCity :: Array ContactWhere -> String
getCity = fromMaybe "Empty City"
<<< maybe Nothing (\(ContactWhere {city:x}) -> x)
<<< head
getCountry :: Array ContactWhere -> String
getCountry = fromMaybe "Empty Country"
<<< maybe Nothing (\(ContactWhere {country:x}) -> x)
<<< head
-- | ContactWhere / Touch infos
getTouch :: Array ContactWhere -> Maybe ContactTouch
getTouch = maybe Nothing (\(ContactWhere {touch:x}) -> x) <<< head
getPhone :: Array ContactWhere -> String
getPhone obj = fromMaybe "" $ getPhone' <$> (getTouch obj)
getPhone' :: ContactTouch -> String
getPhone' = fromMaybe "no phone" <<< _.phone <<< unwrap
getMail :: Array ContactWhere -> String
getMail obj = fromMaybe "" $ getMail' <$> (getTouch obj)
getMail' :: ContactTouch -> String
getMail' = fromMaybe "no mail" <<< _.mail <<< unwrap
-- | TODO format data in better design (UI) shape
contactInfos :: HyperdataContact -> Array ReactElement
contactInfos (HyperdataContact {who:who, ou:ou}) =
[ ul [className "list-group"] (infoRender (Tuple "Last Name" $ " " <> getLastName who))
, ul [className "list-group"] (infoRender (Tuple "First name" $ " " <> getFirstName who))
, ul [className "list-group"] (infoRender (Tuple "Organization" $ " " <> getOrga ou ))
, ul [className "list-group"] (infoRender (Tuple "Lab/Team/Dept"$ " " <> getOrga ou ))
, ul [className "list-group"] (infoRender (Tuple "Office" $ " " <> getOffice ou ))
, ul [className "list-group"] (infoRender (Tuple "City" $ " " <> getCity ou ))
, ul [className "list-group"] (infoRender (Tuple "Country" $ " " <> getCountry ou ))
, ul [className "list-group"] (infoRender (Tuple "Role" $ " " <> getRole ou ))
, ul [className "list-group"] (infoRender (Tuple "Phone" $ " " <> getPhone ou ))
, ul [className "list-group"] (infoRender (Tuple "Mail" $ " " <> getMail ou ))
]
{- $
listInfo <.~$> hyperdata
where
checkMaybe (Nothing) = empty
checkMaybe (Just (HyperData a)) = a
-}
listInfo :: Tuple String String -> ReactElement
listInfo s = listElement $ infoRender s
listElement :: Array ReactElement -> ReactElement
listElement = li [className "list-group-item justify-content-between"]
infoRender :: Tuple String String -> Array ReactElement
infoRender (Tuple title content) =
[ span [className "badge badge-default badge-pill"] [text title]
, span [] [text content]
]
-- TODO copy of Gargantext.Pages.Corpus.Tabs.Specs
module Gargantext.Pages.Annuaire.User.Contacts.Tabs.Specs where
import Prelude hiding (div)
import Data.List (fromFoldable)
import Data.Tuple (Tuple(..))
import Gargantext.Pages.Annuaire.User.Contacts.Types (Props)
import Gargantext.Pages.Annuaire.User.Contacts.Tabs.Documents as DV
import Gargantext.Pages.Annuaire.User.Contacts.Tabs.Ngrams.NgramsTable as NV
import Gargantext.Components.Tab as Tab
import Thermite (Spec, focus, hideState, noState, cmapProps)
pureTabs :: Spec {} Props Void
pureTabs = hideState (const {activeTab: 0}) statefulTabs
statefulTabs :: Spec Tab.State Props Tab.Action
statefulTabs =
Tab.tabs identity identity $ fromFoldable
[ Tuple "Documents" $ noState DV.docViewSpec
, Tuple "Patents" $ ngramsViewSpec {mode: NV.Patents}
, Tuple "Books" $ ngramsViewSpec {mode: NV.Books}
, Tuple "Communication" $ ngramsViewSpec {mode: NV.Communication}
, Tuple "Trash" $ noState DV.docViewSpec -- TODO pass-in trash mode
]
ngramsViewSpec :: {mode :: NV.Mode} -> Spec Tab.State Props Tab.Action
ngramsViewSpec {mode} =
cmapProps (\{loaded, path, dispatch} -> {mode,loaded,path, dispatch})
(noState NV.ngramsTableSpec)
......@@ -11,10 +11,12 @@ import Data.Map (Map(..))
import React (ReactElement)
import React.DOM (div)
import Gargantext.Components.Loader as Loader
import Gargantext.Components.Tab as Tab
import Gargantext.Utils.DecodeMaybe ((.?|))
import Data.Newtype
-- TODO: should it be a NodePoly HyperdataContact ?
newtype Contact = Contact {
id :: Int
, typename :: Maybe Int
......@@ -166,29 +168,5 @@ instance decodeUser :: DecodeJson Contact where
, hyperdata
}
data Action
= TabA Tab.Action
| FetchContact Int
type State =
{ activeTab :: Int
, contact :: Maybe Contact
}
initialState :: State
initialState =
{ activeTab : 0
, contact: Nothing
}
_contact :: Lens' State (Maybe Contact)
_contact = lens (\s -> s.contact) (\s ss -> s{contact = ss})
_tablens :: Lens' State Tab.State
_tablens = lens (\s -> s.activeTab) (\s ss -> s {activeTab = ss})
_tabAction :: Prism' Action Tab.Action
_tabAction = prism TabA \ action ->
case action of
TabA laction -> Right laction
_-> Left action
type PropsRow = Loader.InnerPropsRow Int Contact ()
type Props = Record PropsRow
......@@ -19,33 +19,10 @@ import Gargantext.Config (toUrl, NodeType(..), End(..))
import Gargantext.Config.REST (get)
import Gargantext.Pages.Corpus.Tabs.Types (CorpusInfo(..))
import Gargantext.Pages.Corpus.Tabs.Types (Props) as Tabs
import Gargantext.Pages.Corpus.Tabs.States (State, initialState) as Tabs
import Gargantext.Pages.Corpus.Tabs.Actions (Action) as Tabs
import Gargantext.Pages.Corpus.Tabs.Specs (statefulTabs) as Tabs
import Gargantext.Pages.Corpus.Tabs.Specs (pureTabs) as Tabs
-------------------------------------------------------------------
type Props = Tabs.Props
type State = { tabsView :: Tabs.State
}
initialState :: Props -> State
initialState _props =
{ tabsView : Tabs.initialState {} }
------------------------------------------------------------------------
_tabsView :: forall a b. Lens' { tabsView :: a | b } a
_tabsView = lens (\s -> s.tabsView) (\s ss -> s{tabsView = ss})
------------------------------------------------------------------------
data Action
= TabsA Tabs.Action
_tabsAction :: Prism' Action Tabs.Action
_tabsAction = prism TabsA \ action ->
case action of
TabsA taction -> Right taction
-- _-> Left action
------------------------------------------------------------------------
layout :: Spec {} {nodeId :: Int} Void
layout = simpleSpec defaultPerformAction render
......@@ -53,12 +30,11 @@ layout = simpleSpec defaultPerformAction render
render :: Render {} {nodeId :: Int} Void
render _ {nodeId} _ _ =
[ corpusLoader { path: nodeId
, component: createClass "Layout" layout' initialState
, component: createClass "Layout" layout' (const {})
} ]
layout' :: Spec State Props Action
layout' = noState corpusHeaderSpec
<> focus _tabsView _tabsAction Tabs.statefulTabs
layout' :: Spec {} Props Void
layout' = corpusHeaderSpec <> Tabs.pureTabs
corpusHeaderSpec :: Spec {} Props Void
corpusHeaderSpec = simpleSpec defaultPerformAction render
......
module Gargantext.Pages.Corpus.Tabs
( module Gargantext.Pages.Corpus.Tabs.States
, module Gargantext.Pages.Corpus.Tabs.Actions
, module Gargantext.Pages.Corpus.Tabs.Specs
( module Gargantext.Pages.Corpus.Tabs.Specs
) where
import Gargantext.Pages.Corpus.Tabs.States
import Gargantext.Pages.Corpus.Tabs.Actions
import Gargantext.Pages.Corpus.Tabs.Specs
module Gargantext.Pages.Corpus.Tabs.Actions where
import Data.Lens (Prism', prism)
import Data.Either (Either(..))
import Gargantext.Components.Tab as Tab
data Action
= TabAction Tab.Action -- = ChangeTab which is only used locally
_TabAction :: Prism' Action Tab.Action
_TabAction = prism TabAction \ action ->
case action of
TabAction laction -> Right laction
_-> Left action
......@@ -25,12 +25,11 @@ import React as React
import React (ReactClass, ReactElement, Children)
------------------------------------------------------------------------
import Gargantext.Prelude
import Gargantext.Config (Path(..), NodeType(..), TabType(..), toUrl, End(..), OrderBy(..))
import Gargantext.Config (Path(..), NodeType(..), TabSubType(..), TabType(..), toUrl, End(..), OrderBy(..))
import Gargantext.Config.REST (get, put, post, deleteWithBody)
import Gargantext.Utils.DecodeMaybe ((.|))
import Gargantext.Components.Charts.Options.ECharts (chart)
import Gargantext.Components.Loader as Loader
import Gargantext.Components.Table as T
import Gargantext.Components.Node (NodePoly(..))
import Gargantext.Components.Table as T
import Gargantext.Pages.Corpus.Dashboard (globalPublis)
......@@ -74,9 +73,9 @@ newtype DocumentsView
}
derive instance genericCorpus :: Generic DocumentsView _
derive instance genericDocumentsView :: Generic DocumentsView _
instance showCorpus :: Show DocumentsView where
instance showDocumentsView :: Show DocumentsView where
show = genericShow
......@@ -203,7 +202,7 @@ loadPage :: PageParams -> Aff (Array DocumentsView)
loadPage {nodeId, params: {limit, offset, orderBy}} = do
logs "loading documents page: loadPage with Offset and limit"
--res <- get $ toUrl Back (Children Url_Document offset limit) nodeId
res <- get $ toUrl Back (Tab TabDocs offset limit (convOrderBy <$> orderBy)) (Just nodeId)
res <- get $ toUrl Back (Tab (TabCorpus TabDocs) offset limit (convOrderBy <$> orderBy)) (Just nodeId)
let docs = res2corpus <$> res
--_ <- logs "Ok: loading page documents"
--_ <- logs $ map show docs
......
module Gargantext.Pages.Corpus.Tabs.Ngrams.NgramsTable where
module Gargantext.Pages.Corpus.Tabs.Ngrams.NgramsTable
(Mode(..), ngramsTableSpec)
where
import Control.Monad.State (class MonadState, execState)
import Data.Argonaut (class DecodeJson, decodeJson, (.?), (.??))
......@@ -490,14 +491,14 @@ type PageLoaderProps =
--, corpusInfo :: Maybe (NodePoly CorpusInfo)
}
getTable :: TabType -> Maybe Int -> Aff NgramsTable
getTable tab = get <<< toUrl Back (Ngrams tab Nothing)
getTable :: CTabNgramType -> Maybe Int -> Aff NgramsTable
getTable tab = get <<< toUrl Back (Ngrams (TabCorpus (TabNgramType tab)) Nothing)
modeTabType :: Mode -> TabType
modeTabType Authors = TabAuthors
modeTabType Sources = TabSources
modeTabType Institutes = TabInstitutes
modeTabType Terms = TabTerms
modeTabType :: Mode -> CTabNgramType
modeTabType Authors = CTabAuthors
modeTabType Sources = CTabSources
modeTabType Institutes = CTabInstitutes
modeTabType Terms = CTabTerms
loadPage :: PageParams -> Aff NgramsTable
loadPage {nodeId, mode} = getTable (modeTabType mode) (Just nodeId) -- TODO this ignores params
......
......@@ -6,21 +6,18 @@ import Data.List (fromFoldable)
import Data.Tuple (Tuple(..))
import Gargantext.Pages.Corpus.Tabs.Types (Props)
import Gargantext.Pages.Corpus.Tabs.States (State(), initialState, _activeTab)
import Gargantext.Pages.Corpus.Tabs.Actions (Action(), _TabAction)
import Gargantext.Pages.Corpus.Tabs.Documents as DV
import Gargantext.Pages.Corpus.Tabs.Ngrams.NgramsTable as NV
import Gargantext.Components.Tab as Tab
import Thermite (Spec, focus, hideState, noState, cmapProps)
pureTabs :: Spec {} Props Void
pureTabs = hideState (const {activeTab: 0}) statefulTabs
-- pureTabs :: Spec {} Props Void
-- pureTabs = hideState initialState statefulTabs
statefulTabs :: Spec State Props Action
statefulTabs :: Spec Tab.State Props Tab.Action
statefulTabs =
Tab.tabs _activeTab _TabAction $ fromFoldable
Tab.tabs identity identity $ fromFoldable
[ Tuple "Documents" $ noState DV.docViewSpec
, Tuple "Authors" $ ngramsViewSpec {mode: NV.Authors}
, Tuple "Sources" $ ngramsViewSpec {mode: NV.Sources}
......@@ -29,7 +26,7 @@ statefulTabs =
, Tuple "Trash" $ noState DV.docViewSpec -- TODO pass-in trash mode
]
ngramsViewSpec :: {mode :: NV.Mode} -> Spec State Props Action
ngramsViewSpec :: {mode :: NV.Mode} -> Spec Tab.State Props Tab.Action
ngramsViewSpec {mode} =
cmapProps (\{loaded, path, dispatch} -> {mode,loaded,path, dispatch})
(noState NV.ngramsTableSpec)
module Gargantext.Pages.Corpus.Tabs.States where
import Data.Lens (Lens', lens)
import Gargantext.Components.Tab as Tab
type State =
{ activeTab :: Int
}
initialState :: {} -> State
initialState _ =
{ activeTab: 0
}
_activeTab :: Lens' State Tab.State
_activeTab = lens _.activeTab (\s ss -> s {activeTab = ss})
......@@ -10,7 +10,6 @@ import Gargantext.Pages.Corpus.Document as Document
import Gargantext.Pages.Corpus.Graph as GE
-- import Gargantext.Pages.Corpus.Tabs.Terms.NgramsTable as NG
import Gargantext.Pages.Annuaire.User.Contacts as C
-- import Gargantext.Pages.Home as L
-- import Gargantext.Pages.Layout.Specs.Search as S
import Gargantext.Router (Routes(..))
......@@ -40,13 +39,9 @@ dispatchAction dispatcher _ SearchView = do
dispatchAction dispatcher _ (UserPage id) = do
dispatcher $ SetRoute $ UserPage id
-- dispatcher $ UserPageA TODO
dispatcher $ UserPageA $ C.FetchContact id
dispatchAction dispatcher _ (ContactPage id) = do
dispatcher $ SetRoute $ ContactPage id
-- dispatcher $ UserPageA TODO
dispatcher $ UserPageA $ C.FetchContact id
dispatchAction dispatcher _ (Annuaire id) = do
dispatcher $ SetRoute $ Annuaire id
......
......@@ -12,7 +12,6 @@ import Routing.Hash (setHash)
import Gargantext.Components.Login as LN
import Gargantext.Components.Modals.Modal (modalShow)
import Gargantext.Pages.Annuaire as Annuaire
import Gargantext.Pages.Annuaire.User.Contacts as C
import Gargantext.Pages.Corpus.Document as D
import Gargantext.Pages.Corpus.Graph as GE
import Gargantext.Pages.Layout.Specs.AddCorpus as AC
......@@ -32,7 +31,6 @@ data Action
| GraphExplorerA GE.Action
| DocumentViewA D.Action
| AnnuaireAction Annuaire.Action
| UserPageA C.Action
| Go
| ShowLogin
| Logout
......@@ -76,7 +74,6 @@ performAction Go _ _ = void do
performAction (LoginA _) _ _ = pure unit
performAction (AddCorpusA _) _ _ = pure unit
performAction (SearchA _) _ _ = pure unit
performAction (UserPageA _) _ _ = pure unit
performAction (DocumentViewA _) _ _ = pure unit
performAction (GraphExplorerA _) _ _ = pure unit
performAction (AnnuaireAction _) _ _ = pure unit
......@@ -101,12 +98,6 @@ _searchAction = prism SearchA \action ->
SearchA caction -> Right caction
_-> Left action
_userPageAction :: Prism' Action C.Action
_userPageAction = prism UserPageA \action ->
case action of
UserPageA caction -> Right caction
_-> Left action
_annuaireAction :: Prism' Action Annuaire.Action
_annuaireAction = prism AnnuaireAction \action ->
case action of
......
......@@ -23,10 +23,10 @@ import Gargantext.Pages.Corpus.Document as Annotation
import Gargantext.Pages.Corpus.Dashboard as Dsh
import Gargantext.Pages.Corpus.Graph as GE
import Gargantext.Pages.Home as L
import Gargantext.Pages.Layout.Actions (Action(..), _addCorpusAction, _documentViewAction, _graphExplorerAction, _loginAction, _searchAction, _userPageAction, performAction)
import Gargantext.Pages.Layout.Actions (Action(..), _addCorpusAction, _documentViewAction, _graphExplorerAction, _loginAction, _searchAction, performAction)
import Gargantext.Pages.Layout.Specs.AddCorpus as AC
import Gargantext.Pages.Layout.Specs.Search as S
import Gargantext.Pages.Layout.States (AppState, _addCorpusState, _documentViewState, _graphExplorerState, _loginState, _searchState, _userPageState)
import Gargantext.Pages.Layout.States (AppState, _addCorpusState, _documentViewState, _graphExplorerState, _loginState, _searchState)
import Gargantext.Router (Routes(..))
layoutSpec :: Spec AppState {} Action
......@@ -63,8 +63,8 @@ pagesComponent s = case s.currentRoute of
selectSpec Dashboard = layout0 $ noState Dsh.layoutDashboard
selectSpec (Annuaire i) = layout0 $ cmapProps (const {annuaireId: i}) $ noState A.layout
selectSpec (UserPage i) = layout0 $ focus _userPageState _userPageAction C.layoutUser
selectSpec (ContactPage i) = layout0 $ focus _userPageState _userPageAction C.layoutUser
selectSpec (UserPage i) = layout0 $ cmapProps (const {nodeId: i}) $ noState C.layoutUser
selectSpec (ContactPage i) = layout0 $ cmapProps (const {nodeId: i}) $ noState C.layoutUser
-- selectSpec _ = simpleSpec defaultPerformAction defaultRender
......
......@@ -9,7 +9,6 @@ import Gargantext.Components.Login as LN
import Gargantext.Pages.Corpus.Document as D
import Gargantext.Pages.Corpus.Graph as GE
import Gargantext.Pages.Annuaire.User.Contacts as C
import Gargantext.Pages.Layout.Specs.AddCorpus as AC
import Gargantext.Pages.Layout.Specs.Search as S
import Gargantext.Router (Routes(..))
......@@ -19,7 +18,6 @@ type AppState =
, loginState :: LN.State
, addCorpusState :: AC.State
, searchState :: S.State
, userPageState :: C.State
, documentState :: D.State
, search :: String
, showLogin :: Boolean
......@@ -36,7 +34,6 @@ initAppState = do
, loginState
, addCorpusState : AC.initialState
, searchState : S.initialState
, userPageState : C.initialState
, documentState : D.initialState {}
, search : ""
, showLogin : false
......@@ -55,9 +52,6 @@ _addCorpusState = lens (\s -> s.addCorpusState) (\s ss -> s{addCorpusState = ss}
_searchState :: Lens' AppState S.State
_searchState = lens (\s -> s.searchState) (\s ss -> s{searchState = ss})
_userPageState :: Lens' AppState C.State
_userPageState = lens (\s -> s.userPageState) (\s ss -> s{userPageState = ss})
_documentViewState :: Lens' AppState D.State
_documentViewState = lens (\s -> s.documentState) (\s ss -> s{documentState = ss})
......
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