Commit 402c5110 authored by arturo's avatar arturo

>>> continue

parent ac47c858
Pipeline #2720 failed with stage
in 0 seconds
......@@ -30,10 +30,11 @@ 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 (AffRESTError, logRESTError)
import Gargantext.Config.REST (AffRESTError, logRESTError')
import Gargantext.Config.Utils (handleRESTError)
import Gargantext.Ends (Frontends)
import Gargantext.Hooks.Loader (useLoaderEffect)
import Gargantext.Plugins.Core.Console as C
import Gargantext.Routes as GR
import Gargantext.Sessions (Session, get, mkNodeId)
import Gargantext.Sessions.Types (useOpenNodesMemberBox, openNodesInsert, openNodesDelete)
......@@ -51,8 +52,8 @@ import Toestand as T
moduleName :: R2.Module
moduleName = "Gargantext.Components.Forest.Tree"
here :: R2.Here
here = R2.here moduleName
console :: C.Console
console = C.encloseContext C.Component "Forest.Tree"
-- Shared by every component here
type Common =
......@@ -146,7 +147,7 @@ treeLoader = B.leaf (moduleName <> "treeLoader") cpt where
props = Record.merge common extra where
common = RecordE.pick p :: Record Common
extra = { reloadTree: p.reload, root, session, tree: tree' }
errorHandler = logRESTError here "[treeLoader]"
errorHandler = logRESTError' console "[treeLoader]"
---------------------------------------------------
......@@ -279,7 +280,7 @@ childLoader = B.leaf (moduleName <> "childLoader") cpt where
}
where
errorHandler = logRESTError here "[childLoader]"
errorHandler = logRESTError' console "[childLoader]"
fetch _ = getNodeTreeFirstLevel p.session p.id
paint reload tree' = render (Record.merge base extra) where
base = nodeProps { reload = reload }
......@@ -309,13 +310,13 @@ deleteNode' nt p@{ boxes: { forestOpen }, session, tree: (NTree (LNode {id, pare
doSearch task { boxes: { tasks }, tree: NTree (LNode {id}) _ } = liftEffect $ do
GAT.insert id task tasks
here.log2 "[doSearch] DoSearch task:" task
console.log2 "[doSearch] DoSearch task:" task
updateNode params { boxes: { errors, tasks }, session, tree: (NTree (LNode {id}) _) } = do
eTask <- updateRequest params session id
handleRESTError errors eTask $ \task -> liftEffect $ do
GAT.insert id task tasks
here.log2 "[updateNode] UpdateNode task:" task
console.log2 "[updateNode] UpdateNode task:" task
renameNode name p@{ boxes: { errors }, session, tree: (NTree (LNode {id}) _) } = do
eTask <- rename session id $ RenameValue { text: name }
......@@ -347,19 +348,19 @@ uploadFile' nodeType fileType fileFormat mName contents p@{ boxes: { errors, tas
eTask <- uploadFile { contents, fileFormat, fileType, id, mName, nodeType, selection, session }
handleRESTError errors eTask $ \task -> liftEffect $ do
GAT.insert id task tasks
here.log2 "[uploadFile'] UploadFile, uploaded, task:" task
console.log2 "[uploadFile'] UploadFile, uploaded, task:" task
uploadArbitraryFile' fileFormat mName blob p@{ boxes: { errors, tasks }, session, tree: (NTree (LNode { id }) _) } selection = do
eTask <- uploadArbitraryFile session id { blob, fileFormat, mName } selection
handleRESTError errors eTask $ \task -> liftEffect $ do
GAT.insert id task tasks
here.log2 "[uploadArbitraryFile'] UploadArbitraryFile, uploaded, task:" task
console.log2 "[uploadArbitraryFile'] UploadArbitraryFile, uploaded, task:" task
uploadFrameCalc' p@{ boxes: { errors, tasks }, session, tree: (NTree (LNode { id }) _) } = do
eTask <- uploadFrameCalc session id
handleRESTError errors eTask $ \task -> liftEffect $ do
GAT.insert id task tasks
here.log2 "[performAction] UploadFrameCalc, uploaded, task:" task
console.log2 "[performAction] UploadFrameCalc, uploaded, task:" task
moveNode params p@{ boxes: { errors, forestOpen }, session } = traverse_ f params where
f (SubTreeOut { in: in', out }) = do
......@@ -401,11 +402,11 @@ performAction (UploadFile nodeType fileType fileFormat mName contents selection)
uploadFile' nodeType fileType fileFormat mName contents p selection
performAction (UploadArbitraryFile fileFormat mName blob selection) p =
uploadArbitraryFile' fileFormat mName blob p selection
performAction DownloadNode _ = liftEffect $ here.log "[performAction] DownloadNode"
performAction DownloadNode _ = liftEffect $ console.log "[performAction] DownloadNode"
performAction (MoveNode {params}) p = moveNode params p
performAction (MergeNode {params}) p = mergeNode params p
performAction (LinkNode { nodeType, params }) p = linkNode nodeType params p
performAction RefreshTree p = refreshTree p
performAction ClosePopover p = closePopover p
performAction (DocumentsFromWriteNodes { id }) p = documentsFromWriteNodes id p
performAction NoAction _ = liftEffect $ here.log "[performAction] NoAction"
performAction NoAction _ = liftEffect $ console.log "[performAction] NoAction"
......@@ -5,6 +5,7 @@ module Gargantext.Components.Forest.Tree.Node
import Gargantext.Prelude
import DOM.Simple.Console (log)
import Data.Array.NonEmpty as NArray
import Data.Foldable (intercalate)
import Data.Maybe (Maybe(..), maybe)
......@@ -28,12 +29,13 @@ import Gargantext.Components.Forest.Tree.Node.Tools.Sync (nodeActionsGraph, node
import Gargantext.Components.GraphExplorer.API as GraphAPI
import Gargantext.Components.Lang (Lang(EN))
import Gargantext.Components.Nodes.Corpus (loadCorpusWithChild)
import Gargantext.Config.REST (logRESTError)
import Gargantext.Config.REST (logRESTError')
import Gargantext.Context.Progress (asyncContext, asyncProgress)
import Gargantext.Ends (Frontends, url)
import Gargantext.Hooks.FirstEffect (useFirstEffect')
import Gargantext.Hooks.Loader (useLoaderEffect)
import Gargantext.Hooks.Version (Version, useVersion)
import Gargantext.Plugins.Core.Console as C
import Gargantext.Routes as Routes
import Gargantext.Sessions (Session, sessionId)
import Gargantext.Types (ID, Name)
......@@ -54,8 +56,8 @@ foreign import nodeUserRegexp :: Regex.Regex
moduleName :: R2.Module
moduleName = "Gargantext.Components.Forest.Tree.Node"
here :: R2.Here
here = R2.here moduleName
console :: C.Console
console = C.encloseContext C.Component "Forest.Tree.Node"
-- Main Node
type MainLeafProps =
......@@ -171,20 +173,20 @@ mainLeaf = B.leaf (moduleName <> "mainLeaf") cpt where
onTaskFinish id' t _ = do
GAT.finish id' t tasks
if GAT.asyncTaskTTriggersAppReload t then do
here.log2 "reloading root for task" t
console.log2 "reloading root for task" t
T2.reload reloadRoot
else do
if GAT.asyncTaskTTriggersTreeReload t then do
here.log2 "reloading tree for task" t
console.log2 "reloading tree for task" t
T2.reload reload
else do
here.log2 "task doesn't trigger a tree reload" t
console.log2 "task doesn't trigger a tree reload" t
pure unit
if GAT.asyncTaskTTriggersMainPageReload t then do
here.log2 "reloading main page for task" t
console.log2 "reloading main page for task" t
T2.reload reloadMainPage
else do
here.log2 "task doesn't trigger a main page reload" t
console.log2 "task doesn't trigger a main page reload" t
pure unit
-- snd tasks $ GAT.Finish id' t
-- mT <- T.read tasks
......@@ -527,18 +529,31 @@ type NodeActionsProps = ( nodeType :: GT.NodeType | NodeActionsCommon )
nodeActions :: B.Tree NodeActionsProps
nodeActions = B.tree (moduleName <> "nodeActions") cpt where
cpt props _ = pure (child props.nodeType)
where
nodeActionsP = SProxy :: SProxy "nodeType"
cpt props@{ nodeType: GT.NodeList } _ =
pure $ listNodeActions (childProps props)
cpt props@{ nodeType: GT.Graph } _ =
pure $ graphNodeActions (childProps props)
cpt _ _ =
pure $ mempty
childProps p = Record.delete nodeActionsP p
nodeActionsP = SProxy :: SProxy "nodeType"
-- cpt props _ = pure (child props.nodeType)
-- where
-- nodeActionsP = SProxy :: SProxy "nodeType"
childProps = Record.delete nodeActionsP props
-- childProps = Record.delete nodeActionsP props
child GT.NodeList = listNodeActions childProps
child GT.Graph = graphNodeActions childProps
child _ = mempty
-- child GT.NodeList = listNodeActions childProps
-- child GT.Graph = graphNodeActions childProps
-- child _ = mempty
graphNodeActions :: B.Leaf NodeActionsCommon
graphNodeActions = B.leaf (moduleName <> "graphNodeActions") cpt where
graphNodeActions = B.leaf' (moduleName <> "graphNodeActions") cpt where
cpt { id, session, refresh } _ = do
-- States
state /\ stateBox <- R2.useBox' Nothing
......@@ -559,7 +574,7 @@ graphNodeActions = B.leaf (moduleName <> "graphNodeActions") cpt where
[]
graphVersions session graphId = GraphAPI.graphVersions { graphId, session }
errorHandler = logRESTError here "[graphNodeActions]"
errorHandler = logRESTError' console "[graphNodeActions]"
listNodeActions :: B.Leaf NodeActionsCommon
......@@ -588,7 +603,7 @@ listNodeActions = B.leaf (moduleName <> "listNodeActions") cpt where
}
where
errorHandler = logRESTError here "[listNodeActions]"
errorHandler = logRESTError' console "[listNodeActions]"
-----------------------------------------------
......
This diff is collapsed.
......@@ -45,14 +45,12 @@ type Props =
, graphId :: GET.GraphId
)
here :: R2.Here
here = R2.here "Gargantext.Components.GraphExplorer.Layout"
moduleName :: R2.Module
moduleName = "Gargantext.Components.GraphExplorer.Layout"
layout :: R2.Leaf Props
layout = R2.leaf layoutCpt
layoutCpt :: R.Component Props
layoutCpt = here.component "explorerWriteGraph" cpt where
layout :: B.Leaf Props
layout = B.leaf (moduleName <> "explorerWriteGraph") cpt where
cpt props@{ boxes
, graph
, mMetaData'
......@@ -207,10 +205,8 @@ type GraphProps =
, mMetaData :: T.Box (Maybe GET.MetaData)
)
graphView :: R2.Leaf GraphProps
graphView = R2.leaf graphViewCpt
graphViewCpt :: R.Component GraphProps
graphViewCpt = here.component "graphView" cpt
graphView :: B.Leaf GraphProps
graphView = B.leaf (moduleName <> "graphView") cpt
where
cpt { boxes
, controls
......@@ -265,7 +261,7 @@ graphViewCpt = here.component "graphView" cpt
, stage: controls.graphStage
, startForceAtlas
, transformedGraph
} []
}
--------------------------------------------------------
......
......@@ -14,12 +14,14 @@ import Data.Generic.Rep (class Generic)
import Data.Maybe (Maybe(..))
import Data.Nullable (Nullable)
import Gargantext.Components.App.Data (Boxes)
import Gargantext.Components.Bootstrap as B
import Gargantext.Components.GraphExplorer.Types as GET
import Gargantext.Components.Themes (darksterTheme)
import Gargantext.Components.Themes as Themes
import Gargantext.Hooks.Sigmax as Sigmax
import Gargantext.Hooks.Sigmax.Sigma as Sigma
import Gargantext.Hooks.Sigmax.Types as SigmaxTypes
import Gargantext.Plugins.Core.Console as C
import Gargantext.Utils.Reactix as R2
import Reactix as R
import Reactix.DOM.HTML as RH
......@@ -27,8 +29,11 @@ import Record (merge)
import Record as Record
import Toestand as T
here :: R2.Here
here = R2.here "Gargantext.Components.Graph"
moduleName :: R2.Module
moduleName = "Gargantext.Components.GraphExplorer.Resources"
console :: C.Console
console = C.encloseContext C.Component "Graph"
data Stage = Init | Ready | Cleanup
......@@ -52,11 +57,8 @@ type Props sigma forceatlas2 =
, transformedGraph :: SigmaxTypes.SGraph
)
graph :: forall s fa2. R2.Component (Props s fa2)
graph = R.createElement graphCpt
graphCpt :: forall s fa2. R.Memo (Props s fa2)
graphCpt = R.memo' $ here.component "graph" cpt where
graph :: forall s fa2. B.Leaf (Props s fa2)
graph = B.leaf' (moduleName <> "graph") cpt where
cpt props@{ elRef
, showEdges
, sigmaRef
......@@ -68,12 +70,12 @@ graphCpt = R.memo' $ here.component "graph" cpt where
R.useEffectOnce $ do
pure $ do
here.log "[graphCpt (Cleanup)]"
console.log "[graphCpt (Cleanup)]"
Sigmax.dependOnSigma (R.readRef sigmaRef) "[graphCpt (Cleanup)] no sigma" $ \sigma -> do
Sigma.stopForceAtlas2 sigma
here.log2 "[graphCpt (Cleanup)] forceAtlas stopped for" sigma
console.log2 "[graphCpt (Cleanup)] forceAtlas stopped for" sigma
Sigma.kill sigma
here.log "[graphCpt (Cleanup)] sigma killed"
console.log "[graphCpt (Cleanup)] sigma killed"
-- NOTE: This div is not empty after sigma initializes.
-- When we change state, we make it empty though.
......@@ -102,7 +104,7 @@ graphCpt = R.memo' $ here.component "graph" cpt where
theme <- T.read boxes.theme
eSigma <- Sigma.sigma {settings: sigmaSettings theme}
case eSigma of
Left err -> here.log2 "[graphCpt] error creating sigma" err
Left err -> console.log2 "[graphCpt] error creating sigma" err
Right sig -> do
Sigmax.writeSigma rSigma $ Just sig
......@@ -124,7 +126,7 @@ graphCpt = R.memo' $ here.component "graph" cpt where
Sigmax.setEdges sig false
-- here.log2 "[graph] startForceAtlas" startForceAtlas
-- console.log2 "[graph] startForceAtlas" startForceAtlas
if startForceAtlas then
Sigma.startForceAtlas2 sig fa2
else
......@@ -165,7 +167,7 @@ graphCpt = R.memo' $ here.component "graph" cpt where
Sigmax.updateEdges sigma tEdgesMap
Sigmax.updateNodes sigma tNodesMap
let edgesState = not $ SigmaxTypes.edgeStateHidden showEdges'
here.log2 "[graphCpt] edgesState" edgesState
console.log2 "[graphCpt] edgesState" edgesState
Sigmax.setEdges sigma edgesState
......
module Gargantext.Components.GraphQL.Endpoints where
import Gargantext.Components.GraphQL.Node
import Gargantext.Components.GraphQL.User
import Gargantext.Components.GraphQL.Tree
import Gargantext.Components.GraphQL.User
import Gargantext.Prelude
import Data.Array as A
......@@ -15,6 +15,7 @@ import Gargantext.Components.GraphQL (getClient, queryGql)
import Gargantext.Components.GraphQL.IMT as GQLIMT
import Gargantext.Components.GraphQL.Task as GQLT
import Gargantext.Config.REST (AffRESTError, RESTError(..))
import Gargantext.Plugins.Core.Console as C
import Gargantext.Sessions (Session)
import Gargantext.Types (AsyncTaskWithType(..), AsyncTask(..), AsyncTaskType(..), NodeType)
import Gargantext.Utils.Reactix as R2
......@@ -23,14 +24,14 @@ import GraphQL.Client.Query (mutation)
import GraphQL.Client.Variables (withVars)
import Simple.JSON as JSON
here :: R2.Here
here = R2.here "Gargantext.Components.GraphQL.Endpoints"
console :: C.Console
console = C.encloseContext C.Store "GraphQL.Endpoints"
getIMTSchools :: Session -> AffRESTError (Array GQLIMT.School)
getIMTSchools session = do
{ imt_schools } <- queryGql session "get imt schools" $
GQLIMT.schoolsQuery
liftEffect $ here.log2 "[getIMTSchools] imt_schools" imt_schools
liftEffect $ console.log2 "[getIMTSchools] imt_schools" imt_schools
pure $ Right imt_schools
getNodeParent :: Session -> Int -> NodeType -> Aff (Array Node)
......@@ -38,13 +39,13 @@ 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
liftEffect $ console.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
liftEffect $ console.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
......@@ -53,6 +54,5 @@ getUserInfo session id = do
getTreeFirstLevel :: Session -> Int -> AffRESTError TreeFirstLevel
getTreeFirstLevel session id = do
{ tree } <- queryGql session "get tree first level" $ treeFirstLevelQuery `withVars` { id }
liftEffect $ here.log2 "[getTreeFirstLevel] tree first level" tree
liftEffect $ console.log2 "[getTreeFirstLevel] tree first level" tree
pure $ Right tree -- TODO: error handling
......@@ -6,18 +6,23 @@ import Data.Generic.Rep (class Generic)
import Data.Maybe (Maybe(..))
import Data.Show.Generic (genericShow)
import Data.String (take)
import Gargantext.Components.Bootstrap as B
import Gargantext.Config (publicBackend)
import Gargantext.Config.REST (AffRESTError, get, logRESTError)
import Gargantext.Config.REST (AffRESTError, get, logRESTError')
import Gargantext.Ends (backendUrl)
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Plugins.Core.Console as C
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
here :: R2.Here
here = R2.here "Gargantext.Components.Nodes.Home.Public"
moduleName :: R2.Module
moduleName = "Gargantext.Components.Nodes.Home.Public"
console :: C.Console
console = C.encloseContext C.Page "Nodes.Home.Public"
type PublicDataProps = ( publicData :: Array PublicData )
......@@ -65,10 +70,8 @@ loadPublicData _l = do
backends
-}
renderPublic :: R2.Leaf ()
renderPublic = R2.leafComponent renderPublicCpt
renderPublicCpt :: R.Component ()
renderPublicCpt = here.component "renderPublic" cpt where
renderPublic :: B.Leaf ()
renderPublic = B.leaf (moduleName <> "renderPublic") cpt where
cpt _ _ = do
useLoader { errorHandler
, loader: loadPublicData
......@@ -76,13 +79,10 @@ renderPublicCpt = here.component "renderPublic" cpt where
, render: loaded }
where
loaded publicData = publicLayout { publicData }
errorHandler = logRESTError here "[renderPublic]"
errorHandler = logRESTError' console "[renderPublic]"
publicLayout :: Record PublicDataProps -> R.Element
publicLayout props = R.createElement publicLayoutCpt props []
publicLayoutCpt :: R.Component PublicDataProps
publicLayoutCpt = here.component "publicLayout" cpt
where
publicLayout :: B.Leaf PublicDataProps
publicLayout = B.leaf (moduleName <> "publicLayout") cpt where
cpt { publicData } _ = do
pure $
H.span {}
......
module Gargantext.Config.REST where
import Gargantext.Prelude
import Affjax (Error(..), defaultRequest, request)
import Affjax as Affjax
import Affjax.RequestBody (formData, formURLEncoded, string)
......@@ -18,7 +20,7 @@ import Effect (Effect)
import Effect.Aff (Aff)
import Effect.Class (liftEffect)
import Foreign as Foreign
import Gargantext.Prelude
import Gargantext.Plugins.Core.Console as C
import Gargantext.Utils.Reactix as R2
import Simple.JSON as JSON
import Web.XHR.FormData as XHRFormData
......@@ -34,7 +36,7 @@ instance Show RESTError where
show (SendResponseError e) = "SendResponseError " <> showError e
where
showError (RequestContentError e') = "(RequestContentError " <> show e' <> ")"
showError (ResponseBodyError fe rf) = "(ResponseBodyError " <> show fe <> " (rf)" -- <> show rf <> ")"
showError (ResponseBodyError fe _) = "(ResponseBodyError " <> show fe <> " (rf)" -- <> show rf <> ")"
showError (TimeoutError) = "(TimeoutError)"
showError (RequestFailedError) = "(RequestFailedError)"
showError (XHROtherError e') = "(XHROtherError " <> show e' <> ")"
......@@ -49,6 +51,12 @@ logRESTError here prefix (SendResponseError e) = here.log2 (prefix <> " SendResp
logRESTError here prefix (ReadJSONError e) = here.log2 (prefix <> " ReadJSONError ") $ show e
logRESTError here prefix (CustomError e) = here.log2 (prefix <> " CustomError ") $ e
-- (for now just create a derived function)
logRESTError' :: C.Console -> String -> RESTError -> Effect Unit
logRESTError' console prefix (SendResponseError e) = console.log2 (prefix <> " SendResponseError ") e -- TODO: No show
logRESTError' console prefix (ReadJSONError e) = console.log2 (prefix <> " ReadJSONError ") $ show e
logRESTError' console prefix (CustomError e) = console.log2 (prefix <> " CustomError ") $ e
type AffRESTError a = Aff (Either RESTError a)
......
module Gargantext.Hooks.Sigmax
where
import Prelude
( Unit, bind, discard, flip, map, not, pure, unit
, ($), (&&), (*>), (<<<), (<>), (>>=))
import DOM.Simple.Types (Element)
import Data.Array as A
import Data.Either (either)
import Data.Foldable (sequence_, foldl)
......@@ -15,19 +13,18 @@ import Data.Sequence as Seq
import Data.Set as Set
import Data.Traversable (traverse_)
import Data.Tuple (Tuple(..))
import Data.Tuple.Nested((/\))
import DOM.Simple.Console (log, log2)
import DOM.Simple.Types (Element)
import Data.Tuple.Nested ((/\))
import Effect (Effect)
import Effect.Class.Console (error)
import Effect.Timer (TimeoutId, clearTimeout)
import FFI.Simple ((.=))
import Reactix as R
import Toestand as T
import Gargantext.Hooks.Sigmax.Sigma as Sigma
import Gargantext.Hooks.Sigmax.Types as ST
import Gargantext.Plugins.Core.Console as C
import Gargantext.Utils.Reactix as R2
import Prelude (Unit, bind, discard, flip, map, not, pure, unit, ($), (&&), (*>), (<<<), (<>), (>>=))
import Reactix as R
import Toestand as T
type Sigma =
{ sigma :: R.Ref (Maybe Sigma.Sigma)
......@@ -37,6 +34,9 @@ type Sigma =
type Data n e = { graph :: R.Ref (ST.Graph n e) }
console :: C.Console
console = C.encloseContext C.Plugin "Sigmax"
initSigma :: R.Hooks Sigma
initSigma = do
s <- R2.nothingRef
......@@ -69,21 +69,21 @@ cleanupSigma sigma context = traverse_ kill (readSigma sigma)
killSigma = Sigma.killSigma sig >>= report
runCleanups = sequence_ (R.readRef sigma.cleanup)
emptyOut = writeSigma sigma Nothing *> R.setRef sigma.cleanup Seq.empty
report = either (log2 errorMsg) (\_ -> log successMsg)
report = either (console.log2 errorMsg) (\_ -> console.log successMsg)
prefix = "[" <> context <> "] "
errorMsg = prefix <> "Error killing sigma:"
successMsg = prefix <> "Killed sigma"
refreshData :: forall n e. Sigma.Sigma -> Sigma.Graph n e -> Effect Unit
refreshData sigma graph
= log clearingMsg
= console.log clearingMsg
*> Sigma.clear sigmaGraph
*> log readingMsg
*> console.log readingMsg
*> Sigma.graphRead sigmaGraph graph
>>= either (log2 errorMsg) refresh
>>= either (console.log2 errorMsg) refresh
where
sigmaGraph = Sigma.graph sigma
refresh _ = log refreshingMsg *> Sigma.refresh sigma
refresh _ = console.log refreshingMsg *> Sigma.refresh sigma
clearingMsg = "[refreshData] Clearing existing graph data"
readingMsg = "[refreshData] Reading graph data"
refreshingMsg = "[refreshData] Refreshing graph"
......@@ -98,13 +98,13 @@ sigmafy (ST.Graph g) = {nodes,edges}
dependOnSigma :: Sigma -> String -> (Sigma.Sigma -> Effect Unit) -> Effect Unit
dependOnSigma sigma notFoundMsg f = do
case readSigma sigma of
Nothing -> log notFoundMsg
Nothing -> console.log notFoundMsg
Just sig -> f sig
dependOnContainer :: R.Ref (Nullable Element) -> String -> (Element -> Effect Unit) -> Effect Unit
dependOnContainer container notFoundMsg f = do
case R.readNullableRef container of
Nothing -> log notFoundMsg
Nothing -> console.log notFoundMsg
Just c -> f c
......@@ -206,7 +206,7 @@ bindSelectedEdgesClick sigmaRef (_ /\ setEdgeIds) =
Set.insert edge.id eids
selectorWithSize :: Sigma.Sigma -> Int -> Effect Unit
selectorWithSize sigma size = do
selectorWithSize _ _ = do
pure unit
performDiff :: Sigma.Sigma -> ST.SGraph -> Effect Unit
......
"use strict";
/**
* Get Creation Date
* @return {string}
*/
exports.getCreationDate = function() {
return new Date().toLocaleTimeString()
}
/**
* Bullet CSS
* @type {string}
*/
exports.bulletCSS = 'color: %s; padding: 4px 5px; font-weight: bold;'
/**
* Callee CSS
* @type {string}
*/
exports.calleeCSS = 'color: #FFFFFF; background: %s; padding: 4px 5px; font-size: 10px;'
/**
* Creation Date CSS
* @type {string}
*/
exports.creationDateCSS = 'font-size: 9px; padding: 4px 5px;'
module Gargantext.Plugins.Core.Console
( Console
, encloseContext
, CalleeType(..)
) where
import Gargantext.Prelude
import DOM.Simple.Console (log5, log6, log7)
import Data.Array (unsafeIndex)
import Data.String (Pattern(..), Replacement(..), replace)
import Effect (Effect)
import Partial.Unsafe (unsafePartial)
foreign import getCreationDate :: Effect String -- @TODO not using FFI
foreign import bulletCSS :: String
foreign import calleeCSS :: String
foreign import creationDateCSS :: String
type CalleeName = String
data CalleeType =
Plugin
| Component
| Page
| Store
| Layout
derive instance eqCalleeType :: Eq CalleeType
data LogType =
Log
| Error
| Warn
| Info
derive instance eqLogType :: Eq LogType
type Console =
{ log :: forall a. a -> Effect Unit
, error :: forall a. a -> Effect Unit
, warn :: forall a. a -> Effect Unit
, info :: forall a. a -> Effect Unit
, log2 :: forall a b. a -> b -> Effect Unit
, error2 :: forall a b. a -> b -> Effect Unit
, warn2 :: forall a b. a -> b -> Effect Unit
, info2 :: forall a b. a -> b -> Effect Unit
, log3 :: forall a b c. a -> b -> c -> Effect Unit
, error3 :: forall a b c. a -> b -> c -> Effect Unit
, warn3 :: forall a b c. a -> b -> c -> Effect Unit
, info3 :: forall a b c. a -> b -> c -> Effect Unit
}
-- | Logging as JavaScript fancy way
-- |
-- | Enclose the appling context
-- | ```purescript
-- | console :: Console
-- | console = encloseContext "page" "reactix"
-- | ```
-- |
-- | And reuse it as a native JavaScript call
-- | ```purescript
-- | console.log2 "catch something" somethingRecord
-- | ```
encloseContext :: CalleeType -> CalleeName -> Console
encloseContext a b =
{ log : print a b Log
, error : print a b Error
, warn : print a b Warn
, info : print a b Info
, log2 : print2 a b Log
, error2 : print2 a b Error
, warn2 : print2 a b Warn
, info2 : print2 a b Info
, log3 : print3 a b Log
, error3 : print3 a b Error
, warn3 : print3 a b Warn
, info3 : print3 a b Info
}
bulletContent :: LogType -> String
bulletContent Log = "▷"
bulletContent _ = "▶"
bulletStyle :: LogType -> String
bulletStyle s = replace (Pattern "%s") (Replacement s') bulletCSS
where
s' = case s of
Error -> "#BF3F3F"
Warn -> "#D4CC5B"
Info -> "#69A1F0"
Log -> "#A9A9A9"
calleeStyle :: CalleeType -> String
calleeStyle s = replace (Pattern "%s") (Replacement s') calleeCSS
where
s' = case s of
Plugin -> "#A1D490"
Component -> "#90D4B2"
Page -> "#90B9D4"
Store -> "#BE90D4"
Layout -> "#D3D490"
-- | eg. `print "page" "reactix" "log" "I am a log"`
print :: forall a. CalleeType -> CalleeName -> LogType -> a -> Effect Unit
print s s' s'' a = do
cells <- mkCells s s' s''
log5 (unsafePartial $ unsafeIndex cells 0)
(unsafePartial $ unsafeIndex cells 1)
(unsafePartial $ unsafeIndex cells 2)
(unsafePartial $ unsafeIndex cells 3)
a
-- | eg. `print2 "component" "button" "warn" "catch error" true`
print2 :: forall a b. CalleeType -> CalleeName -> LogType -> a -> b -> Effect Unit
print2 s s' s'' a b = do
cells <- mkCells s s' s''
log6 (unsafePartial $ unsafeIndex cells 0)
(unsafePartial $ unsafeIndex cells 1)
(unsafePartial $ unsafeIndex cells 2)
(unsafePartial $ unsafeIndex cells 3)
a b
print3 :: forall a b c. CalleeType -> CalleeName -> LogType -> a -> b -> c -> Effect Unit
print3 s s' s'' a b c = do
cells <- mkCells s s' s''
log7 (unsafePartial $ unsafeIndex cells 0)
(unsafePartial $ unsafeIndex cells 1)
(unsafePartial $ unsafeIndex cells 2)
(unsafePartial $ unsafeIndex cells 3)
a b c
mkCells :: CalleeType -> CalleeName -> LogType -> Effect (Array String)
mkCells calleeType calleeName logType = do
date <- getCreationDate
-- First cell: containing a concatenation of string with style signs "%c"
cell1 <- pure $ ("%c" <> bulletContent logType <> "%c" <> date <> "%c" <> calleeName)
-- Second cell: providing style for the first "%c"
cell2 <- pure $ bulletStyle $ logType
-- Third cell: idem
cell3 <- pure $ creationDateCSS
-- Fourth cell: idem
cell4 <- pure $ calleeStyle calleeType
pure $ [ cell1, cell2, cell3, cell4 ]
-- Next cells can either be in couple (content + style) or content one only
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