Commit 003e3880 authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

Merge branch 'dev-graphql' into dev-node-calc-parser

parents 99a9f95a 63d64b4d
...@@ -29,6 +29,7 @@ ...@@ -29,6 +29,7 @@
}, },
"dependencies": { "dependencies": {
"@popperjs/core": "^2.9.2", "@popperjs/core": "^2.9.2",
"@urql/core": "^2.3.3",
"aes-js": "^3.1.1", "aes-js": "^3.1.1",
"base-x": "^3.0.2", "base-x": "^3.0.2",
"bootstrap": "^4.6.0", "bootstrap": "^4.6.0",
...@@ -36,8 +37,11 @@ ...@@ -36,8 +37,11 @@
"create-react-class": "^15.6.3", "create-react-class": "^15.6.3",
"echarts": "^5.1.2", "echarts": "^5.1.2",
"echarts-for-react": "^3.0.1", "echarts-for-react": "^3.0.1",
"graphql": "^15.6.1",
"graphql-ws": "^5.5.0",
"highlightjs": "^9.16.2", "highlightjs": "^9.16.2",
"immer": "^9.0.5", "immer": "^9.0.5",
"isomorphic-unfetch": "^3.1.0",
"prop-types": "^15.6.2", "prop-types": "^15.6.2",
"pullstate": "^1.20.6", "pullstate": "^1.20.6",
"react": "^17.0.2", "react": "^17.0.2",
......
let upstream = let upstream =
https://github.com/purescript/package-sets/releases/download/psc-0.14.4-20210826/packages.dhall sha256:eee0765aa98e0da8fc414768870ad588e7cada060f9f7c23c37385c169f74d9f https://github.com/purescript/package-sets/releases/download/psc-0.14.4-20211030/packages.dhall sha256:5cd7c5696feea3d3f84505d311348b9e90a76c4ce3684930a0ff29606d2d816c
let overrides = let overrides =
{ globals = { globals =
...@@ -209,3 +209,4 @@ let additions = ...@@ -209,3 +209,4 @@ let additions =
} }
in upstream // overrides // additions in upstream // overrides // additions
...@@ -41,6 +41,7 @@ to generate this file without the comments in this block. ...@@ -41,6 +41,7 @@ to generate this file without the comments in this block.
, "formula" , "formula"
, "functions" , "functions"
, "globals" , "globals"
, "graphql-client"
, "http-methods" , "http-methods"
, "integers" , "integers"
, "js-timers" , "js-timers"
......
module Gargantext.Components.GraphQL where
import Gargantext.Prelude
import Affjax.RequestHeader as ARH
import Data.Argonaut.Decode (JsonDecodeError)
import Data.Bifunctor (lmap)
import Data.List.Types (NonEmptyList)
import Effect (Effect)
import Effect.Aff (Aff)
import Effect.Class (liftEffect)
import Foreign (unsafeToForeign, ForeignError)
import Gargantext.Components.GraphQL.User (User, UserInfo, UserInfoM)
import Gargantext.Sessions (Session(..))
import Gargantext.Utils.Reactix as R2
import GraphQL.Client.Args (type (==>))
import GraphQL.Client.BaseClients.Urql (UrqlClient, createClient)
import GraphQL.Client.Query (queryWithDecoder)
import GraphQL.Client.Types (class GqlQuery, Client, class QueryClient)
import Simple.JSON as JSON
import Unsafe.Coerce (unsafeCoerce)
here :: R2.Here
here = R2.here "Gargantext.Components.GraphQL"
--client :: Client AffjaxClient Schema Void Void
--client = Client $ AffjaxClient "http://localhost:8008/gql" []
-- | Run a graphQL query with a custom decoder and custom options
gqlQuery ::
forall client schema query returns a b queryOpts mutationOpts.
QueryClient client queryOpts mutationOpts =>
GqlQuery schema query returns =>
JSON.ReadForeign returns =>
--(queryOpts -> queryOpts) ->
(Client client schema a b) ->
String ->
query ->
Aff returns
gqlQuery = queryWithDecoder (unsafeToForeign >>> JSON.read >>> lmap toJsonError)
toJsonError :: NonEmptyList ForeignError -> JsonDecodeError
toJsonError = unsafeCoerce -- map ForeignErrors to JsonDecodeError as you wish
getClient :: Session -> Effect (Client UrqlClient Schema Mutation Void)
getClient (Session { token }) = createClient { headers, url: "http://localhost:8008/gql" }
where
headers = [ ARH.RequestHeader "Authorization" $ "Bearer " <> token ]
queryGql ::
forall query returns.
GqlQuery Schema query returns =>
JSON.ReadForeign returns =>
Session
-> String
-> query
-> Aff returns
queryGql session name q = do
--query client name q
client <- liftEffect $ getClient session
gqlQuery (client :: Client UrqlClient Schema Mutation Void) name q
--query_ "http://localhost:8008/gql" (Proxy :: Proxy Schema)
-- Schema
type Schema
= { user_infos :: { user_id :: Int } ==> Array UserInfo
, users :: { user_id :: Int } ==> Array User
}
type Mutation
= { update_user_info :: UserInfoM ==> Int }
module Gargantext.Components.GraphQL.AffjaxSimpleJSONClient
(AffjaxClient(..))
where
import Prelude
import Affjax (Error(..), Response, URL, defaultRequest, printError, request)
import Affjax.RequestBody as RequestBody
import Affjax.RequestHeader (RequestHeader(..))
import Affjax.ResponseFormat as ResponseFormat
import Data.Argonaut.Core (Json)
import Data.Either (Either(..))
import Data.HTTP.Method as Method
import Data.List.NonEmpty as DLN
import Data.Maybe (Maybe(..))
import Data.MediaType.Common (applicationJSON)
import Effect.Aff (Aff, error, throwError)
import Foreign (unsafeToForeign)
import GraphQL.Client.Types (class QueryClient)
import Simple.JSON as JSON
data AffjaxClient
= AffjaxClient URL (Array RequestHeader)
--
-- instance queryClient :: QueryClient AffjaxClient Unit Unit where
-- clientQuery _ (AffjaxClient url headers) name q vars = throwLeft =<< convertJsonResponse =<< queryPostForeign "query" url headers name q vars
-- clientMutation _ (AffjaxClient url headers) name q vars = throwLeft =<< convertJsonResponse =<< queryPostForeign "mutation" url headers name q vars
-- defQueryOpts = const unit
-- defMutationOpts = const unit
--
-- throwLeft :: forall r body. Either Error { body :: body | r } -> Aff body
-- throwLeft = case _ of
-- Left err -> throwError $ error $ printError err
-- Right { body } -> pure body
--
-- queryPostForeign ::
-- forall d.
-- JSON.WriteForeign d =>
-- String -> URL -> Array RequestHeader -> String -> String -> d -> Aff (Either Error (Response String))
-- queryPostForeign opStr url headers queryName q vars = do
-- request
-- defaultRequest
-- { withCredentials = true
-- , url = url
-- , method = Left Method.POST
-- --, responseFormat = ResponseFormat.json
-- , responseFormat = ResponseFormat.string
-- , content =
-- Just
-- -- $ RequestBody.Json
-- -- $ encodeJson
-- $ RequestBody.String
-- $ JSON.writeJSON
-- { query: opStr <> " " <> queryName <> " " <> q
-- , variables: vars
-- , operationName: queryName
-- }
-- , headers = headers <> [ ContentType applicationJSON ]
-- }
--
-- convertJsonResponse :: Either Error (Response String) -> Aff (Either Error (Response Json))
-- convertJsonResponse (Left err) = pure $ Left err
-- convertJsonResponse (Right res@{ body }) = pure $ case JSON.readJSON body of
-- Left err -> Left $ ResponseBodyError (DLN.head err) (res { body = unsafeToForeign body })
-- Right body' -> Right $ res { body = toJSON body' }
--
-- foreign import toJSON :: forall d. JSON.ReadForeign d => d -> Json
--
--
module Gargantext.Components.GraphQL.User where
import Gargantext.Prelude
import Data.Array as A
import Data.Lens (Lens', lens)
import Data.Maybe (Maybe(..), fromMaybe, maybe)
import GraphQL.Client.Args (NotNull(..), (=>>))
import GraphQL.Client.Variable (Var(..))
import GraphQL.Client.Variables (withVars)
import Type.Proxy (Proxy(..))
type UserInfo
= { ui_id :: Int
, ui_username :: String
, ui_email :: String
, ui_title :: Maybe String
, ui_source :: Maybe String
, ui_cwFirstName :: Maybe String
, ui_cwLastName :: Maybe String
, ui_cwOrganization :: Array String
, ui_cwLabTeamDepts :: Array String
, ui_cwOffice :: Maybe String
, ui_cwCity :: Maybe String
, ui_cwCountry :: Maybe String
, ui_cwRole :: Maybe String
, ui_cwTouchPhone :: Maybe String
, ui_cwTouchMail :: Maybe String }
type UserInfoM
= { ui_id :: NotNull Int
, ui_username :: String
, ui_email :: String
, ui_title :: String
, ui_source :: String
, ui_cwFirstName :: String
, ui_cwLastName :: String
, ui_cwOrganization :: (Array String)
, ui_cwLabTeamDepts :: (Array String)
, ui_cwOffice :: String
, ui_cwCity :: String
, ui_cwCountry :: String
, ui_cwRole :: String
, ui_cwTouchPhone :: String
, ui_cwTouchMail :: String }
userInfoQuery = { user_infos: { user_id: Var :: _ "id" Int } =>>
{ ui_id: unit
, ui_username: unit
, ui_email: unit
, ui_title: unit
, ui_source: unit
, ui_cwFirstName: unit
, ui_cwLastName: unit
, ui_cwCity: unit
, ui_cwCountry: unit
, ui_cwLabTeamDepts: unit
, ui_cwOrganization: unit
, ui_cwOffice: unit
, ui_cwRole: unit
, ui_cwTouchMail: unit
, ui_cwTouchPhone: unit }
}
_ui_cwFirstName :: Lens' UserInfo String
_ui_cwFirstName = lens getter setter
where
getter ({ ui_cwFirstName: val }) = fromMaybe "" val
setter ui val = ui { ui_cwFirstName = Just val }
_ui_cwLastName :: Lens' UserInfo String
_ui_cwLastName = lens getter setter
where
getter ({ ui_cwLastName: val }) = fromMaybe "" val
setter ui val = ui { ui_cwLastName = Just val }
_ui_cwCity :: Lens' UserInfo String
_ui_cwCity = lens getter setter
where
getter ({ ui_cwCity: val }) = fromMaybe "" val
setter ui val = ui { ui_cwCity = Just val }
_ui_cwCountry :: Lens' UserInfo String
_ui_cwCountry = lens getter setter
where
getter ({ ui_cwCountry: val }) = fromMaybe "" val
setter ui val = ui { ui_cwCountry = Just val }
_ui_cwLabTeamDepts :: Lens' UserInfo (Array String)
_ui_cwLabTeamDepts = lens getter setter
where
getter ({ ui_cwLabTeamDepts: val }) = val
setter ui val = ui { ui_cwLabTeamDepts = val }
_ui_cwLabTeamDeptsFirst :: Lens' UserInfo String
_ui_cwLabTeamDeptsFirst = lens getter setter
where
getter ({ ui_cwLabTeamDepts: val }) = fromMaybe "" $ A.head val
setter ui val = ui { ui_cwLabTeamDepts = fromMaybe [val] $ A.updateAt 0 val ui.ui_cwLabTeamDepts }
_ui_cwOffice :: Lens' UserInfo String
_ui_cwOffice = lens getter setter
where
getter ({ ui_cwOffice: val }) = fromMaybe "" val
setter ui val = ui { ui_cwOffice = Just val }
_ui_cwOrganization :: Lens' UserInfo (Array String)
_ui_cwOrganization = lens getter setter
where
getter ({ ui_cwOrganization: val }) = val
setter ui val = ui { ui_cwOrganization = val }
_ui_cwOrganizationFirst :: Lens' UserInfo String
_ui_cwOrganizationFirst = lens getter setter
where
getter ({ ui_cwOrganization: val }) = fromMaybe "" $ A.head val
setter ui val = ui { ui_cwOrganization = fromMaybe [val] $ A.updateAt 0 val ui.ui_cwOrganization }
_ui_cwRole :: Lens' UserInfo String
_ui_cwRole = lens getter setter
where
getter ({ ui_cwRole: val }) = fromMaybe "" val
setter ui val = ui { ui_cwRole = Just val }
_ui_cwTouchMail :: Lens' UserInfo String
_ui_cwTouchMail = lens getter setter
where
getter ({ ui_cwTouchMail: val }) = fromMaybe "" val
setter ui val = ui { ui_cwTouchMail = Just val }
_ui_cwTouchPhone :: Lens' UserInfo String
_ui_cwTouchPhone = lens getter setter
where
getter ({ ui_cwTouchPhone: val }) = fromMaybe "" val
setter ui val = ui { ui_cwTouchPhone = Just val }
type User
= { u_id :: Int
, u_hyperdata ::
{ shared :: Maybe
{ title :: Maybe String
, source :: Maybe String
, who :: Maybe
{ firstName :: Maybe String
, lastName :: Maybe String
}
, "where" :: Array
{ organization :: Array String }
}
}
, u_username :: String
, u_email :: String
}
showUser { u_id
, u_username
, u_email } = "[" <> show u_id <> "] " <> u_username <> " :: " <> u_email
showMUser u = maybe "" showUser u
...@@ -11,6 +11,7 @@ import Effect.Aff (Aff) ...@@ -11,6 +11,7 @@ import Effect.Aff (Aff)
import Gargantext.Components.App.Data (Boxes) import Gargantext.Components.App.Data (Boxes)
import Gargantext.Components.DocsTable as DT import Gargantext.Components.DocsTable as DT
import Gargantext.Components.DocsTable.Types (Year) import Gargantext.Components.DocsTable.Types (Year)
import Gargantext.Components.GraphQL.User (UserInfo)
import Gargantext.Components.NgramsTable as NT import Gargantext.Components.NgramsTable as NT
import Gargantext.Components.NgramsTable.Core as NTC import Gargantext.Components.NgramsTable.Core as NTC
import Gargantext.Components.Nodes.Annuaire.User.Contacts.Types (ContactData) import Gargantext.Components.Nodes.Annuaire.User.Contacts.Types (ContactData)
...@@ -50,13 +51,13 @@ modeTabType' Books = CTabAuthors ...@@ -50,13 +51,13 @@ modeTabType' Books = CTabAuthors
modeTabType' Communication = CTabAuthors modeTabType' Communication = CTabAuthors
type TabsProps = type TabsProps =
( boxes :: Boxes ( boxes :: Boxes
, cacheState :: T.Box LTypes.CacheState , cacheState :: T.Box LTypes.CacheState
, contactData :: ContactData , defaultListId :: Int
, frontends :: Frontends , frontends :: Frontends
, nodeId :: Int , nodeId :: Int
, session :: Session , session :: Session
, sidePanel :: T.Box (Maybe (Record TextsT.SidePanel)) , sidePanel :: T.Box (Maybe (Record TextsT.SidePanel))
) )
tabs :: R2.Leaf TabsProps tabs :: R2.Leaf TabsProps
...@@ -68,21 +69,21 @@ tabsCpt = here.component "tabs" cpt where ...@@ -68,21 +69,21 @@ tabsCpt = here.component "tabs" cpt where
yearFilter <- T.useBox (Nothing :: Maybe Year) yearFilter <- T.useBox (Nothing :: Maybe Year)
pure $ Tab.tabs { activeTab, tabs: tabs' yearFilter props } pure $ Tab.tabs { activeTab, tabs: tabs' yearFilter props }
tabs' yearFilter props@{ boxes, sidePanel } = tabs' yearFilter props@{ boxes, defaultListId, sidePanel } =
[ "Documents" /\ docs [ "Documents" /\ docs
, "Patents" /\ ngramsView (viewProps Patents) , "Patents" /\ ngramsView (viewProps Patents)
, "Books" /\ ngramsView (viewProps Books) , "Books" /\ ngramsView (viewProps Books)
, "Communication" /\ ngramsView (viewProps Communication) , "Communication" /\ ngramsView (viewProps Communication)
, "Trash" /\ docs -- TODO pass-in trash mode , "Trash" /\ docs -- TODO pass-in trash mode
] where ] where
viewProps mode = Record.merge props { defaultListId: props.contactData.defaultListId viewProps mode = Record.merge props { mode }
, mode } totalRecords = 4736 -- TODO lol
totalRecords = 4736 -- TODO lol
docs = DT.docViewLayout (Record.merge { boxes, sidePanel } $ Record.merge dtCommon dtExtra) docs = DT.docViewLayout (Record.merge { boxes, sidePanel } $ Record.merge dtCommon dtExtra)
dtCommon = RX.pick props :: Record DTCommon dtCommon = RX.pick props :: Record DTCommon
dtExtra = dtExtra =
{ chart: mempty { chart: mempty
, listId: props.contactData.defaultListId --, listId: props.contactData.defaultListId
, listId: defaultListId
, mCorpusId: Nothing , mCorpusId: Nothing
, showSearch: true , showSearch: true
, tabType: TabPairing TabDocs , tabType: TabPairing TabDocs
...@@ -100,8 +101,7 @@ type DTCommon = ...@@ -100,8 +101,7 @@ type DTCommon =
) )
type NgramsViewTabsProps = type NgramsViewTabsProps =
( defaultListId :: Int ( mode :: Mode
, mode :: Mode
| TabsProps ) | TabsProps )
ngramsView :: R2.Leaf NgramsViewTabsProps ngramsView :: R2.Leaf NgramsViewTabsProps
......
...@@ -4,25 +4,27 @@ module Gargantext.Components.Nodes.Annuaire.User ...@@ -4,25 +4,27 @@ module Gargantext.Components.Nodes.Annuaire.User
) )
where where
import Gargantext.Prelude import Gargantext.Prelude
import Data.Either (Either) import Data.Either (Either)
import Data.Lens as L
import Data.Maybe (Maybe(..), fromMaybe) import Data.Maybe (Maybe(..), fromMaybe)
import Effect (Effect) import Effect (Effect)
import Effect.Aff (Aff, launchAff_) import Effect.Aff (Aff, launchAff_)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
import Gargantext.Components.App.Data (Boxes) import Gargantext.Components.App.Data (Boxes)
import Gargantext.Components.InputWithEnter (inputWithEnter) import Gargantext.Components.GraphQL.User (UserInfo)
import Gargantext.Components.Nodes.Annuaire.Tabs as Tabs import Gargantext.Components.Nodes.Annuaire.Tabs as Tabs
import Gargantext.Components.Nodes.Annuaire.User.Contact (getUserInfoWithReload, saveUserInfo, contactInfos)
import Gargantext.Components.Nodes.Annuaire.User.Contacts.Types (Contact(..), ContactData, ContactTouch(..), ContactWhere(..), ContactWho(..), HyperdataContact(..), HyperdataUser(..), _city, _country, _firstName, _labTeamDeptsJoinComma, _lastName, _mail, _office, _organizationJoinComma, _ouFirst, _phone, _role, _shared, _touch, _who, defaultContactTouch, defaultContactWhere, defaultContactWho, defaultHyperdataContact, defaultHyperdataUser) import Gargantext.Components.Nodes.Annuaire.User.Contacts.Types (Contact(..), ContactData, ContactTouch(..), ContactWhere(..), ContactWho(..), HyperdataContact(..), HyperdataUser(..), _city, _country, _firstName, _labTeamDeptsJoinComma, _lastName, _mail, _office, _organizationJoinComma, _ouFirst, _phone, _role, _shared, _touch, _who, defaultContactTouch, defaultContactWhere, defaultContactWho, defaultHyperdataContact, defaultHyperdataUser)
import Gargantext.Components.Nodes.Lists.Types as LT import Gargantext.Components.Nodes.Lists.Types as LT
import Gargantext.Config.REST (RESTError, logRESTError) import Gargantext.Config.REST (RESTError, logRESTError)
import Gargantext.Config.Utils (handleRESTError)
import Gargantext.Ends (Frontends) import Gargantext.Ends (Frontends)
import Gargantext.Hooks.Loader (useLoader) import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Routes as Routes import Gargantext.Routes as Routes
import Gargantext.Sessions (WithSession, WithSessionContext, Session, get, put, sessionId) import Gargantext.Sessions (WithSession, WithSessionContext, Session, get, put, sessionId)
import Gargantext.Types (NodeType(..)) import Gargantext.Types (FrontendError, NodeType(..))
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Toestand as T2 import Gargantext.Utils.Toestand as T2
import Reactix as R import Reactix as R
...@@ -53,98 +55,10 @@ displayCpt = here.component "display" cpt ...@@ -53,98 +55,10 @@ displayCpt = here.component "display" cpt
[ H.div { className: "col-md-2" } [ H.img { src: "/images/Gargantextuel-212x300.jpg"} ] [ H.div { className: "col-md-2" } [ H.img { src: "/images/Gargantextuel-212x300.jpg"} ]
, H.div { className: "col-md-1"} [] , H.div { className: "col-md-1"} []
, H.div { className: "col-md-8"} children , H.div { className: "col-md-8"} children
]]]] ]
-- | TODO format data in better design (UI) shape
contactInfos :: HyperdataUser -> (HyperdataUser -> Effect Unit) -> Array R.Element
contactInfos h onUpdateHyperdata = item <$> contactInfoItems
where
item {label, defaultVal, lens} =
contactInfoItem { hyperdata: h
, label
, lens
, onUpdateHyperdata
, placeholder: defaultVal }
contactInfoItems :: Array {label:: String, defaultVal:: String, lens:: HyperdataUserLens}
contactInfoItems =
[ {label: "Last Name" , defaultVal: "Empty Last Name" , lens: _shared <<< _who <<< _lastName }
, {label: "First Name" , defaultVal: "Empty First Name" , lens: _shared <<< _who <<< _firstName }
, {label: "Organisation" , defaultVal: "Empty Organisation" , lens: _shared <<< _ouFirst <<< _organizationJoinComma}
, {label: "Lab/Team/Dept", defaultVal: "Empty Lab/Team/Dept", lens: _shared <<< _ouFirst <<< _labTeamDeptsJoinComma}
, {label: "Office" , defaultVal: "Empty Office" , lens: _shared <<< _ouFirst <<< _office }
, {label: "City" , defaultVal: "Empty City" , lens: _shared <<< _ouFirst <<< _city }
, {label: "Country" , defaultVal: "Empty Country" , lens: _shared <<< _ouFirst <<< _country }
, {label: "Role" , defaultVal: "Empty Role" , lens: _shared <<< _ouFirst <<< _role }
, {label: "Phone" , defaultVal: "Empty Phone" , lens: _shared <<< _ouFirst <<< _touch <<< _phone }
, {label: "Mail" , defaultVal: "Empty Mail" , lens: _shared <<< _ouFirst <<< _touch <<< _mail }
]
type HyperdataUserLens = L.ALens' HyperdataUser String
type ContactInfoItemProps =
( hyperdata :: HyperdataUser
, label :: String
, lens :: HyperdataUserLens
, onUpdateHyperdata :: HyperdataUser -> Effect Unit
, placeholder :: String
)
contactInfoItem :: Record ContactInfoItemProps -> R.Element
contactInfoItem props = R.createElement contactInfoItemCpt props []
contactInfoItemCpt :: R.Component ContactInfoItemProps
contactInfoItemCpt = here.component "contactInfoItem" cpt
where
cpt {hyperdata, label, lens, onUpdateHyperdata, placeholder} _ = do
isEditing <- T.useBox false
isEditing' <- T.useLive T.unequal isEditing
let value = (L.view cLens hyperdata) :: String
valueRef <- R.useRef value
pure $ H.div { className: "form-group row" } [
H.span { className: "col-sm-2 col-form-label" } [ H.text label ]
, item isEditing' isEditing valueRef
]
where
cLens = L.cloneLens lens
item false isEditing valueRef =
H.div { className: "input-group col-sm-6" } [
H.input { className: "form-control"
, defaultValue: placeholder'
, disabled: 1
, type: "text" }
, H.div { className: "btn input-group-append"
, on: { click: onClick } } [
H.div { className: "input-group-text fa fa-pencil" } []
] ]
] ]
where ]
placeholder' = R.readRef valueRef
onClick _ = T.write_ true isEditing
item true isEditing valueRef =
H.div { className: "input-group col-sm-6" } [
inputWithEnter {
autoFocus: true
, className: "form-control"
, defaultValue: R.readRef valueRef
, onBlur: R.setRef valueRef
, onEnter: onClick
, onValueChanged: R.setRef valueRef
, placeholder
, type: "text"
}
, H.div { className: "btn input-group-append"
, on: { click: onClick } } [
H.div { className: "input-group-text fa fa-floppy-o" } []
]
]
where
onClick _ = do
T.write_ true isEditing
let newHyperdata = (L.over cLens (\_ -> R.readRef valueRef) hyperdata) :: HyperdataUser
onUpdateHyperdata newHyperdata
{- {-
listElement :: Array R.Element -> R.Element listElement :: Array R.Element -> R.Element
...@@ -191,16 +105,16 @@ userLayoutWithKeyCpt = here.component "userLayoutWithKey" cpt where ...@@ -191,16 +105,16 @@ userLayoutWithKeyCpt = here.component "userLayoutWithKey" cpt where
cacheState <- T.useBox LT.CacheOn cacheState <- T.useBox LT.CacheOn
useLoader { errorHandler useLoader { errorHandler
, loader: getUserWithReload , loader: getUserInfoWithReload
, path: { nodeId, reload: reload', session } , path: { nodeId, reload: reload', session }
, render: \contactData@{contactNode: Contact {name, hyperdata}} -> , render: \userInfo@{ ui_username } ->
H.ul { className: "col-md-12 list-group" } [ H.ul { className: "col-md-12 list-group" } [
display { title: fromMaybe "no name" name } display { title: fromMaybe "no name" (Just ui_username) }
(contactInfos hyperdata (onUpdateHyperdata reload)) (contactInfos userInfo (onUpdateUserInfo boxes.errors reload))
, Tabs.tabs { , Tabs.tabs {
boxes boxes
, cacheState , cacheState
, contactData , defaultListId: 424242
, frontends , frontends
, nodeId , nodeId
, session , session
...@@ -210,31 +124,26 @@ userLayoutWithKeyCpt = here.component "userLayoutWithKey" cpt where ...@@ -210,31 +124,26 @@ userLayoutWithKeyCpt = here.component "userLayoutWithKey" cpt where
} }
where where
errorHandler = logRESTError here "[userLayoutWithKey]" errorHandler = logRESTError here "[userLayoutWithKey]"
onUpdateHyperdata :: T2.ReloadS -> HyperdataUser -> Effect Unit onUpdateUserInfo :: T.Box (Array FrontendError) -> T2.ReloadS -> UserInfo -> Effect Unit
onUpdateHyperdata reload hd = do onUpdateUserInfo errors reload ui = do
launchAff_ $ do launchAff_ $ do
_ <- saveContactHyperdata session nodeId hd res <- saveUserInfo session nodeId ui
liftEffect $ T2.reload reload handleRESTError errors res $ \_ ->
liftEffect $ T2.reload reload
-- | toUrl to get data XXX --saveContactHyperdata :: Session -> Int -> HyperdataUser -> Aff (Either RESTError Int)
getContact :: Session -> Int -> Aff (Either RESTError ContactData) --saveContactHyperdata session id = put session (Routes.NodeAPI Node (Just id) "")
getContact session id = do
eContactNode <- get session $ Routes.NodeAPI Node (Just id) ""
-- TODO: we need a default list for the pairings
--defaultListIds <- get $ toUrl endConfigStateful Back (Children NodeList 0 1 Nothing) $ Just id
--case (head defaultListIds :: Maybe (NodePoly HyperdataList)) of
-- Just (NodePoly { id: defaultListId }) ->
-- pure {contactNode, defaultListId}
-- Nothing ->
-- throwError $ error "Missing default list"
pure $ (\contactNode -> { contactNode, defaultListId: 424242 }) <$> eContactNode
getUserWithReload :: { nodeId :: Int
, reload :: T2.Reload
, session :: Session} -> Aff (Either RESTError ContactData)
getUserWithReload {nodeId, session} = getContact session nodeId
saveContactHyperdata :: Session -> Int -> HyperdataUser -> Aff (Either RESTError Int)
saveContactHyperdata session id h = do
put session (Routes.NodeAPI Node (Just id) "") h
-- | toUrl to get data XXX
--getContact :: Session -> Int -> Aff (Either RESTError ContactData)
--getContact session id = do
-- eContactNode <- get session $ Routes.NodeAPI Node (Just id) ""
-- -- TODO: we need a default list for the pairings
-- --defaultListIds <- get $ toUrl endConfigStateful Back (Children NodeList 0 1 Nothing) $ Just id
-- --case (head defaultListIds :: Maybe (NodePoly HyperdataList)) of
-- -- Just (NodePoly { id: defaultListId }) ->
-- -- pure {contactNode, defaultListId}
-- -- Nothing ->
-- -- throwError $ error "Missing default list"
-- pure $ (\contactNode -> { contactNode, defaultListId: 424242 }) <$> eContactNode
--
module Gargantext.Components.Nodes.Annuaire.User.Contact module Gargantext.Components.Nodes.Annuaire.User.Contact
( module Gargantext.Components.Nodes.Annuaire.User.Contacts.Types ( module Gargantext.Components.Nodes.Annuaire.User.Contacts.Types
, contactInfos
, contactLayout , contactLayout
, getUserInfo
, getUserInfoWithReload
, saveContactHyperdata
, saveUserInfo
) where ) where
import Data.Either (Either) import Gargantext.Components.GraphQL.User
import Gargantext.Prelude
import Affjax.RequestBody (RequestBody(..))
import Data.Array as A
import Data.Either (Either(..))
import Data.Lens as L import Data.Lens as L
import Data.Maybe (Maybe(..), fromMaybe) import Data.Maybe (Maybe(..), fromMaybe)
import Effect (Effect) import Effect (Effect)
import Effect.Aff (Aff, launchAff_) import Effect.Aff (Aff, launchAff_)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
import Gargantext.Components.App.Data (Boxes) import Gargantext.Components.App.Data (Boxes)
import Gargantext.Components.GraphQL (getClient, queryGql)
import Gargantext.Components.InputWithEnter (inputWithEnter) import Gargantext.Components.InputWithEnter (inputWithEnter)
import Gargantext.Components.Nodes.Annuaire.User.Contacts.Tabs as Tabs import Gargantext.Components.Nodes.Annuaire.User.Contacts.Tabs as Tabs
import Gargantext.Components.Nodes.Annuaire.User.Contacts.Types (Contact'(..), ContactData', ContactTouch(..), ContactWhere(..), ContactWho(..), HyperdataContact(..), HyperdataUser(..), _city, _country, _firstName, _labTeamDeptsJoinComma, _lastName, _mail, _office, _organizationJoinComma, _ouFirst, _phone, _role, _shared, _touch, _who, defaultContactTouch, defaultContactWhere, defaultContactWho, defaultHyperdataContact, defaultHyperdataUser) import Gargantext.Components.Nodes.Annuaire.User.Contacts.Types (ContactData', HyperdataContact(..))
import Gargantext.Components.Nodes.Lists.Types as LT import Gargantext.Components.Nodes.Lists.Types as LT
import Gargantext.Config.REST (RESTError, logRESTError) import Gargantext.Config.REST (RESTError(..), logRESTError)
import Gargantext.Ends (Frontends) import Gargantext.Ends (Frontends)
import Gargantext.Hooks.Loader (useLoader) import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Prelude
import Gargantext.Routes as Routes import Gargantext.Routes as Routes
import Gargantext.Sessions (Session, get, put, sessionId) import Gargantext.Sessions (Session, get, put, sessionId)
import Gargantext.Types (NodeType(..)) import Gargantext.Types (NodeType(..))
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Toestand as T2 import Gargantext.Utils.Toestand as T2
import GraphQL.Client.Args (type (==>), IgnoreArg(..), OrArg(..), onlyArgs, (=>>))
import GraphQL.Client.Query (mutationOpts, mutation)
import GraphQL.Client.Variables (withVars)
import Reactix as R import Reactix as R
import Reactix.DOM.HTML as H import Reactix.DOM.HTML as H
import Record as Record import Record as Record
...@@ -51,36 +64,39 @@ displayCpt = here.component "display" cpt ...@@ -51,36 +64,39 @@ displayCpt = here.component "display" cpt
[ H.div { className: "col-md-2" } [ H.img { src: "/images/Gargantextuel-212x300.jpg"} ] [ H.div { className: "col-md-2" } [ H.img { src: "/images/Gargantextuel-212x300.jpg"} ]
, H.div { className: "col-md-1"} [] , H.div { className: "col-md-1"} []
, H.div { className: "col-md-8"} children , H.div { className: "col-md-8"} children
]]]] ]
]
]
]
-- | TODO format data in better design (UI) shape -- | TODO format data in better design (UI) shape
contactInfos :: HyperdataContact -> (HyperdataContact -> Effect Unit) -> Array R.Element contactInfos :: UserInfo -> (UserInfo -> Effect Unit) -> Array R.Element
contactInfos h onUpdateHyperdata = item <$> contactInfoItems where contactInfos userInfo onUpdateUserInfo = item <$> contactInfoItems where
item { label, lens, defaultVal: placeholder } = item { label, lens, defaultVal } =
contactInfoItem { label, lens, onUpdateHyperdata, placeholder, hyperdata: h } contactInfoItem { defaultVal, label, lens, onUpdateUserInfo, userInfo }
contactInfoItems :: Array {label:: String, defaultVal:: String, lens:: HyperdataContactLens} contactInfoItems :: Array {label:: String, defaultVal:: String, lens:: UserInfoLens}
contactInfoItems = contactInfoItems =
[ {label: "Last Name" , defaultVal: "Empty Last Name" , lens: _who <<< _lastName } [ { label: "Last Name" , defaultVal: "Empty Last Name" , lens: _ui_cwLastName }
, {label: "First Name" , defaultVal: "Empty First Name" , lens: _who <<< _firstName } , { label: "First Name" , defaultVal: "Empty First Name" , lens: _ui_cwFirstName }
, {label: "Organisation" , defaultVal: "Empty Organisation" , lens: _ouFirst <<< _organizationJoinComma} , { label: "Organisation" , defaultVal: "Empty Organisation" , lens: _ui_cwOrganizationFirst }
, {label: "Lab/Team/Dept", defaultVal: "Empty Lab/Team/Dept", lens: _ouFirst <<< _labTeamDeptsJoinComma} , { label: "Lab/Team/Dept", defaultVal: "Empty Lab/Team/Dept", lens: _ui_cwLabTeamDeptsFirst }
, {label: "Office" , defaultVal: "Empty Office" , lens: _ouFirst <<< _office } , { label: "Office" , defaultVal: "Empty Office" , lens: _ui_cwOffice }
, {label: "City" , defaultVal: "Empty City" , lens: _ouFirst <<< _city } , { label: "City" , defaultVal: "Empty City" , lens: _ui_cwCity }
, {label: "Country" , defaultVal: "Empty Country" , lens: _ouFirst <<< _country } , { label: "Country" , defaultVal: "Empty Country" , lens: _ui_cwCountry }
, {label: "Role" , defaultVal: "Empty Role" , lens: _ouFirst <<< _role } , { label: "Role" , defaultVal: "Empty Role" , lens: _ui_cwRole }
, {label: "Phone" , defaultVal: "Empty Phone" , lens: _ouFirst <<< _touch <<< _phone } , { label: "Phone" , defaultVal: "Empty Phone" , lens: _ui_cwTouchPhone }
, {label: "Mail" , defaultVal: "Empty Mail" , lens: _ouFirst <<< _touch <<< _mail } , { label: "Mail" , defaultVal: "Empty Mail" , lens: _ui_cwTouchMail }
] ]
type HyperdataContactLens = L.ALens' HyperdataContact String type UserInfoLens = L.ALens' UserInfo String
type ContactInfoItemProps = type ContactInfoItemProps =
( hyperdata :: HyperdataContact ( defaultVal :: String
, label :: String , label :: String
, lens :: HyperdataContactLens , lens :: UserInfoLens
, onUpdateHyperdata :: HyperdataContact -> Effect Unit , onUpdateUserInfo :: UserInfo -> Effect Unit
, placeholder :: String , userInfo :: UserInfo
) )
contactInfoItem :: R2.Leaf ContactInfoItemProps contactInfoItem :: R2.Leaf ContactInfoItemProps
...@@ -88,47 +104,80 @@ contactInfoItem props = R.createElement contactInfoItemCpt props [] ...@@ -88,47 +104,80 @@ contactInfoItem props = R.createElement contactInfoItemCpt props []
contactInfoItemCpt :: R.Component ContactInfoItemProps contactInfoItemCpt :: R.Component ContactInfoItemProps
contactInfoItemCpt = here.component "contactInfoItem" cpt contactInfoItemCpt = here.component "contactInfoItem" cpt
where where
cpt { hyperdata, label, lens, onUpdateHyperdata, placeholder } _ = do cpt { defaultVal, label, lens, onUpdateUserInfo, userInfo } _ = do
isEditing <- T.useBox false isEditing <- T.useBox false
isEditing' <- T.useLive T.unequal isEditing isEditing' <- T.useLive T.unequal isEditing
let value = (L.view cLens hyperdata) :: String let value = (L.view cLens userInfo) :: String
valueRef <- R.useRef value valueBox <- T.useBox value
pure $ pure $
H.div { className: "form-group row" } H.div { className: "form-group row" }
[ H.span { className: "col-sm-2 col-form-label" } [ H.text label ] [ H.span { className: "col-sm-2 col-form-label" } [ H.text label ]
, item isEditing' isEditing valueRef ] , if isEditing' then
itemEditing { defaultVal, isEditing, lens, onUpdateUserInfo, userInfo, valueBox }
else
itemNotEditing { defaultVal, isEditing, lens, onUpdateUserInfo, userInfo, valueBox }
]
where where
cLens = L.cloneLens lens cLens = L.cloneLens lens
item false isEditing valueRef =
H.div { className: "input-group col-sm-6" } type ItemProps =
[ H.input ( defaultVal :: String
{ className: "form-control", type: "text" , isEditing :: T.Box Boolean
, defaultValue: placeholder', disabled: true } , lens :: UserInfoLens
, H.div { className: "btn input-group-append", on: { click } } , onUpdateUserInfo :: UserInfo -> Effect Unit
[ H.div { className: "input-group-text fa fa-pencil" } [] ]] , userInfo :: UserInfo
where , valueBox :: T.Box String
placeholder' = R.readRef valueRef )
click _ = T.write_ true isEditing
item true isEditing valueRef = itemNotEditing :: R2.Leaf ItemProps
H.div { className: "input-group col-sm-6" } itemNotEditing props = R.createElement itemNotEditingCpt props []
[ inputWithEnter itemNotEditingCpt :: R.Component ItemProps
{ autoFocus: true itemNotEditingCpt = here.component "itemEditing" cpt where
, className: "form-control" cpt { isEditing, valueBox } _ = do
, defaultValue: R.readRef valueRef valueBox' <- T.useLive T.unequal valueBox
, onBlur: R.setRef valueRef
, onEnter: click pure $ H.div { className: "input-group col-sm-6" }
, onValueChanged: R.setRef valueRef [ H.input
, placeholder { className: "form-control", type: "text"
, type: "text" } , defaultValue: valueBox', disabled: true }
, H.div { className: "btn input-group-append", on: { click } } , H.div { className: "btn input-group-append", on: { click } }
[ H.div { className: "input-group-text fa fa-floppy-o" } [] ]] [ H.div { className: "input-group-text fa fa-pencil" } [] ]
where ]
click _ = do where
T.write_ false isEditing click _ = T.write_ true isEditing
let newHyperdata = (L.over cLens (\_ -> R.readRef valueRef) hyperdata) :: HyperdataContact
onUpdateHyperdata newHyperdata itemEditing :: R2.Leaf ItemProps
itemEditing props = R.createElement itemEditingCpt props []
itemEditingCpt :: R.Component ItemProps
itemEditingCpt = here.component "itemNotEditing" cpt where
cpt { defaultVal, isEditing, lens, onUpdateUserInfo, userInfo, valueBox } _ = do
valueBox' <- T.useLive T.unequal valueBox
pure $ H.div { className: "input-group col-sm-6" }
[ inputWithEnter
{ autoFocus: true
, className: "form-control"
, defaultValue: valueBox'
, onBlur: \v -> T.write_ v valueBox
, onEnter: click
, onValueChanged: \v -> do
here.log2 "[itemEditingCpt] value Changed: " v
T.write_ v valueBox
, placeholder: defaultVal
, type: "text" }
, H.div { className: "btn input-group-append", on: { click } }
[ H.div { className: "input-group-text fa fa-floppy-o" } [] ]
]
where
cLens = L.cloneLens lens
click _ = do
T.write_ false isEditing
value <- T.read valueBox
here.log2 "[itemEditing] value" value
let newUserInfo = (L.set cLens value userInfo) :: UserInfo
onUpdateUserInfo newUserInfo
type ReloadProps = type ReloadProps =
( boxes :: Boxes ( boxes :: Boxes
...@@ -148,6 +197,29 @@ type KeyLayoutProps = ...@@ -148,6 +197,29 @@ type KeyLayoutProps =
saveContactHyperdata :: Session -> Int -> HyperdataContact -> Aff (Either RESTError Int) saveContactHyperdata :: Session -> Int -> HyperdataContact -> Aff (Either RESTError Int)
saveContactHyperdata session id = put session (Routes.NodeAPI Node (Just id) "") saveContactHyperdata session id = put session (Routes.NodeAPI Node (Just id) "")
saveUserInfo :: Session -> Int -> UserInfo -> Aff (Either RESTError Int)
saveUserInfo session id ui = do
client <- liftEffect $ getClient session
res <- mutationOpts
(\m -> m)
client
"update user_info"
{ update_user_info: onlyArgs { ui_id: id
, ui_cwFirstName: ga ui.ui_cwFirstName
, ui_cwLastName: ga ui.ui_cwLastName
, ui_cwOrganization: ui.ui_cwOrganization
, ui_cwLabTeamDepts: ui.ui_cwLabTeamDepts
, ui_cwOffice: ga ui.ui_cwOffice
, ui_cwCity: ga ui.ui_cwCity
, ui_cwCountry: ga ui.ui_cwCountry
, ui_cwRole: ga ui.ui_cwRole
, ui_cwTouchPhone: ga ui.ui_cwTouchPhone
, ui_cwTouchMail: ga ui.ui_cwTouchMail } }
pure $ Right res.update_user_info
where
ga Nothing = ArgL IgnoreArg
ga (Just val) = ArgR val
type AnnuaireLayoutProps = ( annuaireId :: Int, session :: Session | ReloadProps ) type AnnuaireLayoutProps = ( annuaireId :: Int, session :: Session | ReloadProps )
type AnnuaireKeyLayoutProps = ( annuaireId :: Int | KeyLayoutProps ) type AnnuaireKeyLayoutProps = ( annuaireId :: Int | KeyLayoutProps )
...@@ -175,27 +247,31 @@ contactLayoutWithKeyCpt = here.component "contactLayoutWithKey" cpt where ...@@ -175,27 +247,31 @@ contactLayoutWithKeyCpt = here.component "contactLayoutWithKey" cpt where
_ <- T.useLive T.unequal reload _ <- T.useLive T.unequal reload
cacheState <- T.useBox LT.CacheOn cacheState <- T.useBox LT.CacheOn
useLoader { errorHandler useLoader { errorHandler
, loader: getAnnuaireContact session annuaireId --, loader: getAnnuaireContact session annuaireId
, loader: getUserInfo session
, path: nodeId , path: nodeId
, render: \contactData@{contactNode: Contact' {name, hyperdata}} -> , render: \userInfo@{ ui_username } ->
H.ul { className: "col-md-12 list-group" } H.ul { className: "col-md-12 list-group" }
[ display { title: fromMaybe "no name" name } [ display { title: fromMaybe "no name" (Just ui_username) }
(contactInfos hyperdata (onUpdateHyperdata reload)) (contactInfos userInfo (onUpdateUserInfo reload))
, Tabs.tabs , Tabs.tabs
{ boxes { boxes
, cacheState , cacheState
, contactData , defaultListId: 424242 -- TODO
, frontends , frontends
, nodeId , nodeId
, session , session
, sidePanel: sidePanelTexts , sidePanel: sidePanelTexts
} ] } }
]
}
where where
errorHandler = logRESTError here "[contactLayoutWithKey]" errorHandler = logRESTError here "[contactLayoutWithKey]"
onUpdateHyperdata :: T2.ReloadS -> HyperdataContact -> Effect Unit onUpdateUserInfo :: T2.ReloadS -> UserInfo -> Effect Unit
onUpdateHyperdata reload hd = onUpdateUserInfo reload ui = do
launchAff_ $ launchAff_ $ do
saveContactHyperdata session nodeId hd *> liftEffect (T2.reload reload) _ <- saveUserInfo session nodeId ui
liftEffect (T2.reload reload)
getAnnuaireContact :: Session -> Int -> Int -> Aff (Either RESTError ContactData') getAnnuaireContact :: Session -> Int -> Int -> Aff (Either RESTError ContactData')
getAnnuaireContact session annuaireId id = do getAnnuaireContact session annuaireId id = do
...@@ -208,3 +284,18 @@ getAnnuaireContact session annuaireId id = do ...@@ -208,3 +284,18 @@ getAnnuaireContact session annuaireId id = do
-- Nothing -> -- Nothing ->
-- throwError $ error "Missing default list" -- throwError $ error "Missing default list"
pure $ (\contactNode -> { contactNode, defaultListId: 424242 }) <$> eContactNode pure $ (\contactNode -> { contactNode, defaultListId: 424242 }) <$> eContactNode
getUserInfoWithReload :: { nodeId :: Int
, reload :: T2.Reload
, session :: Session} -> Aff (Either RESTError UserInfo)
getUserInfoWithReload {nodeId, session} = getUserInfo session nodeId -- getContact session nodeId
getUserInfo :: Session -> Int -> Aff (Either RESTError UserInfo)
getUserInfo session id = do
{ user_infos } <- queryGql session "get user infos" $ userInfoQuery `withVars` { id }
liftEffect $ here.log2 "[getUserInfo] user infos" user_infos
pure $ case A.head user_infos of
Nothing -> Left (CustomError $ "user with id " <> show id <> " not found")
-- NOTE Contact is at G.C.N.A.U.C.Types
Just ui -> Right ui
...@@ -47,14 +47,14 @@ modeTabType' Patents = CTabAuthors ...@@ -47,14 +47,14 @@ modeTabType' Patents = CTabAuthors
modeTabType' Books = CTabAuthors modeTabType' Books = CTabAuthors
modeTabType' Communication = CTabAuthors modeTabType' Communication = CTabAuthors
type TabsProps = ( type TabsProps =
boxes :: Boxes ( boxes :: Boxes
, cacheState :: T.Box LTypes.CacheState , cacheState :: T.Box LTypes.CacheState
, contactData :: ContactData' , defaultListId :: Int
, frontends :: Frontends , frontends :: Frontends
, nodeId :: Int , nodeId :: Int
, session :: Session , session :: Session
, sidePanel :: T.Box (Maybe (Record TTypes.SidePanel)) , sidePanel :: T.Box (Maybe (Record TTypes.SidePanel))
) )
tabs :: R2.Leaf TabsProps tabs :: R2.Leaf TabsProps
...@@ -64,7 +64,7 @@ tabsCpt = here.component "tabs" cpt ...@@ -64,7 +64,7 @@ tabsCpt = here.component "tabs" cpt
where where
cpt { boxes cpt { boxes
, cacheState , cacheState
, contactData: {defaultListId} , defaultListId
, frontends , frontends
, nodeId , nodeId
, session , session
...@@ -134,7 +134,6 @@ type NgramsViewTabsProps = ( ...@@ -134,7 +134,6 @@ type NgramsViewTabsProps = (
ngramsView :: R2.Component NgramsViewTabsProps ngramsView :: R2.Component NgramsViewTabsProps
ngramsView = R.createElement ngramsViewCpt ngramsView = R.createElement ngramsViewCpt
ngramsViewCpt :: R.Component NgramsViewTabsProps ngramsViewCpt :: R.Component NgramsViewTabsProps
ngramsViewCpt = here.component "ngramsView" cpt ngramsViewCpt = here.component "ngramsView" cpt
where where
......
...@@ -152,7 +152,7 @@ postMultipartFormData mtoken url body = do ...@@ -152,7 +152,7 @@ postMultipartFormData mtoken url body = do
, ARH.Accept applicationJSON , ARH.Accept applicationJSON
] <> ] <>
foldMap (\token -> foldMap (\token ->
[ ARH.RequestHeader "Authorization" $ "Bearer " <> token ] [ ARH.RequestHeader "Authorization" $ " " <> token ]
) mtoken ) mtoken
, content = Just $ formData fd , content = Just $ formData fd
} }
......
...@@ -1153,6 +1153,11 @@ ...@@ -1153,6 +1153,11 @@
dependencies: dependencies:
unzipper "^0.9.3" unzipper "^0.9.3"
"@graphql-typed-document-node/core@^3.1.0":
version "3.1.0"
resolved "https://registry.yarnpkg.com/@graphql-typed-document-node/core/-/core-3.1.0.tgz#0eee6373e11418bfe0b5638f654df7a4ca6a3950"
integrity sha512-wYn6r8zVZyQJ6rQaALBEln5B1pzxb9shV5Ef97kTvn6yVGrqyXVnDqnU24MXnFubR+rZjBY9NWuxX3FB2sTsjg==
"@hutson/parse-repository-url@^3.0.0": "@hutson/parse-repository-url@^3.0.0":
version "3.0.2" version "3.0.2"
resolved "https://registry.yarnpkg.com/@hutson/parse-repository-url/-/parse-repository-url-3.0.2.tgz#98c23c950a3d9b6c8f0daed06da6c3af06981340" resolved "https://registry.yarnpkg.com/@hutson/parse-repository-url/-/parse-repository-url-3.0.2.tgz#98c23c950a3d9b6c8f0daed06da6c3af06981340"
...@@ -1918,6 +1923,14 @@ ...@@ -1918,6 +1923,14 @@
dependencies: dependencies:
"@types/node" "*" "@types/node" "*"
"@urql/core@^2.3.3":
version "2.3.3"
resolved "https://registry.yarnpkg.com/@urql/core/-/core-2.3.3.tgz#e4777b95c31d8ad0ba21ea1f5c851cbbe1d0ac17"
integrity sha512-Bi9mafTFu0O1XZmI7/HrEk12LHZW+Fs/V1FqSJoUDgYIhARIJW6cCh3Havy1dJJ0FETxYmmQQXPf6kst+IP2qQ==
dependencies:
"@graphql-typed-document-node/core" "^3.1.0"
wonka "^4.0.14"
"@vue/compiler-core@3.1.5": "@vue/compiler-core@3.1.5":
version "3.1.5" version "3.1.5"
resolved "https://registry.yarnpkg.com/@vue/compiler-core/-/compiler-core-3.1.5.tgz#298f905b6065d6d81ff63756f98c60876b393c87" resolved "https://registry.yarnpkg.com/@vue/compiler-core/-/compiler-core-3.1.5.tgz#298f905b6065d6d81ff63756f98c60876b393c87"
...@@ -4734,6 +4747,16 @@ graceful-fs@^4.1.2: ...@@ -4734,6 +4747,16 @@ graceful-fs@^4.1.2:
resolved "https://registry.yarnpkg.com/graceful-fs/-/graceful-fs-4.2.6.tgz#ff040b2b0853b23c3d31027523706f1885d76bee" resolved "https://registry.yarnpkg.com/graceful-fs/-/graceful-fs-4.2.6.tgz#ff040b2b0853b23c3d31027523706f1885d76bee"
integrity sha512-nTnJ528pbqxYanhpDYsi4Rd8MAeaBA67+RZ10CM1m3bTAVFEDcd5AuA4a6W5YkGZ1iNXHzZz8T6TBKLeBuNriQ== integrity sha512-nTnJ528pbqxYanhpDYsi4Rd8MAeaBA67+RZ10CM1m3bTAVFEDcd5AuA4a6W5YkGZ1iNXHzZz8T6TBKLeBuNriQ==
graphql-ws@^5.5.0:
version "5.5.0"
resolved "https://registry.yarnpkg.com/graphql-ws/-/graphql-ws-5.5.0.tgz#79f10248d23d104369eaef93acb9f887276a2c42"
integrity sha512-WQepPMGQQoqS2VsrI2I3RMLCVz3CW4/6ZqGV6ABDOwH4R62DzjxwMlwZbj6vhSI/7IM3/C911yITwgs77iO/hw==
graphql@^15.6.1:
version "15.6.1"
resolved "https://registry.yarnpkg.com/graphql/-/graphql-15.6.1.tgz#9125bdf057553525da251e19e96dab3d3855ddfc"
integrity sha512-3i5lu0z6dRvJ48QP9kFxBkJ7h4Kso7PS8eahyTFz5Jm6CvQfLtNIE8LX9N6JLnXTuwR+sIYnXzaWp6anOg0QQw==
handlebars@^4.7.6: handlebars@^4.7.6:
version "4.7.7" version "4.7.7"
resolved "https://registry.yarnpkg.com/handlebars/-/handlebars-4.7.7.tgz#9ce33416aad02dbd6c8fafa8240d5d98004945a1" resolved "https://registry.yarnpkg.com/handlebars/-/handlebars-4.7.7.tgz#9ce33416aad02dbd6c8fafa8240d5d98004945a1"
...@@ -5567,6 +5590,14 @@ isobject@^3.0.0, isobject@^3.0.1: ...@@ -5567,6 +5590,14 @@ isobject@^3.0.0, isobject@^3.0.1:
resolved "https://registry.yarnpkg.com/isobject/-/isobject-3.0.1.tgz#4e431e92b11a9731636aa1f9c8d1ccbcfdab78df" resolved "https://registry.yarnpkg.com/isobject/-/isobject-3.0.1.tgz#4e431e92b11a9731636aa1f9c8d1ccbcfdab78df"
integrity sha1-TkMekrEalzFjaqH5yNHMvP2reN8= integrity sha1-TkMekrEalzFjaqH5yNHMvP2reN8=
isomorphic-unfetch@^3.1.0:
version "3.1.0"
resolved "https://registry.yarnpkg.com/isomorphic-unfetch/-/isomorphic-unfetch-3.1.0.tgz#87341d5f4f7b63843d468438128cb087b7c3e98f"
integrity sha512-geDJjpoZ8N0kWexiwkX8F9NkTsXhetLPVbZFQ+JTW239QNOwvB0gniuR1Wc6f0AMTn7/mFGyXvHTifrCp/GH8Q==
dependencies:
node-fetch "^2.6.1"
unfetch "^4.2.0"
isstream@~0.1.2: isstream@~0.1.2:
version "0.1.2" version "0.1.2"
resolved "https://registry.yarnpkg.com/isstream/-/isstream-0.1.2.tgz#47e63f7af55afa6f92e1500e690eb8b8529c099a" resolved "https://registry.yarnpkg.com/isstream/-/isstream-0.1.2.tgz#47e63f7af55afa6f92e1500e690eb8b8529c099a"
...@@ -6476,6 +6507,13 @@ node-addon-api@^3.0.2: ...@@ -6476,6 +6507,13 @@ node-addon-api@^3.0.2:
resolved "https://registry.yarnpkg.com/node-addon-api/-/node-addon-api-3.2.1.tgz#81325e0a2117789c0128dab65e7e38f07ceba161" resolved "https://registry.yarnpkg.com/node-addon-api/-/node-addon-api-3.2.1.tgz#81325e0a2117789c0128dab65e7e38f07ceba161"
integrity sha512-mmcei9JghVNDYydghQmeDX8KoAm0FAiYyIcUt/N4nhyAipB17pllZQDOJD2fotxABnt4Mdz+dKTO7eftLg4d0A== integrity sha512-mmcei9JghVNDYydghQmeDX8KoAm0FAiYyIcUt/N4nhyAipB17pllZQDOJD2fotxABnt4Mdz+dKTO7eftLg4d0A==
node-fetch@^2.6.1:
version "2.6.5"
resolved "https://registry.yarnpkg.com/node-fetch/-/node-fetch-2.6.5.tgz#42735537d7f080a7e5f78b6c549b7146be1742fd"
integrity sha512-mmlIVHJEu5rnIxgEgez6b9GgWXbkZj5YZ7fx+2r94a2E+Uirsp6HsPTPlomfdHtpt/B0cdKviwkoaM6pyvUOpQ==
dependencies:
whatwg-url "^5.0.0"
node-forge@^0.10.0: node-forge@^0.10.0:
version "0.10.0" version "0.10.0"
resolved "https://registry.yarnpkg.com/node-forge/-/node-forge-0.10.0.tgz#32dea2afb3e9926f02ee5ce8794902691a676bf3" resolved "https://registry.yarnpkg.com/node-forge/-/node-forge-0.10.0.tgz#32dea2afb3e9926f02ee5ce8794902691a676bf3"
...@@ -9046,6 +9084,11 @@ tr46@^1.0.1: ...@@ -9046,6 +9084,11 @@ tr46@^1.0.1:
dependencies: dependencies:
punycode "^2.1.0" punycode "^2.1.0"
tr46@~0.0.3:
version "0.0.3"
resolved "https://registry.yarnpkg.com/tr46/-/tr46-0.0.3.tgz#8184fd347dac9cdc185992f3a6622e14b9d9ab6a"
integrity sha1-gYT9NH2snNwYWZLzpmIuFLnZq2o=
"traverse@>=0.3.0 <0.4": "traverse@>=0.3.0 <0.4":
version "0.3.9" version "0.3.9"
resolved "https://registry.yarnpkg.com/traverse/-/traverse-0.3.9.tgz#717b8f220cc0bb7b44e40514c22b2e8bbc70d8b9" resolved "https://registry.yarnpkg.com/traverse/-/traverse-0.3.9.tgz#717b8f220cc0bb7b44e40514c22b2e8bbc70d8b9"
...@@ -9175,6 +9218,11 @@ uncss@^0.17.3: ...@@ -9175,6 +9218,11 @@ uncss@^0.17.3:
postcss-selector-parser "6.0.2" postcss-selector-parser "6.0.2"
request "^2.88.0" request "^2.88.0"
unfetch@^4.2.0:
version "4.2.0"
resolved "https://registry.yarnpkg.com/unfetch/-/unfetch-4.2.0.tgz#7e21b0ef7d363d8d9af0fb929a5555f6ef97a3be"
integrity sha512-F9p7yYCn6cIW9El1zi0HI6vqpeIvBsr3dSuRO6Xuppb1u5rXpCPmMvLSyECLhybr9isec8Ohl0hPekMVrEinDA==
unicode-canonical-property-names-ecmascript@^1.0.4: unicode-canonical-property-names-ecmascript@^1.0.4:
version "1.0.4" version "1.0.4"
resolved "https://registry.yarnpkg.com/unicode-canonical-property-names-ecmascript/-/unicode-canonical-property-names-ecmascript-1.0.4.tgz#2619800c4c825800efdd8343af7dd9933cbe2818" resolved "https://registry.yarnpkg.com/unicode-canonical-property-names-ecmascript/-/unicode-canonical-property-names-ecmascript-1.0.4.tgz#2619800c4c825800efdd8343af7dd9933cbe2818"
...@@ -9608,6 +9656,11 @@ weak-lru-cache@^1.0.0: ...@@ -9608,6 +9656,11 @@ weak-lru-cache@^1.0.0:
resolved "https://registry.yarnpkg.com/weak-lru-cache/-/weak-lru-cache-1.0.0.tgz#f1394721169883488c554703704fbd91cda05ddf" resolved "https://registry.yarnpkg.com/weak-lru-cache/-/weak-lru-cache-1.0.0.tgz#f1394721169883488c554703704fbd91cda05ddf"
integrity sha512-135bPugHHIJLNx20guHgk4etZAbd7nou34NQfdKkJPgMuC3Oqn4cT6f7ORVvnud9oEyXJVJXPcTFsUvttGm5xg== integrity sha512-135bPugHHIJLNx20guHgk4etZAbd7nou34NQfdKkJPgMuC3Oqn4cT6f7ORVvnud9oEyXJVJXPcTFsUvttGm5xg==
webidl-conversions@^3.0.0:
version "3.0.1"
resolved "https://registry.yarnpkg.com/webidl-conversions/-/webidl-conversions-3.0.1.tgz#24534275e2a7bc6be7bc86611cc16ae0a5654871"
integrity sha1-JFNCdeKnvGvnvIZhHMFq4KVlSHE=
webidl-conversions@^4.0.2: webidl-conversions@^4.0.2:
version "4.0.2" version "4.0.2"
resolved "https://registry.yarnpkg.com/webidl-conversions/-/webidl-conversions-4.0.2.tgz#a855980b1f0b6b359ba1d5d9fb39ae941faa63ad" resolved "https://registry.yarnpkg.com/webidl-conversions/-/webidl-conversions-4.0.2.tgz#a855980b1f0b6b359ba1d5d9fb39ae941faa63ad"
...@@ -9639,6 +9692,14 @@ whatwg-mimetype@^2.2.0, whatwg-mimetype@^2.3.0: ...@@ -9639,6 +9692,14 @@ whatwg-mimetype@^2.2.0, whatwg-mimetype@^2.3.0:
resolved "https://registry.yarnpkg.com/whatwg-mimetype/-/whatwg-mimetype-2.3.0.tgz#3d4b1e0312d2079879f826aff18dbeeca5960fbf" resolved "https://registry.yarnpkg.com/whatwg-mimetype/-/whatwg-mimetype-2.3.0.tgz#3d4b1e0312d2079879f826aff18dbeeca5960fbf"
integrity sha512-M4yMwr6mAnQz76TbJm914+gPpB/nCwvZbJU28cUD6dR004SAxDLOOSUaB1JDRqLtaOV/vi0IC5lEAGFgrjGv/g== integrity sha512-M4yMwr6mAnQz76TbJm914+gPpB/nCwvZbJU28cUD6dR004SAxDLOOSUaB1JDRqLtaOV/vi0IC5lEAGFgrjGv/g==
whatwg-url@^5.0.0:
version "5.0.0"
resolved "https://registry.yarnpkg.com/whatwg-url/-/whatwg-url-5.0.0.tgz#966454e8765462e37644d3626f6742ce8b70965d"
integrity sha1-lmRU6HZUYuN2RNNib2dCzotwll0=
dependencies:
tr46 "~0.0.3"
webidl-conversions "^3.0.0"
whatwg-url@^7.0.0: whatwg-url@^7.0.0:
version "7.1.0" version "7.1.0"
resolved "https://registry.yarnpkg.com/whatwg-url/-/whatwg-url-7.1.0.tgz#c2c492f1eca612988efd3d2266be1b9fc6170d06" resolved "https://registry.yarnpkg.com/whatwg-url/-/whatwg-url-7.1.0.tgz#c2c492f1eca612988efd3d2266be1b9fc6170d06"
...@@ -9697,6 +9758,11 @@ widest-line@^2.0.0: ...@@ -9697,6 +9758,11 @@ widest-line@^2.0.0:
dependencies: dependencies:
string-width "^2.1.1" string-width "^2.1.1"
wonka@^4.0.14:
version "4.0.15"
resolved "https://registry.yarnpkg.com/wonka/-/wonka-4.0.15.tgz#9aa42046efa424565ab8f8f451fcca955bf80b89"
integrity sha512-U0IUQHKXXn6PFo9nqsHphVCE5m3IntqZNB9Jjn7EB1lrR7YTDY3YWgFvEvwniTzXSvOH/XMzAZaIfJF/LvHYXg==
word-wrap@~1.2.3: word-wrap@~1.2.3:
version "1.2.3" version "1.2.3"
resolved "https://registry.yarnpkg.com/word-wrap/-/word-wrap-1.2.3.tgz#610636f6b1f703891bd34771ccb17fb93b47079c" resolved "https://registry.yarnpkg.com/word-wrap/-/word-wrap-1.2.3.tgz#610636f6b1f703891bd34771ccb17fb93b47079c"
......
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