Commit 32c5689d authored by Mael NICOLAS's avatar Mael NICOLAS

changed User to Contact, need to resolve some issue on the type

parent dcf2f584
...@@ -20,7 +20,7 @@ import Effect.Aff (Aff) ...@@ -20,7 +20,7 @@ import Effect.Aff (Aff)
import Gargantext.Config (toUrl, NodeType(..), End(..)) import Gargantext.Config (toUrl, NodeType(..), End(..))
import Gargantext.Config.REST (get) import Gargantext.Config.REST (get)
import Gargantext.Pages.Annuaire.User.Users.Types.Types (User(..), HyperData(..)) import Gargantext.Pages.Annuaire.User.Contacts.Types.Types (Contact(..), HyperData(..))
import Gargantext.Utils.DecodeMaybe ((.?|)) import Gargantext.Utils.DecodeMaybe ((.?|))
import Data.Argonaut (class DecodeJson, decodeJson, (.?)) import Data.Argonaut (class DecodeJson, decodeJson, (.?))
...@@ -75,7 +75,7 @@ defaultAnnuaireInfo = AnnuaireInfo { id : 0 ...@@ -75,7 +75,7 @@ defaultAnnuaireInfo = AnnuaireInfo { id : 0
, hyperdata : "" , hyperdata : ""
} }
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
toRows :: AnnuaireTable -> Array (Maybe User) toRows :: AnnuaireTable -> Array (Maybe Contact)
toRows (AnnuaireTable a) = a.annuaireTable toRows (AnnuaireTable a) = a.annuaireTable
layoutAnnuaire :: Spec State {} Action layoutAnnuaire :: Spec State {} Action
...@@ -126,14 +126,14 @@ render dispatch _ state _ = [ div [className "row"] ...@@ -126,14 +126,14 @@ render dispatch _ state _ = [ div [className "row"]
individuals = maybe (toRows defaultAnnuaireTable) toRows state.stable individuals = maybe (toRows defaultAnnuaireTable) toRows state.stable
showRow :: Maybe User -> ReactElement showRow :: Maybe Contact -> ReactElement
showRow Nothing = tr [][] showRow Nothing = tr [][]
showRow (Just (User { id : id, hyperdata : (HyperData user) })) = showRow (Just (Contact { id : id, hyperdata : (HyperData contact) })) =
tr [] tr []
[ td [] [ a [ href (toUrl Back NodeUser id) ] [ text $ maybe' user.nom <> " " <> maybe' user.prenom ] ] [ td [] [ a [ href (toUrl Back NodeUser id) ] [ text $ maybe' contact.nom <> " " <> maybe' contact.prenom ] ]
, td [] [text $ maybe' user.fonction] , td [] [text $ maybe' contact.fonction]
, td [] [text $ maybe' user.service] , td [] [text $ maybe' contact.service]
, td [] [text $ maybe' user.groupe] , td [] [text $ maybe' contact.groupe]
] ]
where where
maybe' = maybe "" identity maybe' = maybe "" identity
...@@ -169,7 +169,7 @@ instance decodeAnnuaireInfo :: DecodeJson AnnuaireInfo where ...@@ -169,7 +169,7 @@ instance decodeAnnuaireInfo :: DecodeJson AnnuaireInfo where
} }
newtype AnnuaireTable = AnnuaireTable { annuaireTable :: Array (Maybe User)} newtype AnnuaireTable = AnnuaireTable { annuaireTable :: Array (Maybe Contact)}
instance decodeAnnuaireTable :: DecodeJson AnnuaireTable where instance decodeAnnuaireTable :: DecodeJson AnnuaireTable where
decodeJson json = do decodeJson json = do
rows <- decodeJson json rows <- decodeJson json
...@@ -177,7 +177,6 @@ instance decodeAnnuaireTable :: DecodeJson AnnuaireTable where ...@@ -177,7 +177,6 @@ instance decodeAnnuaireTable :: DecodeJson AnnuaireTable where
------------------------------------------------------------------------ ------------------------------------------------------------------------
performAction :: PerformAction State {} Action performAction :: PerformAction State {} Action
performAction (Load aId) _ _ = do performAction (Load aId) _ _ = do
eitherInfo <- lift $ getInfo aId eitherInfo <- lift $ getInfo aId
_ <- case eitherInfo of _ <- case eitherInfo of
(Right info') -> void $ modifyState $ _info ?~ info' (Right info') -> void $ modifyState $ _info ?~ info'
......
module Gargantext.Pages.Annuaire.User.Contacts
(module Gargantext.Pages.Annuaire.User.Contacts.Types,
module Gargantext.Pages.Annuaire.User.Contacts.Specs)
where
import Gargantext.Pages.Annuaire.User.Contacts.Types
import Gargantext.Pages.Annuaire.User.Contacts.Specs
module Gargantext.Pages.Annuaire.User.Users.API where module Gargantext.Pages.Annuaire.User.Contacts.API where
import Prelude import Prelude
...@@ -12,19 +12,19 @@ import Effect.Console (log) ...@@ -12,19 +12,19 @@ import Effect.Console (log)
import Gargantext.Config (toUrl, NodeType(..), End(..)) import Gargantext.Config (toUrl, NodeType(..), End(..))
import Gargantext.Config.REST (get) import Gargantext.Config.REST (get)
import Gargantext.Pages.Annuaire.User.Users.Types (Action(..), State, User, _user) import Gargantext.Pages.Annuaire.User.Contacts.Types (Action(..), State, Contact, _contact)
import Thermite (PerformAction, modifyState) import Thermite (PerformAction, modifyState)
getUser :: Int -> Aff (Either String User) getUser :: Int -> Aff (Either String Contact)
getUser id = get $ toUrl Back Node id getUser id = get $ toUrl Back Node id
performAction :: PerformAction State {} Action performAction :: PerformAction State {} Action
performAction (FetchUser userId) _ _ = do performAction (FetchContact contactId) _ _ = do
value <- lift $ getUser userId value <- lift $ getUser contactId
_ <- case value of _ <- case value of
(Right user) -> void $ modifyState $ _user ?~ user (Right contact) -> void $ modifyState $ _contact ?~ contact
(Left err) -> do (Left err) -> do
liftEffect $ log err liftEffect $ log err
liftEffect <<< log $ "Fetching user..." liftEffect <<< log $ "Fetching contact..."
performAction _ _ _ = pure unit performAction _ _ _ = pure unit
module Gargantext.Pages.Annuaire.User.Users.Specs module Gargantext.Pages.Annuaire.User.Contacts.Specs
(module Gargantext.Pages.Annuaire.User.Users.Specs.Renders, (module Gargantext.Pages.Annuaire.User.Contacts.Specs.Renders,
layoutUser) layoutUser)
where where
import Gargantext.Pages.Annuaire.User.Users.Specs.Renders import Gargantext.Pages.Annuaire.User.Contacts.Specs.Renders
import Thermite (Spec, simpleSpec) import Thermite (Spec, simpleSpec)
import Gargantext.Pages.Annuaire.User.Users.Types (Action, State) import Gargantext.Pages.Annuaire.User.Contacts.Types (Action, State)
import Gargantext.Pages.Annuaire.User.Users.API (performAction) import Gargantext.Pages.Annuaire.User.Contacts.API (performAction)
layoutUser :: Spec State {} Action layoutUser :: Spec State {} Action
layoutUser = simpleSpec performAction render layoutUser = simpleSpec performAction render
module Gargantext.Pages.Annuaire.User.Users.Specs.Documents where module Gargantext.Pages.Annuaire.User.Contacts.Specs.Documents where
import Prelude import Prelude
import React.DOM (table, tbody, td, text, th, thead, tr) import React.DOM (table, tbody, td, text, th, thead, tr)
......
module Gargantext.Pages.Annuaire.User.Users.Specs.Renders module Gargantext.Pages.Annuaire.User.Contacts.Specs.Renders
where where
import Gargantext.Pages.Annuaire.User.Users.Types import Gargantext.Pages.Annuaire.User.Contacts.Types
import Data.List (List, zipWith, catMaybes, toUnfoldable) import Data.List (List, zipWith, catMaybes, toUnfoldable)
import Data.Unfoldable (class Unfoldable) import Data.Unfoldable (class Unfoldable)
...@@ -20,20 +20,20 @@ render :: Render State {} Action ...@@ -20,20 +20,20 @@ render :: Render State {} Action
render dispatch _ state _ = render dispatch _ state _ =
[ [
div [className "col-md-12"] div [className "col-md-12"]
$ case state.user of $ case state.contact of
(Just (User user)) -> display user.name [userInfos user.hyperdata] (Just (Contact contact)) -> display contact.name [contactInfos contact.hyperdata]
Nothing -> display "User not found" [] Nothing -> display "Contact not found" []
] ]
display :: String -> Array ReactElement -> Array ReactElement display :: String -> Array ReactElement -> Array ReactElement
display title elems = display title elems =
[ div [className "container-fluid"] [ div [className "container-fluid"]
[ div [className "row", _id "user-page-header"] [ div [className "row", _id "contact-page-header"]
[ div [className "col-md-6"] [ h3 [] [text title] ] [ div [className "col-md-6"] [ h3 [] [text title] ]
, div [className "col-md-8"] [] , div [className "col-md-8"] []
, div [className "col-md-2"] [ span [] [text ""] ] , div [className "col-md-2"] [ span [] [text ""] ]
] ]
, div [className "row", _id "user-page-info"] , div [className "row", _id "contact-page-info"]
[ div [className "col-md-12"] [ div [className "col-md-12"]
[ div [className "row"] [ div [className "row"]
[ div [className "col-md-2"] [ div [className "col-md-2"]
...@@ -54,8 +54,8 @@ mapMyMap f m = toUnfoldable ...@@ -54,8 +54,8 @@ mapMyMap f m = toUnfoldable
infixl 4 mapMyMap as <.~$> infixl 4 mapMyMap as <.~$>
userInfos :: Maybe HyperData -> ReactElement contactInfos :: Maybe HyperData -> ReactElement
userInfos hyperdata = contactInfos hyperdata =
ul [className "list-group"] $ ul [className "list-group"] $
listInfo <.~$> (checkMaybe hyperdata) listInfo <.~$> (checkMaybe hyperdata)
where where
......
module Gargantext.Pages.Annuaire.User.Users.Types module Gargantext.Pages.Annuaire.User.Contacts.Types
(module Gargantext.Pages.Annuaire.User.Users.Types.Types, (module Gargantext.Pages.Annuaire.User.Contacts.Types.Types,
module Gargantext.Pages.Annuaire.User.Users.Types.Lens, module Gargantext.Pages.Annuaire.User.Contacts.Types.Lens,
module Gargantext.Pages.Annuaire.User.Users.Types.States, module Gargantext.Pages.Annuaire.User.Contacts.Types.States,
brevetSpec, brevetSpec,
projectSpec, projectSpec,
facets facets
...@@ -10,9 +10,9 @@ module Gargantext.Pages.Annuaire.User.Users.Types ...@@ -10,9 +10,9 @@ module Gargantext.Pages.Annuaire.User.Users.Types
import Prelude import Prelude
import Gargantext.Pages.Annuaire.User.Users.Types.Lens import Gargantext.Pages.Annuaire.User.Contacts.Types.Lens
import Gargantext.Pages.Annuaire.User.Users.Types.Types import Gargantext.Pages.Annuaire.User.Contacts.Types.Types
import Gargantext.Pages.Annuaire.User.Users.Types.States import Gargantext.Pages.Annuaire.User.Contacts.Types.States
import Gargantext.Pages.Annuaire.User.Brevets as B import Gargantext.Pages.Annuaire.User.Brevets as B
import Data.List (fromFoldable) import Data.List (fromFoldable)
import Data.Tuple (Tuple(..)) import Data.Tuple (Tuple(..))
......
module Gargantext.Pages.Annuaire.User.Users.Types.Lens where module Gargantext.Pages.Annuaire.User.Contacts.Types.Lens where
import Gargantext.Pages.Annuaire.User.Brevets as B import Gargantext.Pages.Annuaire.User.Brevets as B
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.Lens (Lens', Prism', lens, prism) import Data.Lens (Lens', Prism', lens, prism)
import Data.Maybe (Maybe) import Data.Maybe (Maybe)
import Gargantext.Pages.Annuaire.User.Users.Types.States (Action(..), State) import Gargantext.Pages.Annuaire.User.Contacts.Types.States (Action(..), State)
import Gargantext.Pages.Annuaire.User.Users.Types.Types (User) import Gargantext.Pages.Annuaire.User.Contacts.Types.Types (Contact)
import Gargantext.Pages.Annuaire.User.Users.Specs.Documents as P import Gargantext.Pages.Annuaire.User.Contacts.Specs.Documents as P
import Gargantext.Components.Tab as Tab import Gargantext.Components.Tab as Tab
import Thermite (Spec, noState) import Thermite (Spec, noState)
_user :: Lens' State (Maybe User) _contact :: Lens' State (Maybe Contact)
_user = lens (\s -> s.user) (\s ss -> s{user = ss}) _contact = lens (\s -> s.contact) (\s ss -> s{contact = ss})
_tablens :: Lens' State Tab.State _tablens :: Lens' State Tab.State
_tablens = lens (\s -> s.activeTab) (\s ss -> s {activeTab = ss}) _tablens = lens (\s -> s.activeTab) (\s ss -> s {activeTab = ss})
......
module Gargantext.Pages.Annuaire.User.Users.Types.States where module Gargantext.Pages.Annuaire.User.Contacts.Types.States where
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Gargantext.Pages.Annuaire.User.Users.Types.Types (User) import Gargantext.Pages.Annuaire.User.Contacts.Types.Types (Contact)
import Gargantext.Pages.Annuaire.User.Users.Specs.Documents as P import Gargantext.Pages.Annuaire.User.Contacts.Specs.Documents as P
import Gargantext.Components.Tab as Tab import Gargantext.Components.Tab as Tab
data Action data Action
= TabA Tab.Action = TabA Tab.Action
| FetchUser Int | FetchContact Int
type State = type State =
{ activeTab :: Int { activeTab :: Int
, user :: Maybe User , contact :: Maybe Contact
} }
initialState :: State initialState :: State
initialState = initialState =
{ activeTab : 0 { activeTab : 0
, user: Nothing , contact : Nothing
} }
module Gargantext.Pages.Annuaire.User.Users.Types.Types where module Gargantext.Pages.Annuaire.User.Contacts.Types.Types where
import Prelude import Prelude
...@@ -36,8 +36,8 @@ the "user" field is encapsulated in a Maybe. ...@@ -36,8 +36,8 @@ the "user" field is encapsulated in a Maybe.
-} -}
newtype User = newtype Contact =
User { id :: Int Contact { id :: Int
, typename :: Maybe Int , typename :: Maybe Int
, userId :: Int , userId :: Int
, parentId :: Int , parentId :: Int
...@@ -105,7 +105,7 @@ instance decodeUserHyperData :: DecodeJson HyperData where ...@@ -105,7 +105,7 @@ instance decodeUserHyperData :: DecodeJson HyperData where
, entite2, mail , entite2, mail
} }
instance decodeUser :: DecodeJson User where instance decodeUser :: DecodeJson Contact where
decodeJson json = do decodeJson json = do
obj <- decodeJson json obj <- decodeJson json
id <- obj .? "id" id <- obj .? "id"
...@@ -115,7 +115,7 @@ instance decodeUser :: DecodeJson User where ...@@ -115,7 +115,7 @@ instance decodeUser :: DecodeJson User where
name <- obj .? "name" name <- obj .? "name"
date <- obj .?| "date" date <- obj .?| "date"
hyperdata <- obj .? "hyperdata" hyperdata <- obj .? "hyperdata"
pure $ User { id, typename, userId pure $ Contact { id, typename, userId
, parentId, name, date , parentId, name, date
, hyperdata , hyperdata
} }
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
...@@ -12,7 +12,7 @@ import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV ...@@ -12,7 +12,7 @@ import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV
import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE
-- import Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsTable as NG -- import Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsTable as NG
import Gargantext.Pages.Annuaire.User.Users as U import Gargantext.Pages.Annuaire.User.Contacts as C
import Gargantext.Pages.Annuaire as Annuaire import Gargantext.Pages.Annuaire as Annuaire
-- import Gargantext.Pages.Home as L -- import Gargantext.Pages.Home as L
-- import Gargantext.Pages.Layout.Specs.Search as S -- import Gargantext.Pages.Layout.Specs.Search as S
...@@ -51,7 +51,7 @@ dispatchAction dispatcher _ SearchView = do ...@@ -51,7 +51,7 @@ dispatchAction dispatcher _ SearchView = do
dispatchAction dispatcher _ (UserPage id) = do dispatchAction dispatcher _ (UserPage id) = do
dispatcher $ SetRoute $ UserPage id dispatcher $ SetRoute $ UserPage id
-- dispatcher $ UserPageA TODO -- dispatcher $ UserPageA TODO
dispatcher $ UserPageA $ U.FetchUser id dispatcher $ UserPageA $ C.FetchContact id
dispatchAction dispatcher _ (Annuaire id) = do dispatchAction dispatcher _ (Annuaire id) = do
dispatcher $ SetRoute $ Annuaire id dispatcher $ SetRoute $ Annuaire id
......
...@@ -17,7 +17,7 @@ import Gargantext.Pages.Corpus as Corpus ...@@ -17,7 +17,7 @@ import Gargantext.Pages.Corpus as Corpus
import Gargantext.Pages.Corpus.Doc.Annotation as D import Gargantext.Pages.Corpus.Doc.Annotation as D
import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV
import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE
import Gargantext.Pages.Annuaire.User.Users as U import Gargantext.Pages.Annuaire.User.Contacts as C
import Gargantext.Pages.Annuaire as Annuaire import Gargantext.Pages.Annuaire as Annuaire
import Gargantext.Pages.Layout.Specs.AddCorpus as AC import Gargantext.Pages.Layout.Specs.AddCorpus as AC
import Gargantext.Pages.Layout.Specs.Search as S import Gargantext.Pages.Layout.Specs.Search as S
...@@ -40,7 +40,7 @@ data Action ...@@ -40,7 +40,7 @@ data Action
| GraphExplorerA GE.Action | GraphExplorerA GE.Action
| DocAnnotationViewA D.Action | DocAnnotationViewA D.Action
| AnnuaireAction Annuaire.Action | AnnuaireAction Annuaire.Action
| UserPageA U.Action | UserPageA C.Action
| Go | Go
| ShowLogin | ShowLogin
| ShowAddcorpus | ShowAddcorpus
...@@ -140,7 +140,7 @@ _searchAction = prism SearchA \action -> ...@@ -140,7 +140,7 @@ _searchAction = prism SearchA \action ->
SearchA caction -> Right caction SearchA caction -> Right caction
_-> Left action _-> Left action
_userPageAction :: Prism' Action U.Action _userPageAction :: Prism' Action C.Action
_userPageAction = prism UserPageA \action -> _userPageAction = prism UserPageA \action ->
case action of case action of
UserPageA caction -> Right caction UserPageA caction -> Right caction
......
...@@ -18,7 +18,7 @@ import Gargantext.Pages.Corpus.Doc.Facets.Dashboard as Dsh ...@@ -18,7 +18,7 @@ import Gargantext.Pages.Corpus.Doc.Facets.Dashboard as Dsh
import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV
import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE
import Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsTable as NG import Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsTable as NG
import Gargantext.Pages.Annuaire.User.Users as U import Gargantext.Pages.Annuaire.User.Contacts as C
import Gargantext.Pages.Home as L import Gargantext.Pages.Home as L
import Gargantext.Pages.Layout.Actions (Action(..), _corpusAction, _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.AddCorpus as AC
...@@ -59,7 +59,7 @@ pagesComponent s = ...@@ -59,7 +59,7 @@ pagesComponent s =
selectSpec Home = layout0 $ noState (L.layoutLanding EN) selectSpec Home = layout0 $ noState (L.layoutLanding EN)
selectSpec AddCorpus = layout0 $ focus _addCorpusState _addCorpusAction AC.layoutAddcorpus selectSpec AddCorpus = layout0 $ focus _addCorpusState _addCorpusAction AC.layoutAddcorpus
selectSpec (DocView i) = layout0 $ focus _docViewState _docViewAction DV.layoutDocview selectSpec (DocView i) = layout0 $ focus _docViewState _docViewAction DV.layoutDocview
selectSpec (UserPage i) = layout0 $ focus _userPageState _userPageAction U.layoutUser selectSpec (UserPage i) = layout0 $ focus _userPageState _userPageAction C.layoutUser
selectSpec (DocAnnotation i) = layout0 $ focus _docAnnotationViewState selectSpec (DocAnnotation i) = layout0 $ focus _docAnnotationViewState
_docAnnotationViewAction Annotation.docview _docAnnotationViewAction Annotation.docview
-- To be removed -- To be removed
......
...@@ -12,7 +12,7 @@ import Gargantext.Pages.Corpus.Doc.Annotation as D ...@@ -12,7 +12,7 @@ import Gargantext.Pages.Corpus.Doc.Annotation as D
import Gargantext.Pages.Annuaire as Annuaire import Gargantext.Pages.Annuaire as Annuaire
import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV
import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE
import Gargantext.Pages.Annuaire.User.Users as U import Gargantext.Pages.Annuaire.User.Contacts as C
import Gargantext.Pages.Layout.Specs.AddCorpus as AC import Gargantext.Pages.Layout.Specs.AddCorpus as AC
import Gargantext.Pages.Layout.Specs.Search as S import Gargantext.Pages.Layout.Specs.Search as S
import Gargantext.Router (Routes(..)) import Gargantext.Router (Routes(..))
...@@ -24,7 +24,7 @@ type AppState = ...@@ -24,7 +24,7 @@ type AppState =
, addCorpusState :: AC.State , addCorpusState :: AC.State
, docViewState :: DV.State , docViewState :: DV.State
, searchState :: S.State , searchState :: S.State
, userPageState :: U.State , userPageState :: C.State
, docAnnotationState :: D.State , docAnnotationState :: D.State
, annuaireState :: Annuaire.State , annuaireState :: Annuaire.State
, ntreeState :: Tree.State , ntreeState :: Tree.State
...@@ -43,7 +43,7 @@ initAppState = ...@@ -43,7 +43,7 @@ initAppState =
, addCorpusState : AC.initialState , addCorpusState : AC.initialState
, docViewState : DV.tdata , docViewState : DV.tdata
, searchState : S.initialState , searchState : S.initialState
, userPageState : U.initialState , userPageState : C.initialState
, docAnnotationState : D.initialState , docAnnotationState : D.initialState
, ntreeState : Tree.exampleTree , ntreeState : Tree.exampleTree
, annuaireState : Annuaire.initialState , annuaireState : Annuaire.initialState
...@@ -70,7 +70,7 @@ _docViewState = lens (\s -> s.docViewState) (\s ss -> s{docViewState = ss}) ...@@ -70,7 +70,7 @@ _docViewState = lens (\s -> s.docViewState) (\s ss -> s{docViewState = ss})
_searchState :: Lens' AppState S.State _searchState :: Lens' AppState S.State
_searchState = lens (\s -> s.searchState) (\s ss -> s{searchState = ss}) _searchState = lens (\s -> s.searchState) (\s ss -> s{searchState = ss})
_userPageState :: Lens' AppState U.State _userPageState :: Lens' AppState C.State
_userPageState = lens (\s -> s.userPageState) (\s ss -> s{userPageState = ss}) _userPageState = lens (\s -> s.userPageState) (\s ss -> s{userPageState = ss})
_annuaireState :: Lens' AppState Annuaire.State _annuaireState :: Lens' AppState Annuaire.State
......
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