Commit 95650e89 authored by Mael NICOLAS's avatar Mael NICOLAS

upgraded mapMyMap, need to change HyperData type

parent 63c4610a
......@@ -3,11 +3,13 @@ module Gargantext.Pages.Annuaire.User.Users.Specs.Renders
import Gargantext.Pages.Annuaire.User.Users.Types
import Data.List (List, toUnfoldable, zip)
import Data.Map (Map, empty, keys, values)
import Data.List (List, zipWith, catMaybes, toUnfoldable)
import Data.Unfoldable (class Unfoldable)
import Data.Map (Map, empty, keys, values, lookup)
import Data.Set (toUnfoldable) as S
import Data.Maybe (Maybe(..))
import Data.Tuple (Tuple(..), uncurry)
import Prelude (($), (<<<), (<$>))
import Prelude (($), (<<<), (<$>), flip, class Ord)
import React (ReactElement)
import React.DOM (div, h3, img, li, span, text, ul)
import React.DOM.Props (_id, className, src)
......@@ -37,15 +39,18 @@ display title elems =
[ div [className "col-md-2"]
[ img [src "/images/Gargantextuel-212x300.jpg"] ]
, div [className "col-md-1"] []
, div [className "col-md-8"] elems
, div [className "col-mdData.Unfoldable-8"] elems
]
]
]
]
]
mapMyMap :: forall k v x. (k -> v -> x) -> Map k v -> Array x
mapMyMap f m = toUnfoldable $ uncurry f <$> zip (keys m) (values m)
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 <.~$>
......@@ -57,8 +62,8 @@ userInfos hyperdata =
checkMaybe (Nothing) = empty
checkMaybe (Just (HyperData a)) = a
listInfo :: String -> String -> ReactElement
listInfo s ss = listElement $ infoRender s ss
listInfo :: Tuple String String -> ReactElement
listInfo s = listElement $ infoRender s
listElement :: Array ReactElement -> ReactElement
listElement = li [className "list-group-item justify-content-between"]
......
module Gargantext.Pages.Corpus.User.Users.Actions where
import Gargantext.Pages.Folder as PS
import Gargantext.Pages.Corpus.Doc.Facets.Documents as P
import Gargantext.Components.Tab as Tab
data Action
= NoOp
| PublicationA P.Action
| BrevetsA B.Action
| ProjectsA PS.Action
| TabA Tab.Action
| FetchUser Int
----------------------------------------------
_tabAction :: Prism' Action Tab.Action
_tabAction = prism TabA \ action ->
case action of
TabA laction -> Right laction
_-> Left action
_pubAction :: Prism' Action P.Action
_pubAction = prism PublicationA \ action ->
case action of
PublicationA laction -> Right laction
_-> Left action
_brevetsAction :: Prism' Action B.Action
_brevetsAction = prism BrevetsA \ action ->
case action of
BrevetsA laction -> Right laction
_-> Left action
_projectsAction :: Prism' Action PS.Action
_projectsAction = prism ProjectsA \ action ->
case action of
ProjectsA laction -> Right laction
_-> Left action
module Gargantext.Pages.Corpus.User.Users.States where
import Gargantext.Pages.Corpus.User.Brevets as B
import Data.Maybe (Maybe(..))
import Gargantext.Pages.Corpus.User.Users.Types.Types (User)
import Gargantext.Pages.Folder as PS
import Gargantext.Pages.Corpus.Doc.Facets.Documents as P
import Gargantext.Components.Tab as Tab
type State =
{ activeTab :: Int
, publications :: P.State
, brevets :: B.State
, projects :: PS.State
, user :: Maybe User
}
initialState :: State
initialState =
{ activeTab : 0
, publications : P.initialState
, brevets : B.initialState
, projects : PS.initialState
, user: Nothing
}
------------------------------------------------------
_tablens :: Lens' State Tab.State
_tablens = lens (\s -> s.activeTab) (\s ss -> s {activeTab = ss})
_publens :: Lens' State P.State
_publens = lens (\s -> s.publications) (\s ss -> s { publications= ss})
_brevetslens :: Lens' State B.State
_brevetslens = lens (\s -> s.brevets) (\s ss -> s {brevets = ss})
_projectslens :: Lens' State PS.State
_projectslens = lens (\s -> s.projects) (\s ss -> s {projects = ss})
_user :: Lens' State (Maybe User)
_user = lens (\s -> s.user) (\s ss -> s{user = 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