Commit 7ea0fe74 authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

Merge branch 'dev-node-calc-parser' of...

Merge branch 'dev-node-calc-parser' of ssh://gitlab.iscpif.fr:20022/gargantext/purescript-gargantext into dev-node-calc-parser
parents b4aba663 24d97953
......@@ -4,22 +4,20 @@ module Gargantext.Components.Category where
import Gargantext.Prelude
import Data.Array as A
import Data.Either (Either)
import Data.Generic.Rep (class Generic)
import Data.Map as Map
import Data.Maybe (Maybe(..))
import Effect.Aff (Aff, launchAff)
import Reactix as R
import Reactix.DOM.HTML as H
import Simple.JSON as JSON
import Effect.Aff (launchAff)
import Gargantext.Components.Category.Types (Category(..), Star(..), cat2score, categories, clickAgain, star2score, stars)
import Gargantext.Components.DocsTable.Types (DocumentsView(..), LocalCategories, LocalUserScore)
import Gargantext.Config.REST (RESTError)
import Gargantext.Config.REST (AffRESTError)
import Gargantext.Routes (SessionRoute(NodeAPI))
import Gargantext.Sessions (Session, put)
import Gargantext.Types (NodeID, NodeType(..))
import Gargantext.Utils.Reactix as R2
import Reactix as R
import Reactix.DOM.HTML as H
import Simple.JSON as JSON
here :: R2.Here
here = R2.here "Gargantext.Components.Category"
......@@ -63,7 +61,7 @@ instance JSON.WriteForeign RatingQuery where
writeImpl (RatingQuery post) = JSON.writeImpl { ntc_nodesId: post.nodeIds
, ntc_category: post.rating }
putRating :: Session -> Int -> RatingQuery -> Aff (Either RESTError (Array Int))
putRating :: Session -> Int -> RatingQuery -> AffRESTError (Array Int)
putRating session nodeId = put session $ ratingRoute where
ratingRoute = NodeAPI Node (Just nodeId) "category"
......@@ -147,5 +145,5 @@ instance JSON.WriteForeign CategoryQuery where
categoryRoute :: Int -> SessionRoute
categoryRoute nodeId = NodeAPI Node (Just nodeId) "category"
putCategories :: Session -> Int -> CategoryQuery -> Aff (Either RESTError (Array Int))
putCategories :: Session -> Int -> CategoryQuery -> AffRESTError (Array Int)
putCategories session nodeId = put session $ categoryRoute nodeId
......@@ -34,10 +34,10 @@ import Gargantext.Components.DocsTable.DocumentFormCreation as DFC
import Gargantext.Components.DocsTable.Types (DocumentsView(..), Hyperdata(..), LocalUserScore, Query, Response(..), Year, sampleData, showSource)
import Gargantext.Components.Nodes.Lists.Types as NT
import Gargantext.Components.Nodes.Texts.Types as TextsT
import Gargantext.Components.Reload (reloadContext, textsReloadContext)
import Gargantext.Components.Reload (textsReloadContext)
import Gargantext.Components.Table as TT
import Gargantext.Components.Table.Types as TT
import Gargantext.Config.REST (RESTError, logRESTError)
import Gargantext.Config.REST (AffRESTError, logRESTError)
import Gargantext.Config.Utils (handleRESTError)
import Gargantext.Ends (Frontends, url)
import Gargantext.Hooks.Loader (useLoader, useLoaderWithCacheAPI, HashedResponse(..))
......@@ -339,7 +339,7 @@ type PageParams = {
, yearFilter :: Maybe Year
}
getPageHash :: Session -> PageParams -> Aff (Either RESTError String)
getPageHash :: Session -> PageParams -> AffRESTError String
getPageHash session { nodeId, tabType } =
get session $ tableHashRoute nodeId tabType
......@@ -677,7 +677,7 @@ tableRouteWithPage { listId, nodeId, params: { limit, offset, orderBy, searchTyp
q = queryParamS "query" query
y = mQueryParam "year" yearFilter
deleteAllDocuments :: Session -> Int -> Aff (Either RESTError (Array Int))
deleteAllDocuments :: Session -> Int -> AffRESTError (Array Int)
deleteAllDocuments session = delete session <<< documentsRoute
-- TODO: not optimal but Data.Set lacks some function (Set.alter)
......
......@@ -11,10 +11,9 @@ import Data.Either (Either(..))
import Data.Foldable (foldl, intercalate)
import Data.Maybe (Maybe(..))
import Effect (Effect)
import Effect.Aff (Aff)
import Gargantext.Components.Bootstrap as B
import Gargantext.Components.Bootstrap.Types (ComponentStatus(..))
import Gargantext.Config.REST (RESTError)
import Gargantext.Config.REST (AffRESTError)
import Gargantext.Hooks.FormValidation (VForm, useFormValidation)
import Gargantext.Hooks.FormValidation.Unboxed as FV
import Gargantext.Hooks.StateRecord (useStateRecord)
......@@ -247,7 +246,7 @@ create ::
Session
-> GT.ID
-> Record FormData
-> Aff (Either RESTError GT.AsyncTaskWithType)
-> AffRESTError GT.AsyncTaskWithType
create session nodeId =
rename
>>> post session request
......@@ -271,7 +270,7 @@ createProgress ::
Session
-> GT.ID
-> GT.AsyncTaskWithType
-> Aff (Either RESTError GT.AsyncProgress)
-> AffRESTError GT.AsyncProgress
createProgress
session
nodeId
......
......@@ -17,7 +17,7 @@ import Data.Set as Set
import Data.Show.Generic (genericShow)
import Data.Tuple.Nested ((/\))
import Effect (Effect)
import Effect.Aff (Aff, launchAff_)
import Effect.Aff (launchAff_)
import Effect.Class (liftEffect)
import Gargantext.Components.Category (CategoryQuery(..), putCategories)
import Gargantext.Components.Category.Types (Category(..), decodeCategory, favCategory)
......@@ -25,7 +25,7 @@ import Gargantext.Components.DocsTable.Types (showSource)
import Gargantext.Components.Search (Contact(..), Document(..), HyperdataRowContact(..), HyperdataRowDocument(..), SearchQuery, SearchResult(..), SearchResultTypes(..))
import Gargantext.Components.Table as T
import Gargantext.Components.Table.Types as T
import Gargantext.Config.REST (RESTError(..))
import Gargantext.Config.REST (RESTError(..), AffRESTError)
import Gargantext.Ends (url, Frontends)
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Routes (SessionRoute(Search, NodeAPI))
......@@ -205,7 +205,7 @@ type PagePath = { nodeId :: Int
initialPagePath :: {session :: Session, nodeId :: Int, listId :: Int, query :: SearchQuery} -> PagePath
initialPagePath {session, nodeId, listId, query} = {session, nodeId, listId, query, params: T.initialParams}
loadPage :: PagePath -> Aff (Either RESTError Rows)
loadPage :: PagePath -> AffRESTError Rows
loadPage { session, nodeId, listId, query, params: {limit, offset, orderBy } } = do
let
convOrderBy (T.ASC (T.ColumnName "Date")) = DateAsc
......@@ -404,7 +404,7 @@ derive instance Generic DeleteDocumentQuery _
derive instance Newtype DeleteDocumentQuery _
derive newtype instance JSON.WriteForeign DeleteDocumentQuery
deleteDocuments :: Session -> Int -> DeleteDocumentQuery -> Aff (Either RESTError (Array Int))
deleteDocuments :: Session -> Int -> DeleteDocumentQuery -> AffRESTError (Array Int)
deleteDocuments session nodeId =
deleteWithBody session $ NodeAPI Node (Just nodeId) "documents"
module Gargantext.Components.FolderView where
import Data.Array as A
import Data.Either (Either)
import Data.Maybe (Maybe(..), fromMaybe)
import Data.Nullable (null)
import Data.Traversable (traverse_)
......@@ -24,7 +23,7 @@ import Gargantext.Components.Forest.Tree.Node.Action.Upload (uploadArbitraryFile
import Gargantext.Components.Forest.Tree.Node.Box (nodePopupView)
import Gargantext.Components.Forest.Tree.Node.Tools.FTree (FTree, LNode(..), NTree(..), fTreeID)
import Gargantext.Components.Forest.Tree.Node.Tools.SubTree.Types (SubTreeOut(..))
import Gargantext.Config.REST (RESTError, logRESTError)
import Gargantext.Config.REST (AffRESTError, logRESTError)
import Gargantext.Config.Utils (handleRESTError)
import Gargantext.Hooks.LinkHandler (Methods, useLinkHandler)
import Gargantext.Hooks.Loader (useLoader)
......@@ -262,7 +261,7 @@ type LoadProps =
reload :: T2.Reload
)
loadFolders :: Record LoadProps -> Aff (Either RESTError FTree)
loadFolders :: Record LoadProps -> AffRESTError FTree
loadFolders {nodeId, session} = get session $ TreeFirstLevel (Just nodeId) ""
type PerformActionProps =
......
......@@ -3,7 +3,6 @@ module Gargantext.Components.Forest.Tree where
import Gargantext.Prelude
import Data.Array as A
import Data.Either (Either)
import Data.Maybe (Maybe(..))
import Data.Traversable (traverse_, traverse)
import Effect (Effect)
......@@ -26,7 +25,7 @@ import Gargantext.Components.Forest.Tree.Node.Action.Upload (uploadFile, uploadA
import Gargantext.Components.Forest.Tree.Node.Action.WriteNodesDocuments (documentsFromWriteNodesReq)
import Gargantext.Components.Forest.Tree.Node.Tools.FTree (FTree, LNode(..), NTree(..), fTreeID)
import Gargantext.Components.Forest.Tree.Node.Tools.SubTree.Types (SubTreeOut(..))
import Gargantext.Config.REST (RESTError, logRESTError)
import Gargantext.Config.REST (AffRESTError, logRESTError)
import Gargantext.Config.Utils (handleRESTError)
import Gargantext.Ends (Frontends)
import Gargantext.Hooks.Loader (useLoader)
......@@ -124,10 +123,10 @@ treeLoaderCpt = here.component "treeLoader" cpt where
extra = { reloadTree: p.reload, root, session, tree: tree' }
errorHandler = logRESTError here "[treeLoader]"
getNodeTree :: Session -> ID -> Aff (Either RESTError FTree)
getNodeTree :: Session -> ID -> AffRESTError FTree
getNodeTree session nodeId = get session $ GR.NodeAPI GT.Tree (Just nodeId) ""
getNodeTreeFirstLevel :: Session -> ID -> Aff (Either RESTError FTree)
getNodeTreeFirstLevel :: Session -> ID -> AffRESTError FTree
getNodeTreeFirstLevel session nodeId = get session $ GR.TreeFirstLevel (Just nodeId) ""
tree :: R2.Leaf TreeProps
......
......@@ -16,7 +16,7 @@ import Gargantext.Components.Forest.Tree.Node.Settings (SettingsBox(..), setting
import Gargantext.Components.Forest.Tree.Node.Tools (formChoiceSafe, panel, submitButton)
import Gargantext.Components.InputWithEnter (inputWithEnter)
import Gargantext.Components.Lang (Lang(..), translate)
import Gargantext.Config.REST (RESTError)
import Gargantext.Config.REST (RESTError, AffRESTError)
import Gargantext.Routes as GR
import Gargantext.Sessions (Session, post)
import Gargantext.Types (NodeType(..), charCodeIcon)
......@@ -34,13 +34,13 @@ import Web.HTML.Window (navigator)
here :: R2.Here
here = R2.here "Gargantext.Components.Forest.Tree.Node.Action.Add"
addNode :: Session -> GT.ID -> AddNodeValue -> Aff (Either RESTError (Array GT.ID))
addNode :: Session -> GT.ID -> AddNodeValue -> AffRESTError (Array GT.ID)
addNode session parentId = post session $ GR.NodeAPI GT.Node (Just parentId) ""
addNodeAsync :: Session
-> GT.ID
-> AddNodeValue
-> Aff (Either RESTError GT.AsyncTaskWithType)
-> AffRESTError GT.AsyncTaskWithType
addNodeAsync session parentId q = do
eTask :: Either RESTError GT.AsyncTask <- post session p q
case eTask of
......
......@@ -2,7 +2,6 @@ module Gargantext.Components.Forest.Tree.Node.Action.Contact where
import Prelude
import Data.Either (Either)
import Data.Maybe (Maybe(..))
import Effect.Aff (Aff, launchAff)
import Formula as F
......@@ -12,7 +11,7 @@ import Toestand as T
import Gargantext.Components.Forest.Tree.Node.Action.Types (Action(..))
import Gargantext.Components.Forest.Tree.Node.Action.Contact.Types (AddContactParams(..))
import Gargantext.Config.REST (RESTError)
import Gargantext.Config.REST (AffRESTError)
import Gargantext.Routes as GR
import Gargantext.Sessions (Session, post)
import Gargantext.Types (ID)
......@@ -22,7 +21,7 @@ import Gargantext.Utils.Reactix as R2
here :: R2.Here
here = R2.here "Gargantext.Components.Forest.Tree.Node.Action.Contact"
contactReq :: Session -> ID -> AddContactParams -> Aff (Either RESTError ID)
contactReq :: Session -> ID -> AddContactParams -> AffRESTError ID
contactReq session nodeId =
post session $ GR.NodeAPI GT.Annuaire (Just nodeId) "contact"
......
......@@ -3,27 +3,25 @@ module Gargantext.Components.Forest.Tree.Node.Action.Delete
import Gargantext.Prelude
import Data.Either (Either)
import Data.Maybe (Maybe(..))
import Effect.Aff (Aff)
import Reactix as R
import Reactix.DOM.HTML as H
import Gargantext.Components.Forest.Tree.Node.Action.Types (Action(..))
import Gargantext.Components.Forest.Tree.Node.Tools (submitButton, panel)
import Gargantext.Config.REST (RESTError)
import Gargantext.Config.REST (AffRESTError)
import Gargantext.Routes (SessionRoute(..))
import Gargantext.Sessions (Session, delete, put_)
import Gargantext.Types (NodeType(..))
import Gargantext.Types as GT
import Gargantext.Utils.Reactix as R2
import Reactix as R
import Reactix.DOM.HTML as H
here :: R2.Here
here = R2.here "Gargantext.Components.Forest.Tree.Node.Action.Delete"
-- TODO Delete with asyncTaskWithType
deleteNode :: Session -> GT.ID -> Aff (Either RESTError GT.ID)
deleteNode :: Session -> GT.ID -> AffRESTError GT.ID
deleteNode session nodeId = delete session $ NodeAPI GT.Node (Just nodeId) ""
{-
......@@ -34,7 +32,7 @@ deleteNode session nodeId = delete session $ NodeAPI GT.Node (Just nodeId) ""
-}
type ParentID = GT.ID
unpublishNode :: Session -> Maybe ParentID -> GT.ID -> Aff (Either RESTError GT.ID)
unpublishNode :: Session -> Maybe ParentID -> GT.ID -> AffRESTError GT.ID
unpublishNode s p n = put_ s $ NodeAPI GT.Node p ("unpublish/" <> show n)
......
......@@ -6,11 +6,10 @@ import Data.Either (Either)
import Data.Generic.Rep (class Generic)
import Data.Maybe (Maybe(..))
import Data.Show.Generic (genericShow)
import Effect.Aff (Aff)
import Gargantext.Components.Forest.Tree.Node.Action.Types (Action(..))
import Gargantext.Components.Forest.Tree.Node.Tools (submitButton, panel)
import Gargantext.Components.Forest.Tree.Node.Tools.SubTree (subTreeView, SubTreeParamsIn)
import Gargantext.Config.REST (RESTError)
import Gargantext.Config.REST (AffRESTError, RESTError)
import Gargantext.Routes (SessionRoute(..))
import Gargantext.Sessions (Session, post)
import Gargantext.Types as GT
......@@ -31,7 +30,7 @@ derive newtype instance JSON.ReadForeign LinkNodeReq
derive newtype instance JSON.WriteForeign LinkNodeReq
linkNodeReq :: Session -> Maybe GT.NodeType -> GT.ID -> GT.ID -> Aff (Either RESTError GT.AsyncTaskWithType)
linkNodeReq :: Session -> Maybe GT.NodeType -> GT.ID -> GT.ID -> AffRESTError GT.AsyncTaskWithType
linkNodeReq session nt fromId toId = do
eTask :: Either RESTError GT.AsyncTask <- post session (NodeAPI GT.Node (Just fromId) "update")
(LinkNodeReq { nodeType: linkNodeType nt, id: toId })
......
......@@ -2,27 +2,24 @@ module Gargantext.Components.Forest.Tree.Node.Action.Merge where
import Gargantext.Prelude
import Data.Either (Either)
import Data.Maybe (Maybe(..))
import Data.Set as Set
import Effect.Aff (Aff)
import Reactix as R
import Reactix.DOM.HTML as H
import Toestand as T
import Gargantext.Components.Forest.Tree.Node.Action.Types (Action(..))
import Gargantext.Components.Forest.Tree.Node.Tools (submitButton, panel, checkbox, checkboxesListGroup)
import Gargantext.Components.Forest.Tree.Node.Tools.SubTree (subTreeView, SubTreeParamsIn)
import Gargantext.Config.REST (RESTError)
import Gargantext.Config.REST (AffRESTError)
import Gargantext.Routes (SessionRoute(..))
import Gargantext.Sessions (Session, put_)
import Gargantext.Types as GT
import Gargantext.Utils.Reactix as R2
import Reactix as R
import Reactix.DOM.HTML as H
import Toestand as T
here :: R2.Here
here = R2.here "Gargantext.Components.Forest.Tree.Node.Action.Merge"
mergeNodeReq :: Session -> GT.ID -> GT.ID -> Aff (Either RESTError (Array GT.ID))
mergeNodeReq :: Session -> GT.ID -> GT.ID -> AffRESTError (Array GT.ID)
mergeNodeReq session fromId toId =
put_ session $ NodeAPI GT.Node (Just fromId) ("merge/" <> show toId)
......
......@@ -3,26 +3,25 @@ module Gargantext.Components.Forest.Tree.Node.Action.Move
, moveNode
) where
import Data.Either (Either)
import Gargantext.Prelude
import Data.Maybe (Maybe(..))
import Effect.Aff (Aff)
import Gargantext.Components.Forest.Tree.Node.Action.Types (Action(..))
import Gargantext.Components.Forest.Tree.Node.Tools (submitButton, panel)
import Gargantext.Components.Forest.Tree.Node.Tools.SubTree (SubTreeParamsIn, subTreeView)
import Gargantext.Config.REST (RESTError)
import Gargantext.Prelude
import Gargantext.Config.REST (AffRESTError)
import Gargantext.Routes (SessionRoute(..))
import Gargantext.Sessions (Session, put_)
import Gargantext.Types as GT
import Gargantext.Types as GT
import Gargantext.Utils.Reactix as R2
import Reactix as R
import Reactix.DOM.HTML as H
import Toestand as T
import Reactix as R
import Reactix.DOM.HTML as H
import Toestand as T
here :: R2.Here
here = R2.here "Gargantext.Components.Forest.Tree.Node.Action.Move"
moveNodeReq :: Session -> GT.ID -> GT.ID -> Aff (Either RESTError (Array GT.ID))
moveNodeReq :: Session -> GT.ID -> GT.ID -> AffRESTError (Array GT.ID)
moveNodeReq session fromId toId =
put_ session $ NodeAPI GT.Node (Just fromId) ("move/" <> show toId)
......
module Gargantext.Components.Forest.Tree.Node.Action.Rename where
import Data.Either (Either)
import Gargantext.Prelude
import Data.Generic.Rep (class Generic)
import Data.Maybe (Maybe(..))
import Data.Newtype (class Newtype)
import Effect.Aff (Aff)
import Simple.JSON as JSON
import Gargantext.Prelude
import Gargantext.Components.Forest.Tree.Node.Action.Types (Action(..))
import Gargantext.Config.REST (RESTError)
import Gargantext.Config.REST (AffRESTError)
import Gargantext.Routes as GR
import Gargantext.Sessions (Session, put)
import Gargantext.Types (ID)
import Gargantext.Types as GT
import Simple.JSON as JSON
------------------------------------------------------------------------
rename :: Session -> ID -> RenameValue -> Aff (Either RESTError (Array ID))
rename :: Session -> ID -> RenameValue -> AffRESTError (Array ID)
rename session renameNodeId =
put session $ GR.NodeAPI GT.Node (Just renameNodeId) "rename"
......
module Gargantext.Components.Forest.Tree.Node.Action.Search.Types where
import Gargantext.Prelude
import Data.Array (concat)
import Data.Either (Either)
import Data.Generic.Rep (class Generic)
......@@ -10,21 +12,16 @@ import Data.Set as Set
import Data.String as String
import Data.Tuple (Tuple)
import Data.Tuple.Nested ((/\))
import Effect.Aff (Aff)
import Simple.JSON as JSON
import URI.Extra.QueryPairs as QP
import URI.Query as Q
import Gargantext.Prelude
import Gargantext.Components.Lang (Lang)
import Gargantext.Components.ListSelection.Types as ListSelection
import Gargantext.Config.REST (RESTError)
import Gargantext.Config.REST (AffRESTError, RESTError)
import Gargantext.Ends (class ToUrl, backendUrl)
import Gargantext.Routes as GR
import Gargantext.Sessions (Session(..), post)
import Gargantext.Types as GT
import Simple.JSON as JSON
import URI.Extra.QueryPairs as QP
import URI.Query as Q
type Search = { databases :: Database
, datafield :: Maybe DataField
......@@ -371,7 +368,7 @@ defaultSearchQuery = SearchQuery
, selection : ListSelection.MyListsFirst
}
performSearch :: Session -> Int -> SearchQuery -> Aff (Either RESTError GT.AsyncTaskWithType)
performSearch :: Session -> Int -> SearchQuery -> AffRESTError GT.AsyncTaskWithType
performSearch session nodeId q = do
eTask :: Either RESTError GT.AsyncTask <- post session p q
pure $ (\task -> GT.AsyncTaskWithType { task, typ: GT.Query }) <$> eTask
......
module Gargantext.Components.Forest.Tree.Node.Action.Share where
import Data.Either (Either)
import Gargantext.Prelude
import Data.Generic.Rep (class Generic)
import Data.Maybe (Maybe(..))
import Data.Show.Generic (genericShow)
import Effect.Aff (Aff)
import Reactix as R
import Reactix.DOM.HTML as H
import Simple.JSON as JSON
import Simple.JSON.Generics as JSONG
import Toestand as T
import Gargantext.Prelude
import Gargantext.Components.Forest.Tree.Node.Action.Types (Action)
import Gargantext.Components.Forest.Tree.Node.Action.Types as Action
import Gargantext.Components.Forest.Tree.Node.Tools as Tools
import Gargantext.Components.Forest.Tree.Node.Tools.SubTree (subTreeView, SubTreeParamsIn)
import Gargantext.Config.REST (RESTError)
import Gargantext.Config.REST (AffRESTError)
import Gargantext.Routes as GR
import Gargantext.Sessions (Session, post)
import Gargantext.Types (ID)
import Gargantext.Types as GT
import Gargantext.Utils.SimpleJSON as GUSJ
import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.SimpleJSON as GUSJ
import Reactix as R
import Reactix.DOM.HTML as H
import Simple.JSON as JSON
import Simple.JSON.Generics as JSONG
import Toestand as T
here :: R2.Here
here = R2.here "Gargantext.Components.Forest.Tree.Node.Action.Share"
------------------------------------------------------------------------
shareReq :: Session -> ID -> ShareNodeParams -> Aff (Either RESTError ID)
shareReq :: Session -> ID -> ShareNodeParams -> AffRESTError ID
shareReq session nodeId =
post session $ GR.NodeAPI GT.Node (Just nodeId) "share"
......
module Gargantext.Components.Forest.Tree.Node.Action.Update where
import Gargantext.Components.Forest.Tree.Node.Action.Update.Types
import Gargantext.Prelude
import Data.Either (Either(..))
import Data.Maybe (Maybe(..))
import Effect.Aff (Aff)
import Reactix as R
import Reactix.DOM.HTML as H
import Toestand as T
import Gargantext.Prelude
import Gargantext.Components.Forest.Tree.Node.Action.Types (Action(..))
import Gargantext.Components.Forest.Tree.Node.Action.Update.Types
import Gargantext.Components.Forest.Tree.Node.Tools (formChoiceSafe, submitButton, panel)
import Gargantext.Config.REST (RESTError)
import Gargantext.Config.REST (RESTError, AffRESTError)
import Gargantext.Routes as GR
import Gargantext.Sessions (Session, post)
import Gargantext.Types (NodeType(..), ID)
import Gargantext.Types as GT
import Gargantext.Utils.Reactix as R2
import Reactix as R
import Reactix.DOM.HTML as H
import Toestand as T
here :: R2.Here
here = R2.here "Gargantext.Components.Forest.Tree.Node.Action.Update"
updateRequest :: UpdateNodeParams -> Session -> ID -> Aff (Either RESTError GT.AsyncTaskWithType)
updateRequest :: UpdateNodeParams -> Session -> ID -> AffRESTError GT.AsyncTaskWithType
updateRequest updateNodeParams session nodeId = do
eTask :: Either RESTError GT.AsyncTask <- post session p updateNodeParams
case eTask of
......
......@@ -23,7 +23,7 @@ import Gargantext.Components.Lang (Lang(..))
import Gargantext.Components.ListSelection as ListSelection
import Gargantext.Components.ListSelection.Types (Selection(..))
import Gargantext.Components.ListSelection.Types as ListSelection
import Gargantext.Config.REST (RESTError)
import Gargantext.Config.REST (AffRESTError, RESTError)
import Gargantext.Routes as GR
import Gargantext.Sessions (Session, postWwwUrlencoded, post)
import Gargantext.Types (ID, NodeType(..))
......@@ -355,7 +355,7 @@ uploadFile :: { contents :: String
, mName :: Maybe String
, selection :: ListSelection.Selection
, session :: Session }
-> Aff (Either RESTError GT.AsyncTaskWithType)
-> AffRESTError GT.AsyncTaskWithType
{-
uploadFile session NodeList id JSON { mName, contents } = do
let url = GR.NodeAPI NodeList (Just id) $ GT.asyncTaskTypePath GT.ListUpload
......@@ -394,7 +394,7 @@ uploadArbitraryFile :: Session
-> ID
-> {blob :: UploadFileBlob, mName :: Maybe String}
-> ListSelection.Selection
-> Aff (Either RESTError GT.AsyncTaskWithType)
-> AffRESTError GT.AsyncTaskWithType
uploadArbitraryFile session id {mName, blob: UploadFileBlob blob} selection = do
contents <- readAsDataURL blob
uploadArbitraryData session id mName contents
......@@ -403,7 +403,7 @@ uploadArbitraryData :: Session
-> ID
-> Maybe String
-> String
-> Aff (Either RESTError GT.AsyncTaskWithType)
-> AffRESTError GT.AsyncTaskWithType
uploadArbitraryData session id mName contents' = do
let re = fromRight' (\_ -> unsafeCrashWith "Unexpected Left") $ DSR.regex "data:.*;base64," DSRF.noFlags
contents = DSR.replace re "" contents'
......@@ -544,7 +544,7 @@ uploadFrameCalcViewCpt = here.component "uploadFrameCalcView" cpt
uploadFrameCalc :: Session
-> ID
-> Aff (Either RESTError GT.AsyncTaskWithType)
-> AffRESTError GT.AsyncTaskWithType
uploadFrameCalc session id = do
let p = GR.NodeAPI GT.Node (Just id) $ GT.asyncTaskTypePath GT.UploadFrameCalc
......
......@@ -8,7 +8,7 @@ import Effect.Aff (Aff)
import Gargantext.Components.App.Data (Boxes)
import Gargantext.Components.Forest.Tree.Node.Action.Types (Action(..))
import Gargantext.Components.Forest.Tree.Node.Tools (panel, submitButton)
import Gargantext.Config.REST (RESTError)
import Gargantext.Config.REST (AffRESTError, RESTError)
import Gargantext.Routes (SessionRoute(..))
import Gargantext.Sessions (Session, post)
import Gargantext.Types as GT
......@@ -43,7 +43,7 @@ actionWriteNodesDocumentsCpt = here.component "actionWriteNodesDocuments" cpt wh
pure $ panel bodies (submitButton (DocumentsFromWriteNodes { id }) dispatch)
documentsFromWriteNodesReq :: Session -> GT.ID -> Aff (Either RESTError GT.AsyncTaskWithType)
documentsFromWriteNodesReq :: Session -> GT.ID -> AffRESTError GT.AsyncTaskWithType
documentsFromWriteNodesReq session id = do
eTask :: Either RESTError GT.AsyncTask <-
post session (NodeAPI GT.Node (Just id) "documents-from-write-nodes") { id }
......
......@@ -2,14 +2,13 @@ module Gargantext.Components.Forest.Tree.Node.Tools.ProgressBar where
import Gargantext.Prelude
import Data.Either (Either)
import Data.Int (fromNumber)
import Data.Maybe (Maybe(..))
import Effect (Effect)
import Effect.Aff (Aff, launchAff_)
import Effect.Aff (launchAff_)
import Effect.Class (liftEffect)
import Effect.Timer (clearInterval, setInterval)
import Gargantext.Config.REST (RESTError)
import Gargantext.Config.REST (AffRESTError)
import Gargantext.Config.Utils (handleErrorInAsyncProgress, handleRESTError)
import Gargantext.Routes (SessionRoute(..))
import Gargantext.Sessions (Session, get)
......@@ -109,7 +108,7 @@ progressIndicatorCpt = here.component "progressIndicator" cpt
Nothing -> 0
Just x -> x
queryProgress :: Record Props -> Aff (Either RESTError GT.AsyncProgress)
queryProgress :: Record Props -> AffRESTError GT.AsyncProgress
queryProgress { asyncTask: GT.AsyncTaskWithType { task: GT.AsyncTask {id}
, typ
}
......
......@@ -4,18 +4,16 @@ import Gargantext.Prelude
import Data.Array (length)
import Data.Array as A
import Data.Either (Either)
import Data.Foldable (intercalate)
import Data.Maybe (Maybe(..))
import Data.Tuple.Nested ((/\))
import Effect.Aff (Aff)
import Gargantext.Components.App.Data (Boxes)
import Gargantext.Components.Forest.Tree.Node.Action (Props, subTreeOut, setTreeOut)
import Gargantext.Components.Forest.Tree.Node.Action.Types (Action)
import Gargantext.Components.Forest.Tree.Node.Tools (nodeText)
import Gargantext.Components.Forest.Tree.Node.Tools.FTree (FTree, LNode(..), NTree(..))
import Gargantext.Components.Forest.Tree.Node.Tools.SubTree.Types (SubTreeParams(..), SubTreeOut(..))
import Gargantext.Config.REST (RESTError, logRESTError)
import Gargantext.Config.REST (AffRESTError, logRESTError)
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Routes as GR
import Gargantext.Sessions (Session(..), get)
......@@ -76,12 +74,12 @@ subTreeViewCpt = here.component "subTreeView" cpt
where
errorHandler = logRESTError here "[subTreeView]"
loadSubTree :: Array GT.NodeType -> Session -> Aff (Either RESTError FTree)
loadSubTree :: Array GT.NodeType -> Session -> AffRESTError FTree
loadSubTree nodetypes session = getSubTree session treeId nodetypes
where
Session { treeId } = session
getSubTree :: Session -> Int -> Array GT.NodeType -> Aff (Either RESTError FTree)
getSubTree :: Session -> Int -> Array GT.NodeType -> AffRESTError FTree
getSubTree session treeId showtypes = get session $ GR.NodeAPI GT.Tree (Just treeId) nodeTypes
where
nodeTypes = A.foldl (\a b -> a <> "type=" <> show b <> "&") "?" showtypes
......
......@@ -4,7 +4,6 @@ import Gargantext.Prelude hiding (max, min)
import DOM.Simple.Types (Element)
import Data.Array as A
import Data.Either (Either)
import Data.FoldableWithIndex (foldMapWithIndex)
import Data.Int (toNumber)
import Data.Map as Map
......@@ -13,13 +12,12 @@ import Data.Nullable (null, Nullable)
import Data.Sequence as Seq
import Data.Set as Set
import Data.Tuple (Tuple(..))
import Effect.Aff (Aff)
import Gargantext.Components.App.Data (Boxes)
import Gargantext.Components.Graph as Graph
import Gargantext.Components.GraphExplorer.Controls as Controls
import Gargantext.Components.GraphExplorer.Sidebar.Types as GEST
import Gargantext.Components.GraphExplorer.Types as GET
import Gargantext.Config.REST (RESTError, logRESTError)
import Gargantext.Config.REST (AffRESTError, logRESTError)
import Gargantext.Data.Louvain as Louvain
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Hooks.Sigmax.Types as SigmaxT
......@@ -294,7 +292,7 @@ modeGraphType Types.Sources = "star"
modeGraphType Types.Terms = "def"
getNodes :: Session -> T2.Reload -> GET.GraphId -> Aff (Either RESTError GET.HyperdataGraph)
getNodes :: Session -> T2.Reload -> GET.GraphId -> AffRESTError GET.HyperdataGraph
getNodes session graphVersion graphId =
get session $ NodeAPI Types.Graph
(Just graphId)
......
......@@ -2,12 +2,10 @@ module Gargantext.Components.GraphExplorer.API where
import Gargantext.Prelude
import Data.Either (Either)
import Data.Maybe (Maybe)
import Effect.Aff (Aff)
import Gargantext.Components.GraphExplorer.Types as GET
import Gargantext.Components.NgramsTable.Core as NTC
import Gargantext.Config.REST (RESTError)
import Gargantext.Config.REST (AffRESTError)
import Gargantext.Hooks.Sigmax.Types as SigmaxT
import Gargantext.Routes as GR
import Gargantext.Sessions (Session, get, post)
......@@ -22,7 +20,7 @@ type GraphAsyncUpdateParams =
, version :: NTC.Version
)
graphAsyncUpdate :: Record GraphAsyncUpdateParams -> Aff (Either RESTError GT.AsyncTaskWithType)
graphAsyncUpdate :: Record GraphAsyncUpdateParams -> AffRESTError GT.AsyncTaskWithType
graphAsyncUpdate { graphId, listId, nodes, session, termList, version } = do
eTask <- post session p q
pure $ (\task -> GT.AsyncTaskWithType { task, typ: GT.GraphRecompute }) <$> eTask
......@@ -39,7 +37,7 @@ type GraphAsyncRecomputeParams =
, session :: Session
)
graphAsyncRecompute :: Record GraphAsyncRecomputeParams -> Aff (Either RESTError GT.AsyncTaskWithType)
graphAsyncRecompute :: Record GraphAsyncRecomputeParams -> AffRESTError GT.AsyncTaskWithType
graphAsyncRecompute { graphId, session } = do
eTask <- post session p q
pure $ (\task -> GT.AsyncTaskWithType { task, typ: GT.GraphRecompute }) <$> eTask
......@@ -53,7 +51,7 @@ type QueryProgressParams =
, taskId :: String
)
queryProgress :: Record QueryProgressParams -> Aff (Either RESTError GT.AsyncProgress)
queryProgress :: Record QueryProgressParams -> AffRESTError GT.AsyncProgress
queryProgress { graphId, session, taskId } = do
get session $ GR.GraphAPI graphId $ "async/" <> taskId <> "/poll"
......@@ -67,7 +65,7 @@ type GraphVersionsParams =
, session :: Session
)
graphVersions :: Record GraphVersionsParams -> Aff (Either RESTError (Record GraphVersions))
graphVersions :: Record GraphVersionsParams -> AffRESTError (Record GraphVersions)
graphVersions { graphId, session } = get session $ GR.GraphAPI graphId $ "versions"
type UpdateGraphVersionsParams =
......@@ -75,7 +73,7 @@ type UpdateGraphVersionsParams =
, session :: Session
)
updateGraphVersions :: Record UpdateGraphVersionsParams -> Aff (Either RESTError GET.GraphData)
updateGraphVersions :: Record UpdateGraphVersionsParams -> AffRESTError GET.GraphData
updateGraphVersions { graphId, session } = post session (GR.GraphAPI graphId $ "versions") {}
type CloneGraphParams =
......@@ -84,5 +82,5 @@ type CloneGraphParams =
, session :: Session
)
cloneGraph :: Record CloneGraphParams -> Aff (Either RESTError Int)
cloneGraph :: Record CloneGraphParams -> AffRESTError Int
cloneGraph { hyperdataGraph, id, session } = post session (GR.GraphAPI id $ "clone") hyperdataGraph
......@@ -15,7 +15,7 @@ import Data.Maybe (Maybe(..), fromJust)
import Data.Sequence as Seq
import Data.Set as Set
import Effect (Effect)
import Effect.Aff (Aff, launchAff_)
import Effect.Aff (launchAff_)
import Effect.Class (liftEffect)
import Gargantext.Components.App.Data (Boxes)
import Gargantext.Components.GraphExplorer.Legend as Legend
......@@ -26,7 +26,7 @@ import Gargantext.Components.NgramsTable.Core as NTC
import Gargantext.Components.Nodes.Corpus.Graph.Tabs (tabs) as CGT
import Gargantext.Components.RandomText (words)
import Gargantext.Components.Search (SearchType(..), SearchQuery(..))
import Gargantext.Config.REST (RESTError)
import Gargantext.Config.REST (AffRESTError)
import Gargantext.Data.Array (mapMaybe)
import Gargantext.Ends (Frontends)
import Gargantext.Hooks.Sigmax.Types as SigmaxT
......@@ -375,7 +375,7 @@ sendPatch :: TermList
-> Session
-> GET.MetaData
-> Record SigmaxT.Node
-> Aff (Either RESTError NTC.VersionedNgramsPatches)
-> AffRESTError NTC.VersionedNgramsPatches
sendPatch termList session (GET.MetaData metaData) node = do
eRet <- NTC.putNgramsPatches coreParams versioned
case eRet of
......
......@@ -10,8 +10,10 @@ import Effect (Effect)
import Effect.Aff (Aff)
import Effect.Class (liftEffect)
import Foreign (unsafeToForeign, ForeignError)
import Gargantext.Components.GraphQL.Node (Node)
import Gargantext.Components.GraphQL.User (User, UserInfo, UserInfoM)
import Gargantext.Sessions (Session(..))
import Gargantext.Types (NodeType)
import Gargantext.Utils.Reactix as R2
import GraphQL.Client.Args (type (==>))
import GraphQL.Client.BaseClients.Urql (UrqlClient, createClient)
......@@ -65,7 +67,8 @@ queryGql session name q = do
-- Schema
type Schema
= { user_infos :: { user_id :: Int } ==> Array UserInfo
= { node_parent :: { node_id :: Int, parent_type :: String } ==> Array Node -- TODO: parent_type :: NodeType
, user_infos :: { user_id :: Int } ==> Array UserInfo
, users :: { user_id :: Int } ==> Array User
}
......
module Gargantext.Components.GraphQL.Endpoints where
import Data.Array as A
import Data.Either (Either(..))
import Data.Maybe (Maybe(..))
import Effect.Aff (Aff)
import Effect.Class (liftEffect)
import Gargantext.Components.GraphQL (queryGql)
import Gargantext.Components.GraphQL.Node
import Gargantext.Components.GraphQL.User
import Gargantext.Config.REST (AffRESTError, RESTError(..))
import Gargantext.Prelude
import Gargantext.Sessions (Session)
import Gargantext.Types (NodeType)
import Gargantext.Utils.Reactix as R2
import GraphQL.Client.Variables (withVars)
here :: R2.Here
here = R2.here "Gargantext.Components.GraphQL.Endpoints"
getNodeParent :: Session -> Int -> NodeType -> Aff (Array Node)
getNodeParent session nodeId parentType = do
{ node_parent } <- queryGql session "get node parent" $
nodeParentQuery `withVars` { id: nodeId
, parent_type: show parentType } -- TODO: remove "show"
liftEffect $ here.log2 "[getNodeParent] node_parent" node_parent
pure $ node_parent
getUserInfo :: Session -> Int -> AffRESTError 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
module Gargantext.Components.GraphQL.Node where
import Gargantext.Prelude
import GraphQL.Client.Args ((=>>))
import GraphQL.Client.Variable (Var(..))
import Gargantext.Types (NodeType)
type Node
= { id :: Int
, name :: String
, parent_id :: Int
, type_id :: Int }
nodesQuery = { nodes: { node_id: Var :: _ "id" Int } =>>
{ id: unit
, name: unit
, parent_id: unit
, type_id: unit }
}
nodeParentQuery = { node_parent: { node_id: Var :: _ "id" Int
, parent_type: Var :: _ "parent_type" String } =>> -- TODO parent_type :: NodeType
{ id: unit
, name: unit
, parent_id: unit
, type_id: unit }
}
......@@ -5,10 +5,8 @@ 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.Args (NotNull, (=>>))
import GraphQL.Client.Variable (Var(..))
import GraphQL.Client.Variables (withVars)
import Type.Proxy (Proxy(..))
type UserInfo
......@@ -144,3 +142,4 @@ showUser { u_id
, u_username
, u_email } = "[" <> show u_id <> "] " <> u_username <> " :: " <> u_email
showMUser u = maybe "" showUser u
......@@ -27,14 +27,13 @@ import Data.Tuple.Nested ((/\))
import Effect (Effect)
import Effect.Aff (Aff)
import Gargantext.Components.App.Data (Boxes)
import Gargantext.Components.AutoUpdate (autoUpdateElt)
import Gargantext.Components.NgramsTable.Components as NTC
import Gargantext.Components.NgramsTable.Core (Action(..), CoreAction(..), CoreState, Dispatch, NgramsElement(..), NgramsPatch(..), NgramsTable, NgramsTerm, PageParams, PatchMap(..), Versioned(..), VersionedNgramsTable, VersionedWithCountNgramsTable, _NgramsElement, _NgramsRepoElement, _NgramsTable, _children, _list, _ngrams, _ngrams_repo_elements, _ngrams_scores, _occurrences, _root, addNewNgramA, applyNgramsPatches, applyPatchSet, chartsAfterSync, commitPatch, convOrderBy, coreDispatch, filterTermSize, fromNgramsPatches, ngramsRepoElementToNgramsElement, ngramsTermText, normNgram, patchSetFromMap, replace, singletonNgramsTablePatch, syncResetButtons, toVersioned)
import Gargantext.Components.NgramsTable.Loader (useLoaderWithCacheAPI)
import Gargantext.Components.Nodes.Lists.Types as NT
import Gargantext.Components.Table as TT
import Gargantext.Components.Table.Types as TT
import Gargantext.Config.REST (RESTError, logRESTError)
import Gargantext.Config.REST (AffRESTError, logRESTError)
import Gargantext.Hooks.Loader (useLoaderBox)
import Gargantext.Routes (SessionRoute(..)) as R
import Gargantext.Sessions (Session, get)
......@@ -633,7 +632,7 @@ mainNgramsTableCacheOffCpt = here.component "mainNgramsTableCacheOff" cpt where
errorHandler = logRESTError here "[mainNgramsTable]"
-- NOTE With cache off
loader :: PageParams -> Aff (Either RESTError VersionedWithCountNgramsTable)
loader :: PageParams -> AffRESTError VersionedWithCountNgramsTable
loader { listIds
, nodeId
, params: { limit, offset }
......
module Gargantext.Components.NgramsTable.API where
import Data.Either (Either)
import Effect.Aff (Aff)
import Gargantext.Config.REST (RESTError)
import Gargantext.Config.REST (AffRESTError)
import Gargantext.Routes as GR
import Gargantext.Sessions (Session, post)
import Gargantext.Types as GT
......@@ -16,6 +13,6 @@ type UpdateNodeListParams =
, session :: Session
)
updateNodeList :: Record UpdateNodeListParams -> Aff (Either RESTError Int)
updateNodeList :: Record UpdateNodeListParams -> AffRESTError Int
updateNodeList { listId, nodeId, nodeType, session } =
post session (GR.RecomputeNgrams nodeType nodeId listId) {}
......@@ -79,6 +79,8 @@ module Gargantext.Components.NgramsTable.Core
)
where
import Gargantext.Prelude
import Control.Monad.State (class MonadState, execState)
import DOM.Simple.Console (log2)
import Data.Array (head)
......@@ -125,23 +127,22 @@ import Effect.Exception.Unsafe (unsafeThrow)
import FFI.Simple.Functions (delay)
import Foreign as F
import Foreign.Object as FO
import Reactix (Component, Element, createElement) as R
import Reactix.DOM.HTML as H
import Partial (crashWith)
import Partial.Unsafe (unsafePartial)
import Gargantext.AsyncTasks as GAT
import Gargantext.Components.Table as T
import Gargantext.Components.Table.Types as T
import Gargantext.Config.REST (RESTError)
import Gargantext.Config.REST (RESTError, AffRESTError)
import Gargantext.Config.Utils (handleRESTError)
import Gargantext.Prelude
import Gargantext.Routes (SessionRoute(..))
import Gargantext.Sessions (Session, get, post, put)
import Gargantext.Types (AsyncTask, AsyncTaskType(..), AsyncTaskWithType(..), CTabNgramType(..), FrontendError, ListId, OrderBy(..), ScoreType(..), TabSubType(..), TabType(..), TermList(..), TermSize(..))
import Gargantext.Utils.Either (eitherMap)
import Gargantext.Utils.KarpRabin (indicesOfAny)
import Gargantext.Utils.Reactix as R2
import Partial (crashWith)
import Partial.Unsafe (unsafePartial)
import Reactix (Component, Element, createElement) as R
import Reactix as R
import Reactix.DOM.HTML as H
import Simple.JSON as JSON
import Toestand as T
......@@ -903,7 +904,7 @@ setTermListP ngram patch_list = singletonNgramsTablePatch ngram pe
setTermListA :: NgramsTerm -> Replace TermList -> CoreAction
setTermListA ngram termList = CommitPatch $ setTermListP ngram termList
putNgramsPatches :: forall s. CoreParams s -> VersionedNgramsPatches -> Aff (Either RESTError VersionedNgramsPatches)
putNgramsPatches :: forall s. CoreParams s -> VersionedNgramsPatches -> AffRESTError VersionedNgramsPatches
putNgramsPatches { listIds, nodeId, session, tabType } = put session putNgrams
where putNgrams = PutNgrams tabType (head listIds) Nothing (Just nodeId)
......@@ -967,7 +968,7 @@ commitPatch tablePatch state = do
T.modify_ (\s -> s { ngramsLocalPatch = tablePatch <> s.ngramsLocalPatch }) state
-- First we apply the patches we have locally and then the new patch (tablePatch).
loadNgramsTable :: PageParams -> Aff (Either RESTError VersionedNgramsTable)
loadNgramsTable :: PageParams -> AffRESTError VersionedNgramsTable
loadNgramsTable
{ nodeId
, listIds
......@@ -988,7 +989,7 @@ loadNgramsTable
type NgramsListByTabType = Map TabType VersionedNgramsTable
loadNgramsTableAll :: PageParams -> Aff (Either RESTError NgramsListByTabType)
loadNgramsTableAll :: PageParams -> AffRESTError NgramsListByTabType
loadNgramsTableAll { nodeId, listIds, session } = do
let
cTagNgramTypes =
......@@ -1127,7 +1128,7 @@ chartsAfterSync path'@{ nodeId } errors tasks _ = do
log2 "[chartsAfterSync] Synchronize task" task
GAT.insert nodeId task tasks
postNgramsChartsAsync :: forall s. CoreParams s -> Aff (Either RESTError AsyncTaskWithType)
postNgramsChartsAsync :: forall s. CoreParams s -> AffRESTError AsyncTaskWithType
postNgramsChartsAsync { listIds, nodeId, session, tabType } = do
eTask :: Either RESTError AsyncTask <- post session putNgramsAsync acu
pure $ (\task -> AsyncTaskWithType { task, typ: UpdateNgramsCharts }) <$> eTask
......
......@@ -11,7 +11,7 @@ import Effect.Class (liftEffect)
import Effect.Exception (error)
import Gargantext.Components.LoadingSpinner (loadingSpinner)
import Gargantext.Components.NgramsTable.Core (Version, Versioned(..))
import Gargantext.Config.REST (RESTError(..))
import Gargantext.Config.REST (RESTError(..), AffRESTError)
import Gargantext.Utils.CacheAPI as GUC
import Reactix as R
import Simple.JSON as JSON
......@@ -26,7 +26,7 @@ clearCache _ = GUC.delete $ GUC.CacheName cacheName
type LoaderWithCacheAPIProps path res ret = (
cacheEndpoint :: path -> Aff (Either RESTError Version)
cacheEndpoint :: path -> AffRESTError Version
, errorHandler :: RESTError -> Effect Unit
, handleResponse :: Versioned res -> ret
, mkRequest :: path -> GUC.Request
......@@ -51,7 +51,7 @@ useLoaderWithCacheAPI { cacheEndpoint, errorHandler, handleResponse, mkRequest,
pure $ maybe (loadingSpinner {}) renderer state'
type LoaderWithCacheAPIEffectProps path res ret = (
cacheEndpoint :: path -> Aff (Either RESTError Version)
cacheEndpoint :: path -> AffRESTError Version
, errorHandler :: RESTError -> Effect Unit
, handleResponse :: Versioned res -> ret
, mkRequest :: path -> GUC.Request
......
......@@ -5,20 +5,19 @@ module Gargantext.Components.Nodes.Annuaire
import Gargantext.Prelude
import Data.Array as A
import Data.Either (Either)
import Data.Eq.Generic (genericEq)
import Data.Generic.Rep (class Generic)
import Data.Maybe (Maybe(..), maybe, fromMaybe)
import Data.Newtype (class Newtype)
import Data.Sequence as Seq
import Data.Symbol (SProxy(..))
import Effect.Aff (Aff, launchAff_)
import Effect.Aff (launchAff_)
import Gargantext.Components.NgramsTable.Loader (clearCache)
import Gargantext.Components.Nodes.Annuaire.User.Contacts.Types as CT
import Gargantext.Components.Nodes.Lists.Types as NT
import Gargantext.Components.Table (defaultContainer, initialParams, makeRow, table, tableHeaderLayout) as TT
import Gargantext.Components.Table.Types (ColumnName(..), Params) as TT
import Gargantext.Config.REST (RESTError, logRESTError)
import Gargantext.Config.REST (AffRESTError, logRESTError)
import Gargantext.Ends (url, Frontends)
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Routes (SessionRoute(..))
......@@ -293,6 +292,6 @@ loadPage session {nodeId, params: { offset, limit }} =
where
children = Children NodeContact offset limit Nothing {-(convOrderBy <$> orderBy)-} (Just nodeId)
getAnnuaireInfo :: Session -> Int -> Aff (Either RESTError AnnuaireInfo)
getAnnuaireInfo :: Session -> Int -> AffRESTError AnnuaireInfo
getAnnuaireInfo session id = get session (NodeAPI Node (Just id) "")
......@@ -7,10 +7,9 @@ module Gargantext.Components.Nodes.Annuaire.User
import Gargantext.Prelude
import Data.Either (Either)
import Data.Maybe (Maybe(..), fromMaybe)
import Effect (Effect)
import Effect.Aff (Aff, launchAff_)
import Effect.Aff (launchAff_)
import Effect.Class (liftEffect)
import Gargantext.Components.App.Data (Boxes)
import Gargantext.Components.GraphQL.User (UserInfo)
......@@ -18,13 +17,13 @@ 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.Lists.Types as LT
import Gargantext.Config.REST (RESTError, logRESTError)
import Gargantext.Config.REST (logRESTError)
import Gargantext.Config.Utils (handleRESTError)
import Gargantext.Ends (Frontends)
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Routes as Routes
import Gargantext.Sessions (WithSession, WithSessionContext, Session, get, put, sessionId)
import Gargantext.Types (FrontendError, NodeType(..))
import Gargantext.Sessions (WithSession, WithSessionContext, sessionId)
import Gargantext.Types (FrontendError)
import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Toestand as T2
import Reactix as R
......@@ -131,11 +130,11 @@ userLayoutWithKeyCpt = here.component "userLayoutWithKey" cpt where
handleRESTError errors res $ \_ ->
liftEffect $ T2.reload reload
--saveContactHyperdata :: Session -> Int -> HyperdataUser -> Aff (Either RESTError Int)
--saveContactHyperdata :: Session -> Int -> HyperdataUser -> AffRESTError Int
--saveContactHyperdata session id = put session (Routes.NodeAPI Node (Just id) "")
-- | toUrl to get data XXX
--getContact :: Session -> Int -> Aff (Either RESTError ContactData)
--getContact :: Session -> Int -> AffRESTError ContactData
--getContact session id = do
-- eContactNode <- get session $ Routes.NodeAPI Node (Just id) ""
-- -- TODO: we need a default list for the pairings
......
......@@ -2,7 +2,6 @@ module Gargantext.Components.Nodes.Annuaire.User.Contact
( module Gargantext.Components.Nodes.Annuaire.User.Contacts.Types
, contactInfos
, contactLayout
, getUserInfo
, getUserInfoWithReload
, saveContactHyperdata
, saveUserInfo
......@@ -11,21 +10,21 @@ module Gargantext.Components.Nodes.Annuaire.User.Contact
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.Maybe (Maybe(..), fromMaybe)
import Effect (Effect)
import Effect.Aff (Aff, launchAff_)
import Effect.Aff (launchAff_)
import Effect.Class (liftEffect)
import Gargantext.Components.App.Data (Boxes)
import Gargantext.Components.GraphQL (getClient, queryGql)
import Gargantext.Components.GraphQL (getClient)
import Gargantext.Components.GraphQL.Endpoints (getUserInfo)
import Gargantext.Components.InputWithEnter (inputWithEnter)
import Gargantext.Components.Nodes.Annuaire.User.Contacts.Tabs as Tabs
import Gargantext.Components.Nodes.Annuaire.User.Contacts.Types (ContactData', HyperdataContact(..))
import Gargantext.Components.Nodes.Lists.Types as LT
import Gargantext.Config.REST (RESTError(..), logRESTError)
import Gargantext.Config.REST (AffRESTError, logRESTError)
import Gargantext.Ends (Frontends)
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Routes as Routes
......@@ -33,9 +32,8 @@ import Gargantext.Sessions (Session, get, put, sessionId)
import Gargantext.Types (NodeType(..))
import Gargantext.Utils.Reactix as R2
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 GraphQL.Client.Args (IgnoreArg(..), OrArg(..), onlyArgs)
import GraphQL.Client.Query (mutationOpts)
import Reactix as R
import Reactix.DOM.HTML as H
import Record as Record
......@@ -194,10 +192,10 @@ type KeyLayoutProps =
, session :: Session
| ReloadProps )
saveContactHyperdata :: Session -> Int -> HyperdataContact -> Aff (Either RESTError Int)
saveContactHyperdata :: Session -> Int -> HyperdataContact -> AffRESTError Int
saveContactHyperdata session id = put session (Routes.NodeAPI Node (Just id) "")
saveUserInfo :: Session -> Int -> UserInfo -> Aff (Either RESTError Int)
saveUserInfo :: Session -> Int -> UserInfo -> AffRESTError Int
saveUserInfo session id ui = do
client <- liftEffect $ getClient session
res <- mutationOpts
......@@ -273,7 +271,7 @@ contactLayoutWithKeyCpt = here.component "contactLayoutWithKey" cpt where
_ <- saveUserInfo session nodeId ui
liftEffect (T2.reload reload)
getAnnuaireContact :: Session -> Int -> Int -> Aff (Either RESTError ContactData')
getAnnuaireContact :: Session -> Int -> Int -> AffRESTError ContactData'
getAnnuaireContact session annuaireId id = do
eContactNode <- get session $ Routes.NodeAPI Annuaire (Just annuaireId) $ show id
-- TODO: we need a default list for the pairings
......@@ -288,14 +286,5 @@ getAnnuaireContact session annuaireId id = do
getUserInfoWithReload :: { nodeId :: Int
, reload :: T2.Reload
, session :: Session} -> Aff (Either RESTError UserInfo)
, session :: Session} -> AffRESTError 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
......@@ -8,7 +8,7 @@ import Data.List as List
import Data.Maybe (Maybe(..), fromMaybe)
import Data.Show.Generic (genericShow)
import Effect (Effect)
import Effect.Aff (Aff, throwError)
import Effect.Aff (throwError)
import Effect.Exception (error)
import Gargantext.Components.App.Data (Boxes)
import Gargantext.Components.CodeEditor as CE
......@@ -18,7 +18,7 @@ import Gargantext.Components.Node (NodePoly(..), HyperdataList)
import Gargantext.Components.Nodes.Corpus.Types (CorpusData, Hyperdata)
import Gargantext.Components.Nodes.Types (FTField, FTFieldWithIndex, FTFieldsWithIndex(..), Field(..), FieldType(..), Hash, Index, defaultHaskell', defaultJSON', defaultMarkdown', defaultPython')
import Gargantext.Components.TileMenu (tileMenu)
import Gargantext.Config.REST (RESTError(..))
import Gargantext.Config.REST (RESTError(..), AffRESTError)
import Gargantext.Data.Array as GDA
import Gargantext.Prelude (class Eq, class Show, Unit, bind, discard, pure, show, unit, ($), (<>), const, (<<<), (+), (==), (-), (<), (>), (<$>))
import Gargantext.Routes (SessionRoute(Children, NodeAPI))
......@@ -363,11 +363,11 @@ type LoadProps =
, session :: Session
)
loadCorpus' :: Record LoadProps -> Aff (Either RESTError (NodePoly Hyperdata))
loadCorpus' :: Record LoadProps -> AffRESTError (NodePoly Hyperdata)
loadCorpus' {nodeId, session} = get session $ NodeAPI Corpus (Just nodeId) ""
-- Just to make reloading effective
loadCorpusWithReload :: { reload :: T2.Reload | LoadProps } -> Aff (Either RESTError (NodePoly Hyperdata))
loadCorpusWithReload :: { reload :: T2.Reload | LoadProps } -> AffRESTError (NodePoly Hyperdata)
loadCorpusWithReload {nodeId, session} = loadCorpus' {nodeId, session}
type SaveProps = (
......@@ -375,11 +375,11 @@ type SaveProps = (
| LoadProps
)
saveCorpus :: Record SaveProps -> Aff (Either RESTError Int)
saveCorpus :: Record SaveProps -> AffRESTError Int
saveCorpus {hyperdata, nodeId, session} = do
put session (NodeAPI Corpus (Just nodeId) "") hyperdata
loadCorpus :: Record LoadProps -> Aff (Either RESTError CorpusData)
loadCorpus :: Record LoadProps -> AffRESTError CorpusData
loadCorpus {nodeId, session} = do
-- fetch corpus via lists parentId
res <- get session nodePolyRoute
......@@ -416,7 +416,7 @@ loadCorpus {nodeId, session} = do
defaultListIdsRoute = Children NodeList 0 1 Nothing <<< Just
loadCorpusWithChild :: Record LoadProps -> Aff (Either RESTError CorpusData)
loadCorpusWithChild :: Record LoadProps -> AffRESTError CorpusData
loadCorpusWithChild { nodeId: childId, session } = do
-- fetch corpus via lists parentId
eListNode <- get session $ listNodeRoute childId ""
......@@ -452,7 +452,7 @@ type LoadWithReloadProps =
-- Just to make reloading effective
loadCorpusWithChildAndReload :: Record LoadWithReloadProps -> Aff (Either RESTError CorpusData)
loadCorpusWithChildAndReload :: Record LoadWithReloadProps -> AffRESTError CorpusData
loadCorpusWithChildAndReload {nodeId, session} = loadCorpusWithChild {nodeId, session}
data ViewType = Code | Folders
......
module Gargantext.Components.Nodes.Corpus.Chart.API where
import Data.Either (Either)
import Effect.Aff (Aff)
import Gargantext.Config.REST (RESTError)
import Gargantext.Config.REST (AffRESTError)
import Gargantext.Routes (SessionRoute(..))
import Gargantext.Sessions (Session, post)
import Gargantext.Types as T
recomputeChart :: Session -> T.ChartType -> T.CTabNgramType -> Int -> Int -> Aff (Either RESTError (Array Int))
recomputeChart :: Session -> T.ChartType -> T.CTabNgramType -> Int -> Int -> AffRESTError (Array Int)
recomputeChart session chartType ngramType corpusId listId =
post session (RecomputeListChart chartType ngramType corpusId listId) {}
......@@ -3,11 +3,9 @@ module Gargantext.Components.Nodes.Corpus.Chart.Common where
import Gargantext.Prelude
import Data.Array as A
import Data.Either (Either)
import Data.Tuple.Nested ((/\))
import Effect.Aff (Aff)
import Gargantext.Components.Nodes.Corpus.Chart.Types (MetricsProps, ReloadPath)
import Gargantext.Config.REST (RESTError)
import Gargantext.Config.REST (AffRESTError)
import Gargantext.Hooks.Loader (HashedResponse, useLoader, useLoaderWithCacheAPI)
import Gargantext.Sessions (Session)
import Gargantext.Types (FrontendError(..))
......@@ -22,7 +20,7 @@ here :: R2.Here
here = R2.here "Gargantext.Components.Nodes.Corpus.Chart.Common"
type MetricsLoadViewProps a = (
getMetrics :: Session -> ReloadPath -> Aff (Either RESTError a)
getMetrics :: Session -> ReloadPath -> AffRESTError a
, loaded :: Record MetricsProps -> a -> R.Element
| MetricsProps
)
......@@ -55,7 +53,7 @@ metricsLoadViewCpt = here.component "metricsLoadView" cpt
here.log2 "RESTError" error
type MetricsWithCacheLoadViewProps res ret =
( getMetricsHash :: Session -> ReloadPath -> Aff (Either RESTError Hash)
( getMetricsHash :: Session -> ReloadPath -> AffRESTError Hash
, handleResponse :: HashedResponse res -> ret
, loaded :: Record MetricsProps -> ret -> R.Element
, mkRequest :: ReloadPath -> GUC.Request
......
module Gargantext.Components.Nodes.Corpus.Chart.Histo where
import Data.Either (Either)
import Data.Eq.Generic (genericEq)
import Data.Generic.Rep (class Generic)
import Data.Maybe (Maybe(..))
import Data.Newtype (class Newtype)
import Data.Tuple.Nested ((/\))
import Effect.Aff (Aff)
import Reactix as R
import Reactix.DOM.HTML as H
import Simple.JSON as JSON
import Toestand as T
import Gargantext.Components.Charts.Options.Color (grey, blue)
import Gargantext.Components.Charts.Options.Data (dataSerie)
import Gargantext.Components.Charts.Options.ECharts (Options(..), chart, xAxis', yAxis')
......@@ -19,7 +12,7 @@ import Gargantext.Components.Charts.Options.Font (itemStyle, mkTooltip, template
import Gargantext.Components.Charts.Options.Series (seriesBarD1)
import Gargantext.Components.Nodes.Corpus.Chart.Common (metricsWithCacheLoadView)
import Gargantext.Components.Nodes.Corpus.Chart.Types (MetricsProps, Path, Props, ReloadPath)
import Gargantext.Config.REST (RESTError)
import Gargantext.Config.REST (AffRESTError)
import Gargantext.Hooks.Loader (HashedResponse(..))
import Gargantext.Prelude (class Eq, bind, map, pure, ($), (==))
import Gargantext.Routes (SessionRoute(..))
......@@ -28,6 +21,10 @@ import Gargantext.Types (ChartType(..))
import Gargantext.Utils.CacheAPI as GUC
import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Toestand as T2
import Reactix as R
import Reactix.DOM.HTML as H
import Simple.JSON as JSON
import Toestand as T
here :: R2.Here
here = R2.here "Gargantext.Components.Nodes.Corpus.Chart.Histo"
......@@ -76,7 +73,7 @@ chartOptions { onClick, onInit } (HistoMetrics { dates: dates', count: count'})
map mapSeriesBar count'
]
getMetricsHash :: Session -> ReloadPath -> Aff (Either RESTError String)
getMetricsHash :: Session -> ReloadPath -> AffRESTError String
getMetricsHash session (_ /\ { corpusId, listId, tabType }) = do
get session $ ChartHash { chartType: Histo, listId: mListId, tabType } (Just corpusId)
where
......
module Gargantext.Components.Nodes.Corpus.Chart.Metrics where
import Data.Generic.Rep (class Generic)
import Data.Either (Either)
import Data.Eq.Generic (genericEq)
import Data.Map as Map
import Data.Generic.Rep (class Generic)
import Data.Map (Map)
import Data.Map as Map
import Data.Maybe (Maybe(..))
import Data.Newtype (class Newtype)
import Data.Tuple (Tuple(..))
import Data.Tuple.Nested ((/\))
import Effect.Aff (Aff)
import Reactix as R
import Reactix.DOM.HTML as H
import Simple.JSON as JSON
import Toestand as T
import Gargantext.Prelude (class Eq, bind, negate, pure, ($), (<$>), (<>))
import Gargantext.Components.Charts.Options.ECharts (Options(..), chart, yAxis')
import Gargantext.Components.Charts.Options.Type (xAxis)
import Gargantext.Components.Charts.Options.Series (Series, seriesScatterD2)
import Gargantext.Components.Charts.Options.Color (green, grey, red)
import Gargantext.Components.Charts.Options.Font (itemStyle, mkTooltip, templateFormatter)
import Gargantext.Components.Charts.Options.Data (dataSerie)
import Gargantext.Components.Charts.Options.ECharts (Options(..), chart, yAxis')
import Gargantext.Components.Charts.Options.Font (itemStyle, mkTooltip, templateFormatter)
import Gargantext.Components.Charts.Options.Series (Series, seriesScatterD2)
import Gargantext.Components.Charts.Options.Type (xAxis)
import Gargantext.Components.Nodes.Corpus.Chart.Common (metricsWithCacheLoadView)
import Gargantext.Components.Nodes.Corpus.Chart.Types
(MetricsProps, Path, Props, ReloadPath)
import Gargantext.Config.REST (RESTError)
import Gargantext.Components.Nodes.Corpus.Chart.Types (MetricsProps, Path, Props, ReloadPath)
import Gargantext.Config.REST (AffRESTError)
import Gargantext.Hooks.Loader (HashedResponse(..))
import Gargantext.Prelude (class Eq, bind, negate, pure, ($), (<$>), (<>))
import Gargantext.Routes (SessionRoute(..))
import Gargantext.Sessions (Session, get)
import Gargantext.Types (TermList(..))
import Gargantext.Utils.CacheAPI as GUC
import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Toestand as T2
import Reactix as R
import Reactix.DOM.HTML as H
import Simple.JSON as JSON
import Toestand as T
here :: R2.Here
here = R2.here "Gargantext.Components.Nodes.Corpus.Chart.Metrics"
......@@ -95,7 +90,7 @@ scatterOptions { onClick, onInit } metrics' = Options
}
--}
getMetricsHash :: Session -> ReloadPath -> Aff (Either RESTError String)
getMetricsHash :: Session -> ReloadPath -> AffRESTError String
getMetricsHash session (_ /\ { corpusId, listId, tabType }) =
get session $ CorpusMetricsHash { listId, tabType } (Just corpusId)
......
......@@ -2,38 +2,33 @@ module Gargantext.Components.Nodes.Corpus.Chart.Pie where
import Data.Array (zip, filter)
import Data.Array as A
import Data.Generic.Rep (class Generic)
import Data.Either (Either)
import Data.Eq.Generic (genericEq)
import Data.Generic.Rep (class Generic)
import Data.Maybe (Maybe(..))
import Data.Newtype (class Newtype)
import Data.String (take, joinWith, Pattern(..), split, length)
import Data.Tuple (Tuple(..))
import Data.Tuple.Nested ((/\))
import Effect.Aff (Aff)
import Reactix as R
import Reactix.DOM.HTML as H
import Simple.JSON as JSON
import Toestand as T
import Gargantext.Prelude (class Eq, bind, map, pure, ($), (==), (>))
import Gargantext.Components.Charts.Options.Color (blue)
import Gargantext.Components.Charts.Options.Data (dataSerie)
import Gargantext.Components.Charts.Options.ECharts (Options(..), chart, xAxis', yAxis')
import Gargantext.Components.Charts.Options.Font (itemStyle, mkTooltip, templateFormatter)
import Gargantext.Components.Charts.Options.Series (seriesBarD1, seriesPieD1)
import Gargantext.Config.REST (RESTError)
import Gargantext.Components.Nodes.Corpus.Chart.Common (metricsWithCacheLoadView)
import Gargantext.Components.Nodes.Corpus.Chart.Types
(MetricsProps, Path, Props, ReloadPath)
import Gargantext.Components.Nodes.Corpus.Chart.Types (MetricsProps, Path, Props, ReloadPath)
import Gargantext.Config.REST (AffRESTError)
import Gargantext.Hooks.Loader (HashedResponse(..))
import Gargantext.Prelude (class Eq, bind, map, pure, ($), (==), (>))
import Gargantext.Routes (SessionRoute(..))
import Gargantext.Sessions (Session, get)
import Gargantext.Types (ChartType(..))
import Gargantext.Utils.CacheAPI as GUC
import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Toestand as T2
import Reactix as R
import Reactix.DOM.HTML as H
import Simple.JSON as JSON
import Toestand as T
here :: R2.Here
here = R2.here "Gargantext.Components.Nodes.Corpus.Chart.Pie"
......@@ -84,7 +79,7 @@ chartOptionsPie { onClick, onInit } (HistoMetrics { dates: dates', count: count'
, onInit
}
getMetricsHash :: Session -> ReloadPath -> Aff (Either RESTError String)
getMetricsHash :: Session -> ReloadPath -> AffRESTError String
getMetricsHash session (_ /\ { corpusId, listId, tabType }) = do
get session $ ChartHash { chartType: ChartPie, listId: mListId, tabType } (Just corpusId)
where
......
module Gargantext.Components.Nodes.Corpus.Chart.Tree where
import Data.Either (Either)
import Gargantext.Prelude
import Data.Generic.Rep (class Generic)
import Data.Maybe (Maybe(..))
import Data.Newtype (class Newtype)
import Data.Tuple.Nested ((/\))
import Effect.Aff (Aff)
import Reactix as R
import Reactix.DOM.HTML as H
import Simple.JSON as JSON
import Toestand as T
import Gargantext.Prelude
import Gargantext.Components.Charts.Options.ECharts (Options(..), chart, xAxis', yAxis')
import Gargantext.Components.Charts.Options.Series (TreeNode, Trees(..), mkTree)
import Gargantext.Components.Charts.Options.Font (mkTooltip, templateFormatter)
import Gargantext.Components.Charts.Options.Series (TreeNode, Trees(..), mkTree)
import Gargantext.Components.Nodes.Corpus.Chart.Common (metricsWithCacheLoadView)
import Gargantext.Components.Nodes.Corpus.Chart.Types (MetricsProps, Path, Props, ReloadPath)
import Gargantext.Config.REST (RESTError)
import Gargantext.Config.REST (AffRESTError)
import Gargantext.Hooks.Loader (HashedResponse(..))
import Gargantext.Routes (SessionRoute(..))
import Gargantext.Sessions (Session, get)
......@@ -26,6 +19,10 @@ import Gargantext.Types (ChartType(..))
import Gargantext.Utils.CacheAPI as GUC
import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Toestand as T2
import Reactix as R
import Reactix.DOM.HTML as H
import Simple.JSON as JSON
import Toestand as T
here :: R2.Here
here = R2.here "Gargantext.Components.Nodes.Corpus.Chart.Tree"
......@@ -56,7 +53,7 @@ scatterOptions { onClick, onInit } nodes = Options
}
getMetricsHash :: Session -> ReloadPath -> Aff (Either RESTError String)
getMetricsHash :: Session -> ReloadPath -> AffRESTError String
getMetricsHash session (_ /\ { corpusId, listId, tabType }) = do
get session $ ChartHash { chartType: ChartTree, listId: mListId, tabType } (Just corpusId)
where
......
......@@ -2,14 +2,13 @@ module Gargantext.Components.Nodes.Corpus.Document where
import Data.Either (Either(..))
import Data.Maybe (Maybe(..), fromMaybe)
import Effect.Aff (Aff)
import Gargantext.Components.Annotation.AnnotatedField as AnnotatedField
import Gargantext.Components.AutoUpdate (autoUpdate)
import Gargantext.Components.NgramsTable.Core (CoreAction(..), Versioned(..), addNewNgramA, applyNgramsPatches, coreDispatch, loadNgramsTable, replace, setTermListA, syncResetButtons, findNgramRoot)
import Gargantext.Components.Node (NodePoly(..))
import Gargantext.Components.Nodes.Corpus.Document.Types (DocPath, Document(..), LoadedData, NodeDocument, Props, State, initialState)
import Gargantext.Components.Search (SearchType(..))
import Gargantext.Config.REST (RESTError, logRESTError)
import Gargantext.Config.REST (AffRESTError, logRESTError)
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Prelude (bind, pure, show, unit, ($), (<>), (<$>), (<<<))
import Gargantext.Routes (SessionRoute(..))
......@@ -155,10 +154,10 @@ documentLayoutWithKeyCpt = here.component "documentLayoutWithKey" cpt
------------------------------------------------------------------------
loadDocument :: Session -> Int -> Aff (Either RESTError NodeDocument)
loadDocument :: Session -> Int -> AffRESTError NodeDocument
loadDocument session nodeId = get session $ NodeAPI Node (Just nodeId) ""
loadData :: DocPath -> Aff (Either RESTError LoadedData)
loadData :: DocPath -> AffRESTError LoadedData
loadData { listIds, nodeId, session, tabType } = do
eDocument <- loadDocument session nodeId
case eDocument of
......
......@@ -2,15 +2,13 @@ module Gargantext.Components.Nodes.Dashboard.Types where
import Gargantext.Prelude
import Data.Either (Either)
import Data.Eq.Generic (genericEq)
import Data.Generic.Rep (class Generic)
import Data.Maybe (Maybe(..))
import Data.Newtype (class Newtype)
import Effect.Aff (Aff)
import Gargantext.Components.Nodes.Corpus.Chart.Predefined as P
import Gargantext.Components.Nodes.Types (FTFieldList)
import Gargantext.Config.REST (RESTError)
import Gargantext.Config.REST (AffRESTError)
import Gargantext.Routes (SessionRoute(NodeAPI))
import Gargantext.Sessions (Session, get, put)
import Gargantext.Types (NodeType(..))
......@@ -40,16 +38,16 @@ instance Eq Hyperdata where
type LoadProps = ( nodeId :: Int, session :: Session )
loadDashboard' :: Record LoadProps -> Aff (Either RESTError DashboardData)
loadDashboard' :: Record LoadProps -> AffRESTError DashboardData
loadDashboard' {nodeId, session} = get session $ NodeAPI Node (Just nodeId) ""
-- Just to make reloading effective
loadDashboardWithReload :: {reload :: Int | LoadProps} -> Aff (Either RESTError DashboardData)
loadDashboardWithReload :: {reload :: Int | LoadProps} -> AffRESTError DashboardData
loadDashboardWithReload {nodeId, session} = loadDashboard' {nodeId, session}
type SaveProps = ( hyperdata :: Hyperdata | LoadProps )
saveDashboard :: Record SaveProps -> Aff (Either RESTError Int)
saveDashboard :: Record SaveProps -> AffRESTError Int
saveDashboard {hyperdata, nodeId, session} = do
put session (NodeAPI Node (Just nodeId) "") hyperdata
......
......@@ -2,13 +2,11 @@ module Gargantext.Components.Nodes.File where
import Gargantext.Prelude
import Data.Either (Either)
import Data.Eq.Generic (genericEq)
import Data.Generic.Rep (class Generic)
import Data.Maybe (Maybe(..))
import Data.Newtype (class Newtype)
import Effect.Aff (Aff)
import Gargantext.Config.REST (RESTError, logRESTError)
import Gargantext.Config.REST (AffRESTError, logRESTError)
import Gargantext.Ends (toUrl)
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Routes (SessionRoute(..))
......@@ -62,7 +60,7 @@ fileLayoutCpt = here.component "fileLayout" cpt where
errorHandler = logRESTError here "[fileLayout]"
onLoad loaded = fileLayoutLoaded { loaded, nodeId, session }
loadFile :: Session -> NodeID -> Aff (Either RESTError File)
loadFile :: Session -> NodeID -> AffRESTError File
loadFile session nodeId = get session $ NodeAPI Node (Just nodeId) ""
type FileLayoutLoadedProps =
......
......@@ -3,21 +3,26 @@ module Gargantext.Components.Nodes.Frame where
import Gargantext.Prelude
import DOM.Simple as DOM
import Data.Either (Either)
import Data.Array as A
import Data.Either (Either(..))
import Data.Eq.Generic (genericEq)
import Data.Generic.Rep (class Generic)
import Data.Maybe (Maybe(..))
import Data.Newtype (class Newtype)
import Data.Nullable (Nullable, null, toMaybe)
import Data.Show.Generic (genericShow)
import Effect.Aff (Aff)
import Data.Tuple (Tuple(..))
import Effect.Aff (launchAff_)
import Effect.Class (liftEffect)
import Gargantext.Components.FolderView as FV
import Gargantext.Components.Forest.Tree.Node.Action.Upload.Types (FileType(..))
import Gargantext.Components.GraphQL.Endpoints (getNodeParent)
import Gargantext.Components.Node (NodePoly(..))
import Gargantext.Config.REST (RESTError, logRESTError)
import Gargantext.Config.REST (RESTError, AffRESTError, logRESTError)
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Routes (SessionRoute(NodeAPI))
import Gargantext.Routes as GR
import Gargantext.Sessions (Session, get, sessionId)
import Gargantext.Sessions (Session, get, postWwwUrlencoded, sessionId)
import Gargantext.Types (NodeType(..))
import Gargantext.Types as GT
import Gargantext.Utils.EtherCalc as EC
......@@ -79,8 +84,8 @@ type ViewProps =
( frame :: NodePoly Hyperdata
, reload :: T2.ReloadS
, nodeId :: Int
, session :: Session
, nodeType :: NodeType
, session :: Session
)
type Base = String
......@@ -101,7 +106,8 @@ frameLayoutViewCpt = here.component "frameLayoutView" cpt
cpt { frame: NodePoly { hyperdata: h@(Hyperdata { base, frame_id }) }
, nodeId
, nodeType
, reload } _ = do
, reload
, session } _ = do
case nodeType of
NodeFrameVisio ->
case WURL.fromAbsolute base of
......@@ -110,7 +116,7 @@ frameLayoutViewCpt = here.component "frameLayoutView" cpt
_ ->
pure $ H.div{}
[ FV.backButton {} []
, importIntoListButton { hyperdata: h, nodeId } []
, importIntoListButton { hyperdata: h, nodeId, session } []
, H.div { className : "frame"
, rows: "100%,*" }
[ -- H.script { src: "https://visio.gargantext.org/external_api.js"} [],
......@@ -123,14 +129,16 @@ frameLayoutViewCpt = here.component "frameLayoutView" cpt
type ImportIntoListButtonProps =
( hyperdata :: Hyperdata
, nodeId :: Int )
, nodeId :: Int
, session :: Session )
importIntoListButton :: R2.Component ImportIntoListButtonProps
importIntoListButton = R.createElement importIntoListButtonCpt
importIntoListButtonCpt :: R.Component ImportIntoListButtonProps
importIntoListButtonCpt = here.component "importIntoListButton" cpt where
cpt { hyperdata: Hyperdata { base, frame_id }
, nodeId } _ = do
, nodeId
, session } _ = do
pure $ H.div { className: "btn btn-default"
, on: { click: onClick } }
[ H.text $ "Import into list" ]
......@@ -138,11 +146,25 @@ importIntoListButtonCpt = here.component "importIntoListButton" cpt where
onClick _ = do
let url = base <> "/" <> frame_id
--task = GT.AsyncTaskWithType { task, typ: GT.ListCSVUpload }
uploadPath = GR.NodeAPI NodeList (Just id) $ GT.asyncTaskTypePath GT.ListCSVUpload
csv <- EC.downloadCSV base frame_id
here.log2 "[importIntoListButton] CSV: " csv
--eTask <- postWwwUrlencoded session uploadPath body
pure unit
launchAff_ $ do
-- Get corpus_id
corpusNodes <- getNodeParent session nodeId Corpus
case A.uncons corpusNodes of
Nothing -> liftEffect $ here.log2 "[importIntoListButton] corpusNodes empty" corpusNodes
Just { head: corpusNode } -> do
-- Use that corpus id
eCsv <- EC.downloadCSV base frame_id
case eCsv of
Left err -> liftEffect $ here.log2 "[importIntoListButton] error with csv" err
Right csv -> do
let uploadPath = GR.NodeAPI NodeList (Just corpusNode.id) $ GT.asyncTaskTypePath GT.ListCSVUpload
eTask :: Either RESTError GT.AsyncTaskWithType <- postWwwUrlencoded
session
uploadPath
[ Tuple "_wf_data" (Just csv.body)
, Tuple "_wf_filetype" (Just $ show CSV)
, Tuple "_wf_name" (Just frame_id) ]
pure unit
type NodeFrameVisioProps =
( frame_id :: String
......@@ -177,9 +199,9 @@ type ReloadProps = ( nodeId :: Int
, reload :: T2.Reload
, session :: Session )
loadframe' :: Record LoadProps -> Aff (Either RESTError (NodePoly Hyperdata))
loadframe' :: Record LoadProps -> AffRESTError (NodePoly Hyperdata)
loadframe' { nodeId, session } = get session $ NodeAPI Node (Just nodeId) ""
-- Just to make reloading effective
loadframeWithReload :: Record ReloadProps -> Aff (Either RESTError (NodePoly Hyperdata))
loadframeWithReload :: Record ReloadProps -> AffRESTError (NodePoly Hyperdata)
loadframeWithReload { nodeId, session } = loadframe' { nodeId, session }
......@@ -2,14 +2,12 @@ module Gargantext.Components.Nodes.Home.Public where
import Gargantext.Prelude
import Data.Either (Either)
import Data.Generic.Rep (class Generic)
import Data.Maybe (Maybe(..))
import Data.Show.Generic (genericShow)
import Data.String (take)
import Effect.Aff (Aff)
import Gargantext.Config (publicBackend)
import Gargantext.Config.REST (RESTError, get, logRESTError)
import Gargantext.Config.REST (AffRESTError, get, logRESTError)
import Gargantext.Ends (backendUrl)
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Utils.Reactix as R2
......@@ -45,7 +43,7 @@ type LoadData = ()
type LoadProps = (reload :: Int)
-- | WIP still finding the right way to chose the default public backend
loadPublicData :: Record LoadProps -> Aff (Either RESTError (Array PublicData))
loadPublicData :: Record LoadProps -> AffRESTError (Array PublicData)
loadPublicData _l = do
-- This solution is error prone (url needs to be cleaned)
--backend <- liftEffect public
......
module Gargantext.Components.Score where
import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, jsonEmptyObject, (.:), (:=), (~>), encodeJson)
import Data.Int (fromString)
import Data.Either (Either)
import Data.Maybe (Maybe(..), maybe)
import DOM.Simple.Console (log2)
import Effect.Aff (Aff, launchAff_)
import Effect.Class (liftEffect)
import Reactix as R
import Reactix.DOM.HTML as H
import Simple.JSON as JSON
import Gargantext.Prelude
import Gargantext.Config.REST (RESTError)
import Data.Int (fromString)
import Data.Maybe (Maybe(..))
import Effect.Aff (launchAff_)
import Effect.Class (liftEffect)
import Gargantext.Config.REST (AffRESTError)
import Gargantext.Routes (SessionRoute(NodeAPI))
import Gargantext.Sessions (Session, sessionId, get, delete, put)
import Gargantext.Sessions (Session, put)
import Gargantext.Types as GT
import Gargantext.Utils.Array as GUA
import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Toestand as GUT
import Reactix as R
import Reactix.DOM.HTML as H
import Simple.JSON as JSON
type Score = Int
type DocID = Int
......@@ -79,7 +75,7 @@ instance JSON.WriteForeign ScoreQuery where
writeImpl (ScoreQuery post) = JSON.writeImpl { nts_nodesId: post.nodeIds
, nts_score: post.score }
putScore :: Session -> GT.NodeID -> ScoreQuery -> Aff (Either RESTError (Array Int))
putScore :: Session -> GT.NodeID -> ScoreQuery -> AffRESTError (Array Int)
putScore session nodeId = put session $ scoreRoute nodeId
where
scoreRoute :: GT.NodeID -> SessionRoute
......
......@@ -73,7 +73,7 @@ readJSON affResp =
-- TODO too much duplicate code in `postWwwUrlencoded`
send :: forall body res. JSON.WriteForeign body => JSON.ReadForeign res =>
Method -> Maybe Token -> String -> Maybe body -> Aff (Either RESTError res)
Method -> Maybe Token -> String -> Maybe body -> AffRESTError res
send m mtoken url reqbody = do
let req = defaultRequest
{ url = url
......@@ -99,30 +99,30 @@ noReqBody :: Maybe String
noReqBody = Just ""
--noReqBody = Nothing
get :: forall a. JSON.ReadForeign a => Maybe Token -> String -> Aff (Either RESTError a)
get :: forall a. JSON.ReadForeign a => Maybe Token -> String -> AffRESTError a
get mtoken url = send GET mtoken url noReqBody
put :: forall a b. JSON.WriteForeign a => JSON.ReadForeign b => Maybe Token -> String -> a -> Aff (Either RESTError b)
put :: forall a b. JSON.WriteForeign a => JSON.ReadForeign b => Maybe Token -> String -> a -> AffRESTError b
put mtoken url = send PUT mtoken url <<< Just
put_ :: forall a. JSON.ReadForeign a => Maybe Token -> String -> Aff (Either RESTError a)
put_ :: forall a. JSON.ReadForeign a => Maybe Token -> String -> AffRESTError a
put_ mtoken url = send PUT mtoken url noReqBody
delete :: forall a. JSON.ReadForeign a => Maybe Token -> String -> Aff (Either RESTError a)
delete :: forall a. JSON.ReadForeign a => Maybe Token -> String -> AffRESTError a
delete mtoken url = send DELETE mtoken url noReqBody
-- This might not be a good idea:
-- https://stackoverflow.com/questions/14323716/restful-alternatives-to-delete-request-body
deleteWithBody :: forall a b. JSON.WriteForeign a => JSON.ReadForeign b => Maybe Token -> String -> a -> Aff (Either RESTError b)
deleteWithBody :: forall a b. JSON.WriteForeign a => JSON.ReadForeign b => Maybe Token -> String -> a -> AffRESTError b
deleteWithBody mtoken url = send DELETE mtoken url <<< Just
post :: forall a b. JSON.WriteForeign a => JSON.ReadForeign b => Maybe Token -> String -> a -> Aff (Either RESTError b)
post :: forall a b. JSON.WriteForeign a => JSON.ReadForeign b => Maybe Token -> String -> a -> AffRESTError b
post mtoken url = send POST mtoken url <<< Just
type FormDataParams = Array (Tuple String (Maybe String))
-- TODO too much duplicate code with `send`
postWwwUrlencoded :: forall b. JSON.ReadForeign b => Maybe Token -> String -> FormDataParams -> Aff (Either RESTError b)
postWwwUrlencoded :: forall b. JSON.ReadForeign b => Maybe Token -> String -> FormDataParams -> AffRESTError b
postWwwUrlencoded mtoken url bodyParams = do
affResp <- request $ defaultRequest
{ url = url
......@@ -140,7 +140,7 @@ postWwwUrlencoded mtoken url bodyParams = do
where
urlEncodedBody = FormURLEncoded.fromArray bodyParams
postMultipartFormData :: forall b. JSON.ReadForeign b => Maybe Token -> String -> String -> Aff (Either RESTError b)
postMultipartFormData :: forall b. JSON.ReadForeign b => Maybe Token -> String -> String -> AffRESTError b
postMultipartFormData mtoken url body = do
fd <- liftEffect $ XHRFormData.new
_ <- liftEffect $ XHRFormData.append (XHRFormData.EntryName "body") body fd
......
......@@ -13,7 +13,7 @@ import Effect.Class (liftEffect)
import Effect.Exception (error)
import Gargantext.Components.App.Data (Boxes)
import Gargantext.Components.LoadingSpinner (loadingSpinner)
import Gargantext.Config.REST (RESTError)
import Gargantext.Config.REST (RESTError, AffRESTError)
import Gargantext.Config.Utils (handleRESTError)
import Gargantext.Types (FrontendError(..))
import Gargantext.Utils.CacheAPI as GUC
......@@ -34,7 +34,7 @@ clearCache _ = GUC.delete $ GUC.CacheName cacheName
type UseLoader path state =
( errorHandler :: RESTError -> Effect Unit
, loader :: path -> Aff (Either RESTError state)
, loader :: path -> AffRESTError state
, path :: path
, render :: state -> R.Element
)
......@@ -66,7 +66,7 @@ loaderCpt = here.component "loader" cpt
type UseLoaderEffect path state =
( errorHandler :: RESTError -> Effect Unit
, loader :: path -> Aff (Either RESTError state)
, loader :: path -> AffRESTError state
, path :: path
, state :: T.Box (Maybe state)
)
......@@ -93,7 +93,7 @@ useLoaderEffect { errorHandler, loader: loader', path, state } = do
type UseLoaderBox path state =
( errorHandler :: RESTError -> Effect Unit
, loader :: path -> Aff (Either RESTError state)
, loader :: path -> AffRESTError state
, path :: T.Box path
, render :: state -> R.Element
)
......@@ -110,7 +110,7 @@ useLoaderBox { errorHandler, loader: loader', path, render } = do
type UseLoaderBoxEffect path state =
( errorHandler :: RESTError -> Effect Unit
, loader :: path -> Aff (Either RESTError state)
, loader :: path -> AffRESTError state
, path :: T.Box path
, state :: T.Box (Maybe state)
)
......@@ -137,7 +137,7 @@ derive newtype instance JSON.WriteForeign a => JSON.WriteForeign (HashedResponse
type LoaderWithCacheAPIProps path res ret =
( boxes :: Boxes
, cacheEndpoint :: path -> Aff (Either RESTError Hash)
, cacheEndpoint :: path -> AffRESTError Hash
, handleResponse :: HashedResponse res -> ret
, mkRequest :: path -> GUC.Request
, path :: path
......@@ -167,7 +167,7 @@ useLoaderWithCacheAPI { boxes
type LoaderWithCacheAPIEffectProps path res ret = (
boxes :: Boxes
, cacheEndpoint :: path -> Aff (Either RESTError Hash)
, cacheEndpoint :: path -> AffRESTError Hash
, handleResponse :: HashedResponse res -> ret
, mkRequest :: path -> GUC.Request
, path :: path
......
......@@ -122,30 +122,30 @@ postAuthRequest backend ar@(AuthRequest {username}) =
| otherwise = Left "Invalid response from server"
get :: forall a p. JSON.ReadForeign a => ToUrl Session p =>
Session -> p -> Aff (Either REST.RESTError a)
Session -> p -> REST.AffRESTError a
get session@(Session {token}) p = REST.get (Just token) (toUrl session p)
put :: forall a b p. JSON.WriteForeign a => JSON.ReadForeign b => ToUrl Session p =>
Session -> p -> a -> Aff (Either REST.RESTError b)
Session -> p -> a -> REST.AffRESTError b
put session@(Session {token}) p = REST.put (Just token) (toUrl session p)
put_ :: forall b p. JSON.ReadForeign b => ToUrl Session p => Session -> p -> Aff (Either REST.RESTError b)
put_ :: forall b p. JSON.ReadForeign b => ToUrl Session p => Session -> p -> REST.AffRESTError b
put_ session@(Session {token}) p = REST.put_ (Just token) (toUrl session p)
delete :: forall a p. JSON.ReadForeign a => ToUrl Session p =>
Session -> p -> Aff (Either REST.RESTError a)
Session -> p -> REST.AffRESTError a
delete session@(Session {token}) p = REST.delete (Just token) (toUrl session p)
-- This might not be a good idea:
-- https://stackoverflow.com/questions/14323716/restful-alternatives-to-delete-request-body
deleteWithBody :: forall a b p. JSON.WriteForeign a => JSON.ReadForeign b => ToUrl Session p =>
Session -> p -> a -> Aff (Either REST.RESTError b)
Session -> p -> a -> REST.AffRESTError b
deleteWithBody session@(Session {token}) p = REST.deleteWithBody (Just token) (toUrl session p)
post :: forall a b p. JSON.WriteForeign a => JSON.ReadForeign b => ToUrl Session p =>
Session -> p -> a -> Aff (Either REST.RESTError b)
Session -> p -> a -> REST.AffRESTError b
post session@(Session {token}) p = REST.post (Just token) (toUrl session p)
postWwwUrlencoded :: forall b p. JSON.ReadForeign b => ToUrl Session p =>
Session -> p -> REST.FormDataParams -> Aff (Either REST.RESTError b)
Session -> p -> REST.FormDataParams -> REST.AffRESTError b
postWwwUrlencoded session@(Session {token}) p = REST.postWwwUrlencoded (Just token) (toUrl session p)
......@@ -3,7 +3,6 @@ module Gargantext.Types where
import Gargantext.Prelude
import Data.Array as A
import Data.Either (Either)
import Data.Eq.Generic (genericEq)
import Data.Generic.Rep (class Generic)
import Data.Int (toNumber)
......@@ -15,8 +14,10 @@ import Data.String as S
import Effect.Aff (Aff)
import Foreign as F
import Gargantext.Components.Lang (class Translate, Lang(..))
import Gargantext.Config.REST (RESTError)
import Gargantext.Config.REST (RESTError, AffRESTError)
import Gargantext.Utils.Glyphicon (classNamePrefix, glyphiconToCharCode)
import GraphQL.Client.Args (class ArgGql)
import GraphQL.Client.Variables.TypeName (class VarTypeName)
import Prim.Row (class Union)
import Reactix as R
import Simple.JSON as JSON
......@@ -167,6 +168,9 @@ instance JSON.ReadForeign NodeType where
Nothing -> F.fail $ F.ErrorAtProperty s $ F.ForeignError "unknown property"
Just nt -> pure nt
instance JSON.WriteForeign NodeType where writeImpl = JSON.writeImpl <<< show
instance ArgGql NodeType NodeType
instance VarTypeName NodeType where
varTypeName _ = "NodeType!"
instance Show NodeType where
show NodeUser = "NodeUser"
......@@ -624,7 +628,7 @@ instance DecodeJson TabType where
type TableResult a = {count :: Int, docs :: Array a}
type AffTableResult a = Aff (TableResult a)
type AffETableResult a = Aff (Either RESTError (TableResult a))
type AffETableResult a = AffRESTError (TableResult a)
data Mode = Authors
| Sources
......
......@@ -5,7 +5,7 @@ import Prelude
import DOM.Simple.Console (log2)
import Data.Either (Either(..))
import Data.Maybe (Maybe(..))
import Effect.Aff (Aff, launchAff_)
import Effect.Aff (launchAff_)
import Effect.Class (liftEffect)
import Reactix as R
import Reactix.DOM.HTML as H
......@@ -24,7 +24,7 @@ type Version = String
foreign import version :: Version
getBackendVersion :: Session -> Aff (Either REST.RESTError Version)
getBackendVersion :: Session -> REST.AffRESTError Version
getBackendVersion (Session { backend }) = REST.get Nothing (toUrl backend "version")
......
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