Commit 8932fa4e authored by Alexandre Delanoë's avatar Alexandre Delanoë

[Garg Prelude] liftEffect <<< log -> logs

parent d57b69ff
module Gargantext.Components.Login where module Gargantext.Components.Login where
import Prelude hiding (div)
import Affjax (defaultRequest, printResponseFormatError, request) import Affjax (defaultRequest, printResponseFormatError, request)
import Affjax.RequestBody (RequestBody(..)) import Affjax.RequestBody (RequestBody(..))
import Affjax.RequestHeader (RequestHeader(..)) import Affjax.RequestHeader (RequestHeader(..))
...@@ -12,11 +10,9 @@ import Data.HTTP.Method (Method(..)) ...@@ -12,11 +10,9 @@ import Data.HTTP.Method (Method(..))
import Data.Lens (over) import Data.Lens (over)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Data.MediaType.Common (applicationJSON) import Data.MediaType.Common (applicationJSON)
import Effect.Class (liftEffect)
import Effect (Effect) import Effect (Effect)
import Effect.Aff (Aff) import Effect.Aff (Aff)
import Effect.Class (liftEffect)
import Effect.Console (log)
import Gargantext.Components.Modals.Modal (modalHide)
import React.DOM (a, button, div, h2, h4, h5, i, input, label, p, span, text) import React.DOM (a, button, div, h2, h4, h5, i, input, label, p, span, text)
import React.DOM.Props (_data, _id, _type, aria, className, href, maxLength, name, onClick, onInput, placeholder, role, target, value) import React.DOM.Props (_data, _id, _type, aria, className, href, maxLength, name, onClick, onInput, placeholder, role, target, value)
import Thermite (PerformAction, Render, Spec, _render, modifyState, simpleSpec) import Thermite (PerformAction, Render, Spec, _render, modifyState, simpleSpec)
...@@ -25,7 +21,12 @@ import Web.HTML (window) ...@@ -25,7 +21,12 @@ import Web.HTML (window)
import Web.HTML.Window (localStorage) import Web.HTML.Window (localStorage)
import Web.Storage.Storage (getItem, setItem) import Web.Storage.Storage (getItem, setItem)
-- TODO: ask for login (modal) or account creation after 15 mn when user is not logged and has made one search at least ------------------------------------------------------------------------
import Gargantext.Prelude
import Gargantext.Components.Modals.Modal (modalHide)
-- TODO: ask for login (modal) or account creation after 15 mn when user
-- is not logged and has made one search at least
newtype State = State newtype State = State
{ username :: String { username :: String
...@@ -69,7 +70,7 @@ performAction Login _ _ = void do ...@@ -69,7 +70,7 @@ performAction Login _ _ = void do
-- res <- lift $ loginReq $ LoginReq { username : state.username, password : state.password } -- res <- lift $ loginReq $ LoginReq { username : state.username, password : state.password }
-- case res of -- case res of
-- Left e -> do -- Left e -> do
-- lift $ log $ show e -- logs e
-- modifyState \(State s) -> State $ s { errorMessage = e} -- modifyState \(State s) -> State $ s { errorMessage = e}
-- Right r@(LoginRes response) -> do -- Right r@(LoginRes response) -> do
-- lift $ setHash "/addCorpus" -- lift $ setHash "/addCorpus"
...@@ -252,15 +253,15 @@ loginReq encodeData = ...@@ -252,15 +253,15 @@ loginReq encodeData =
affResp <- request setting affResp <- request setting
case affResp.body of case affResp.body of
Left err -> do Left err -> do
liftEffect $ log $ printResponseFormatError err logs $ printResponseFormatError err
pure $ Left $ printResponseFormatError err pure $ Left $ printResponseFormatError err
Right json -> do Right json -> do
liftEffect $ log $ "POST method Completed" logs $ "POST method Completed"
liftEffect $ log $ "GET /api response: " <> stringify json logs $ "GET /api response: " <> stringify json
let obj = decodeJson json let obj = decodeJson json
case obj of case obj of
Left e -> Left e ->
liftEffect $ log $ "Error Decoding : " <> show e logs $ "Error Decoding : " <> show e
Right (LoginRes res1) -> Right (LoginRes res1) ->
liftEffect $ setToken res1.token liftEffect $ setToken res1.token
pure obj pure obj
......
module Gargantext.Components.Tree where module Gargantext.Components.Tree where
import Prelude hiding (div)
import Affjax (defaultRequest, printResponseFormatError, request) import Affjax (defaultRequest, printResponseFormatError, request)
import Affjax.RequestBody (RequestBody(..)) import Affjax.RequestBody (RequestBody(..))
import Affjax.ResponseFormat as ResponseFormat import Affjax.ResponseFormat as ResponseFormat
...@@ -14,16 +12,16 @@ import Data.Maybe (Maybe(..)) ...@@ -14,16 +12,16 @@ import Data.Maybe (Maybe(..))
import Data.Newtype (class Newtype) import Data.Newtype (class Newtype)
import Effect (Effect) import Effect (Effect)
import Effect.Aff (Aff) import Effect.Aff (Aff)
import Effect.Class (liftEffect)
import Effect.Console (log)
import Prelude (identity) import Prelude (identity)
import React (ReactElement) import React (ReactElement)
import Gargantext.Config (NodeType(..), readNodeType, toUrl, readNodeType, End(..), ApiVersion, defaultRoot)
import React.DOM (a, button, div, h5, i, input, li, span, text, ul) import React.DOM (a, button, div, h5, i, input, li, span, text, ul)
import React.DOM.Props (Props, _type, className, href, onClick, onInput, placeholder, style, value) import React.DOM.Props (Props, _type, className, href, onClick, onInput, placeholder, style, value)
import Thermite (PerformAction, Render, Spec, cotransform, modifyState, simpleSpec) import Thermite (PerformAction, Render, Spec, cotransform, modifyState, simpleSpec)
import Unsafe.Coerce (unsafeCoerce) import Unsafe.Coerce (unsafeCoerce)
import Gargantext.Prelude
import Gargantext.Config (NodeType(..), readNodeType, toUrl, readNodeType, End(..), ApiVersion, defaultRoot)
type Name = String type Name = String
type Open = Boolean type Open = Boolean
type URL = String type URL = String
...@@ -289,12 +287,12 @@ loadDefaultNode = do ...@@ -289,12 +287,12 @@ loadDefaultNode = do
} }
case res.body of case res.body of
Left err -> do Left err -> do
_ <- liftEffect $ log $ printResponseFormatError err _ <- logs $ printResponseFormatError err
pure $ Left $ printResponseFormatError err pure $ Left $ printResponseFormatError err
Right json -> do Right json -> do
--_ <- liftEffect $ log $ show a.status --_ <- logs $ show a.status
--_ <- liftEffect $ log $ show a.headers --_ <- logs $ show a.headers
--_ <- liftEffect $ log $ show a.body --_ <- logs $ show a.body
let obj = decodeJson json let obj = decodeJson json
pure obj pure obj
...@@ -322,12 +320,12 @@ renameNode renameNodeId reqbody = do ...@@ -322,12 +320,12 @@ renameNode renameNodeId reqbody = do
} }
case res.body of case res.body of
Left err -> do Left err -> do
_ <- liftEffect $ log $ printResponseFormatError err _ <- logs $ printResponseFormatError err
pure $ Left $ printResponseFormatError err pure $ Left $ printResponseFormatError err
Right json -> do Right json -> do
--_ <- liftEffect $ log $ show a.status --_ <- logs $ show a.status
--_ <- liftEffect $ log $ show a.headers --_ <- logs $ show a.headers
--_ <- liftEffect $ log $ show a.body --_ <- logs $ show a.body
let obj = decodeJson json let obj = decodeJson json
pure obj pure obj
...@@ -344,12 +342,12 @@ deleteNode = do ...@@ -344,12 +342,12 @@ deleteNode = do
case res.body of case res.body of
Left err -> do Left err -> do
_ <- liftEffect $ log $ printResponseFormatError err _ <- logs $ printResponseFormatError err
pure $ Left $ printResponseFormatError err pure $ Left $ printResponseFormatError err
Right json -> do Right json -> do
--_ <- liftEffect $ log $ show a.status --_ <- logs $ show a.status
--_ <- liftEffect $ log $ show a.headers --_ <- logs $ show a.headers
--_ <- liftEffect $ log $ show a.body --_ <- logs $ show a.body
let obj = decodeJson json let obj = decodeJson json
pure obj pure obj
...@@ -366,12 +364,12 @@ deleteNodes reqbody = do ...@@ -366,12 +364,12 @@ deleteNodes reqbody = do
} }
case res.body of case res.body of
Left err -> do Left err -> do
_ <- liftEffect $ log $ printResponseFormatError err _ <- logs $ printResponseFormatError err
pure $ Left $ printResponseFormatError err pure $ Left $ printResponseFormatError err
Right json -> do Right json -> do
--_ <- liftEffect $ log $ show a.status --_ <- logs $ show a.status
--_ <- liftEffect $ log $ show a.headers --_ <- logs $ show a.headers
--_ <- liftEffect $ log $ show a.body --_ <- logs $ show a.body
let obj = decodeJson json let obj = decodeJson json
pure obj pure obj
...@@ -387,12 +385,12 @@ createNode reqbody= do ...@@ -387,12 +385,12 @@ createNode reqbody= do
} }
case res.body of case res.body of
Left err -> do Left err -> do
_ <- liftEffect $ log $ printResponseFormatError err _ <- logs $ printResponseFormatError err
pure $ Left $ printResponseFormatError err pure $ Left $ printResponseFormatError err
Right json -> do Right json -> do
--_ <- liftEffect $ log $ show a.status --_ <- logs $ show a.status
--_ <- liftEffect $ log $ show a.headers --_ <- logs $ show a.headers
--_ <- liftEffect $ log $ show a.body --_ <- logs $ show a.body
let obj = decodeJson json let obj = decodeJson json
pure obj pure obj
......
module Gargantext.Pages.Annuaire where module Gargantext.Pages.Annuaire where
import Prelude
import Data.Array (concat) import Data.Array (concat)
import Data.Traversable (foldl) import Data.Traversable (foldl)
import Control.Monad.Trans.Class (lift) import Control.Monad.Trans.Class (lift)
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.Lens (Lens', Prism', lens, prism, (?~)) import Data.Lens (Lens', Prism', lens, prism, (?~))
import Data.Maybe (Maybe(..), maybe) import Data.Maybe (Maybe(..), maybe)
import Effect.Class (liftEffect)
import React (ReactElement) import React (ReactElement)
import React.DOM (div, h1, h3, hr, i, p, text, thead, tbody, input, br', b, b', tr, th, table, td, a) import React.DOM (div, h1, h3, hr, i, p, text, thead, tbody, input, br', b, b', tr, th, table, td, a)
import React.DOM.Props (_type, className, href, onChange, onClick, scope, selected, value, style) import React.DOM.Props (_type, className, href, onChange, onClick, scope, selected, value, style)
import Effect.Console (log)
import Effect.Aff (Aff)
import Thermite (Render, Spec import Thermite (Render, Spec
, simpleSpec , simpleSpec
, PerformAction, modifyState) , PerformAction, modifyState)
import Effect.Console (log)
import Effect.Aff (Aff)
------------------------------------------------------------------------------
import Gargantext.Prelude
import Gargantext.Config (toUrl, NodeType(..), End(..)) import Gargantext.Config (toUrl, NodeType(..), End(..))
import Gargantext.Config.REST (get) import Gargantext.Config.REST (get)
import Gargantext.Pages.Annuaire.User.Users.Types.Types (User(..), HyperData(..)) import Gargantext.Pages.Annuaire.User.Users.Types.Types (User(..), HyperData(..))
import Gargantext.Utils.DecodeMaybe ((.?|)) import Gargantext.Utils.DecodeMaybe ((.?|))
import Data.Argonaut (class DecodeJson, decodeJson, (.?)) import Data.Argonaut (class DecodeJson, decodeJson, (.?))
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
type State = { info :: Maybe AnnuaireInfo type State = { info :: Maybe AnnuaireInfo
, stable :: Maybe AnnuaireTable , stable :: Maybe AnnuaireTable
...@@ -177,20 +175,19 @@ instance decodeAnnuaireTable :: DecodeJson AnnuaireTable where ...@@ -177,20 +175,19 @@ instance decodeAnnuaireTable :: DecodeJson AnnuaireTable where
------------------------------------------------------------------------ ------------------------------------------------------------------------
performAction :: PerformAction State {} Action performAction :: PerformAction State {} Action
performAction (Load aId) _ _ = do performAction (Load aId) _ _ = do
eitherInfo <- lift $ getInfo aId eitherInfo <- lift $ getInfo aId
_ <- case eitherInfo of _ <- case eitherInfo of
(Right info') -> void $ modifyState $ _info ?~ info' (Right info') -> void $ modifyState $ _info ?~ info'
(Left err) -> do (Left err) -> do
liftEffect $ log err logs err
eitherTable <- lift $ getTable aId eitherTable <- lift $ getTable aId
liftEffect $ log "Feching Table" logs "Feching Table"
_ <- case eitherTable of _ <- case eitherTable of
(Right table') -> void $ modifyState $ _table ?~ table' (Right table') -> void $ modifyState $ _table ?~ table'
(Left err) -> do (Left err) -> do
liftEffect $ log err logs err
liftEffect <<< log $ "Annuaire page fetched." logs "Annuaire page fetched."
performAction _ _ _ = pure unit performAction _ _ _ = pure unit
------------------------------------------------------------------------ ------------------------------------------------------------------------
......
module Gargantext.Pages.Annuaire.User.Users.API where module Gargantext.Pages.Annuaire.User.Users.API where
import Prelude
import Control.Monad.Trans.Class (lift) import Control.Monad.Trans.Class (lift)
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.Lens ((?~)) import Data.Lens ((?~))
...@@ -9,11 +7,12 @@ import Data.Maybe (Maybe(..)) ...@@ -9,11 +7,12 @@ import Data.Maybe (Maybe(..))
import Effect.Aff (Aff) import Effect.Aff (Aff)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
import Effect.Console (log) import Effect.Console (log)
import Thermite (PerformAction, modifyState)
import Gargantext.Config (toUrl, NodeType(..), End(..)) import Gargantext.Config (toUrl, NodeType(..), End(..))
import Gargantext.Config.REST (get) import Gargantext.Config.REST (get)
import Gargantext.Pages.Annuaire.User.Users.Types (Action(..), State, User, _user) import Gargantext.Pages.Annuaire.User.Users.Types (Action(..), State, User, _user)
import Thermite (PerformAction, modifyState) import Gargantext.Prelude
getUser :: Int -> Aff (Either String User) getUser :: Int -> Aff (Either String User)
getUser id = get $ toUrl Back Node id getUser id = get $ toUrl Back Node id
...@@ -25,6 +24,6 @@ performAction (FetchUser userId) _ _ = do ...@@ -25,6 +24,6 @@ performAction (FetchUser userId) _ _ = do
_ <- case value of _ <- case value of
(Right user) -> void $ modifyState $ _user ?~ user (Right user) -> void $ modifyState $ _user ?~ user
(Left err) -> do (Left err) -> do
liftEffect $ log err logs err
liftEffect <<< log $ "Fetching user..." logs "Fetching user..."
performAction _ _ _ = pure unit performAction _ _ _ = pure unit
module Gargantext.Pages.Corpus where module Gargantext.Pages.Corpus where
import Prelude hiding (div)
import Control.Monad.Trans.Class (lift) import Control.Monad.Trans.Class (lift)
import Data.Maybe (Maybe(..), maybe) import Data.Argonaut (class DecodeJson, decodeJson, (.?))
import Data.Either (Either(..))
import Data.Lens (Lens', Prism', lens, prism, (?~)) import Data.Lens (Lens', Prism', lens, prism, (?~))
import Data.List (fromFoldable) import Data.List (fromFoldable)
import Data.Either (Either(..)) import Data.Maybe (Maybe(..), maybe)
import Data.Tuple (Tuple(..)) import Data.Tuple (Tuple(..))
import Data.Argonaut (class DecodeJson, decodeJson, (.?))
import Effect.Aff (Aff) import Effect.Aff (Aff)
import Effect.Class (liftEffect)
import Effect.Console (log)
import React.DOM (div, h3, hr, i, p, text) import React.DOM (div, h3, hr, i, p, text)
import React.DOM.Props (className, style) import React.DOM.Props (className, style)
import Thermite ( Render, Spec, PerformAction, focus, hide import Thermite ( Render, Spec, PerformAction, focus, hide
, defaultPerformAction, simpleSpec, modifyState) , defaultPerformAction, simpleSpec, modifyState)
-------------------------------------------------------- --------------------------------------------------------
import Gargantext.Prelude
import Gargantext.Config (toUrl, NodeType(..), End(..)) import Gargantext.Config (toUrl, NodeType(..), End(..))
import Gargantext.Config.REST (get) import Gargantext.Config.REST (get)
--------------------------------------------------------- ---------------------------------------------------------
...@@ -202,7 +197,6 @@ corpusSpec = simpleSpec performAction render ...@@ -202,7 +197,6 @@ corpusSpec = simpleSpec performAction render
] ]
] ]
] ]
--, chart globalPublis -- TODO add chart data in state
] ]
where where
NodePoly { name: title NodePoly { name: title
...@@ -219,8 +213,8 @@ performAction (Load nId) _ _ = do ...@@ -219,8 +213,8 @@ performAction (Load nId) _ _ = do
_ <- case eitherInfo of _ <- case eitherInfo of
(Right node') -> void $ modifyState $ _info ?~ node' (Right node') -> void $ modifyState $ _info ?~ node'
(Left err) -> do (Left err) -> do
liftEffect $ log err logs err
liftEffect <<< log $ "Node Corpus fetched." logs $ "Node Corpus fetched."
performAction _ _ _ = pure unit performAction _ _ _ = pure unit
getNode :: Int -> Aff (Either String (NodePoly CorpusInfo)) getNode :: Int -> Aff (Either String (NodePoly CorpusInfo))
......
module Gargantext.Pages.Corpus.Doc.Facets.Documents where module Gargantext.Pages.Corpus.Doc.Facets.Documents where
import Affjax (defaultRequest, printResponseFormatError, request) import Affjax (defaultRequest, printResponseFormatError, request)
import Affjax.ResponseFormat as ResponseFormat import Affjax.ResponseFormat as ResponseFormat
import Control.Monad.Cont.Trans (lift) import Control.Monad.Cont.Trans (lift)
...@@ -13,31 +12,19 @@ import Data.HTTP.Method (Method(..)) ...@@ -13,31 +12,19 @@ import Data.HTTP.Method (Method(..))
import Data.Tuple (Tuple(..)) import Data.Tuple (Tuple(..))
import Effect (Effect) import Effect (Effect)
import Effect.Aff (Aff) import Effect.Aff (Aff)
import React (ReactElement)
import Gargantext.Prelude hiding (div) import React.DOM (a, b, b', br', div, input, option, select, span, table, tbody, td, text, th, thead, tr, p)
import React.DOM.Props (_type, className, href, onChange, onClick, scope, selected, value)
import Thermite (PerformAction, Render, Spec, modifyState, defaultPerformAction, simpleSpec)
import Unsafe.Coerce (unsafeCoerce)
------------------------------------------------------------------------
import Gargantext.Prelude
import Gargantext.Config (NodeType(..), toUrl, End(..)) import Gargantext.Config (NodeType(..), toUrl, End(..))
import Gargantext.Config.REST (get) import Gargantext.Config.REST (get)
import Gargantext.Utils.DecodeMaybe ((.|)) import Gargantext.Utils.DecodeMaybe ((.|))
------------------------------------------------------------------------
import Gargantext.Components.Charts.Options.ECharts (chart) import Gargantext.Components.Charts.Options.ECharts (chart)
import Gargantext.Pages.Corpus.Doc.Facets.Dashboard (globalPublis) import Gargantext.Pages.Corpus.Doc.Facets.Dashboard (globalPublis)
------------------------------------------------------------------------ ------------------------------------------------------------------------
import React (ReactElement)
import React.DOM (a, b, b', br', div, input, option, select, span, table, tbody, td, text, th, thead, tr, p)
import React.DOM.Props (_type, className, href, onChange, onClick, scope, selected, value)
import Thermite (PerformAction, Render, Spec, modifyState, defaultPerformAction, simpleSpec)
import Unsafe.Coerce (unsafeCoerce)
--main :: forall e. Eff (dom:: DOM, console :: CONSOLE, ajax :: AJAX | e) Unit
--main = do
-- case createReactSpec layoutDocview tdata of
-- { spec, dispatcher } -> void $ do
-- document <- DOM.window >>= DOM.document
-- container <- unsafePartial (fromJust <$> DOM.querySelector (QuerySelector "#app") (DOM.htmlDocumentToParentNode document))
-- RDOM.render (R.createFactory (R.createClass spec) {}) container
--
-- TODO: Pagination Details are not available from the BackEnd -- TODO: Pagination Details are not available from the BackEnd
-- TODO: PageSize Change manually sets the totalPages, need to get from backend and reload the data -- TODO: PageSize Change manually sets the totalPages, need to get from backend and reload the data
-- TODO: Search is pending -- TODO: Search is pending
...@@ -45,7 +32,6 @@ import Unsafe.Coerce (unsafeCoerce) ...@@ -45,7 +32,6 @@ import Unsafe.Coerce (unsafeCoerce)
-- TODO: Sort is Pending -- TODO: Sort is Pending
-- TODO: Filter is Pending -- TODO: Filter is Pending
-- TODO: When a pagination link is clicked, reload data. -- TODO: When a pagination link is clicked, reload data.
-- Right now it doesn't make sense to reload mock data.
data Action data Action
= LoadData Int = LoadData Int
...@@ -208,7 +194,7 @@ loadPage n = do ...@@ -208,7 +194,7 @@ loadPage n = do
case res of case res of
Left err -> do Left err -> do
_ <- logs "Err: loading page documents" _ <- logs "Err: loading page documents"
_ <- logs $ show err _ <- logs err
pure $ Left $ show err pure $ Left $ show err
Right resData -> do Right resData -> do
let docs = toTableData (res2corpus $ resData) let docs = toTableData (res2corpus $ resData)
......
module Gargantext.Pages.Corpus.Doc.Facets.Graph where module Gargantext.Pages.Corpus.Doc.Facets.Graph where
import Prelude hiding (div)
import Affjax (defaultRequest, printResponseFormatError, request) import Affjax (defaultRequest, printResponseFormatError, request)
import Affjax.RequestHeader (RequestHeader(..)) import Affjax.RequestHeader (RequestHeader(..))
import Affjax.ResponseFormat as ResponseFormat import Affjax.ResponseFormat as ResponseFormat
...@@ -15,11 +13,6 @@ import Data.Maybe (Maybe(..), fromJust) ...@@ -15,11 +13,6 @@ import Data.Maybe (Maybe(..), fromJust)
import Data.MediaType.Common (applicationJSON) import Data.MediaType.Common (applicationJSON)
import Data.Newtype (class Newtype) import Data.Newtype (class Newtype)
import Effect.Aff (Aff) import Effect.Aff (Aff)
import Effect.Class (liftEffect)
import Effect.Console (log)
import Gargantext.Components.GraphExplorer.Sigmajs (Color(Color), SigmaEasing, SigmaGraphData(SigmaGraphData), SigmaNode, SigmaSettings, canvas, edgeShape, edgeShapes, forceAtlas2, sStyle, sigma, sigmaEasing, sigmaEdge, sigmaEnableWebGL, sigmaNode, sigmaSettings)
import Gargantext.Components.GraphExplorer.Types (Cluster(..), Edge(..), GraphData(..), Legend(..), Node(..), getLegendData)
import Gargantext.Utils (getter)
import Math (cos, sin) import Math (cos, sin)
import Partial.Unsafe (unsafePartial) import Partial.Unsafe (unsafePartial)
import React (ReactElement) import React (ReactElement)
...@@ -28,6 +21,12 @@ import React.DOM.Props (_id, _type, checked, className, href, name, onChange, pl ...@@ -28,6 +21,12 @@ import React.DOM.Props (_id, _type, checked, className, href, name, onChange, pl
import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec) import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec)
import Unsafe.Coerce (unsafeCoerce) import Unsafe.Coerce (unsafeCoerce)
import Gargantext.Prelude
import Gargantext.Components.GraphExplorer.Sigmajs (Color(Color), SigmaEasing, SigmaGraphData(SigmaGraphData), SigmaNode, SigmaSettings, canvas, edgeShape, edgeShapes, forceAtlas2, sStyle, sigma, sigmaEasing, sigmaEdge, sigmaEnableWebGL, sigmaNode, sigmaSettings)
import Gargantext.Components.GraphExplorer.Types (Cluster(..), Edge(..), GraphData(..), Legend(..), Node(..), getLegendData)
import Gargantext.Utils (getter)
data Action data Action
= LoadGraph String = LoadGraph String
| SelectNode SelectedNode | SelectNode SelectedNode
...@@ -59,7 +58,7 @@ graphSpec = simpleSpec performAction render ...@@ -59,7 +58,7 @@ graphSpec = simpleSpec performAction render
performAction :: PerformAction State {} Action performAction :: PerformAction State {} Action
performAction (LoadGraph fp) _ _ = void do performAction (LoadGraph fp) _ _ = void do
_ <- liftEffect $ log fp _ <- logs fp
case fp of case fp of
"" -> do "" -> do
modifyState \(State s) -> State s {filePath = fp, graphData = GraphData {nodes : [], edges : []}, sigmaGraphData = Nothing} modifyState \(State s) -> State s {filePath = fp, graphData = GraphData {nodes : [], edges : []}, sigmaGraphData = Nothing}
...@@ -117,7 +116,7 @@ render d p (State s) c = ...@@ -117,7 +116,7 @@ render d p (State s) c =
, settings : mySettings , settings : mySettings
, style : sStyle { height : "95%"} , style : sStyle { height : "95%"}
-- , onClickNode : \e -> do -- , onClickNode : \e -> do
-- log $ unsafeCoerce e -- logs $ unsafeCoerce e
-- d $ SelectNode $ SelectedNode {id : (unsafeCoerce e).data.node.id, label : (unsafeCoerce e).data.node.label} -- d $ SelectNode $ SelectedNode {id : (unsafeCoerce e).data.node.id, label : (unsafeCoerce e).data.node.label}
-- pure unit -- pure unit
-- TODO: fix this! -- TODO: fix this!
...@@ -234,10 +233,10 @@ getGraphData fp = do ...@@ -234,10 +233,10 @@ getGraphData fp = do
} }
case resp.body of case resp.body of
Left err -> do Left err -> do
liftEffect $ log $ printResponseFormatError err logs $ printResponseFormatError err
pure $ Left $ printResponseFormatError err pure $ Left $ printResponseFormatError err
Right json -> do Right json -> do
liftEffect $ log $ stringify json logs $ stringify json
let gd = decodeJson json let gd = decodeJson json
pure gd pure gd
...@@ -392,7 +391,7 @@ specOld = simpleSpec performAction render' ...@@ -392,7 +391,7 @@ specOld = simpleSpec performAction render'
, settings : mySettings , settings : mySettings
, style : sStyle { height : "95%"} , style : sStyle { height : "95%"}
-- , onClickNode : \e -> do -- , onClickNode : \e -> do
-- log $ unsafeCoerce e -- logs $ unsafeCoerce e
-- d $ SelectNode $ SelectedNode {id : (unsafeCoerce e).data.node.id, label : (unsafeCoerce e).data.node.label} -- d $ SelectNode $ SelectedNode {id : (unsafeCoerce e).data.node.id, label : (unsafeCoerce e).data.node.label}
-- pure unit -- pure unit
} }
......
...@@ -2,28 +2,27 @@ ...@@ -2,28 +2,27 @@
module Gargantext.Pages.Layout.Actions where module Gargantext.Pages.Layout.Actions where
import Prelude hiding (div)
import Control.Monad.Cont.Trans (lift) import Control.Monad.Cont.Trans (lift)
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.Lens (Prism', prism) import Data.Lens (Prism', prism)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
import Effect.Console (log) import Effect.Console (log)
import Thermite (PerformAction, modifyState)
import Gargantext.Components.Login as LN import Gargantext.Components.Login as LN
import Gargantext.Components.Modals.Modal (modalShow) import Gargantext.Components.Modals.Modal (modalShow)
import Gargantext.Components.Tree as Tree import Gargantext.Components.Tree as Tree
import Gargantext.Pages.Annuaire as Annuaire
import Gargantext.Pages.Annuaire.User.Users as U
import Gargantext.Pages.Corpus as Corpus import Gargantext.Pages.Corpus as Corpus
import Gargantext.Pages.Corpus.Doc.Annotation as D import Gargantext.Pages.Corpus.Doc.Annotation as D
import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV
import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE
import Gargantext.Pages.Annuaire.User.Users as U
import Gargantext.Pages.Annuaire as Annuaire
import Gargantext.Pages.Layout.Specs.AddCorpus as AC import Gargantext.Pages.Layout.Specs.AddCorpus as AC
import Gargantext.Pages.Layout.Specs.Search as S import Gargantext.Pages.Layout.Specs.Search as S
import Gargantext.Pages.Layout.States (AppState) import Gargantext.Pages.Layout.States (AppState)
import Gargantext.Prelude
import Gargantext.Router (Routes) import Gargantext.Router (Routes)
import Thermite (PerformAction, modifyState)
------------------------------------------------------------------------ ------------------------------------------------------------------------
...@@ -70,7 +69,7 @@ performAction Go _ _ = void do ...@@ -70,7 +69,7 @@ performAction Go _ _ = void do
--------------------------------------------------------- ---------------------------------------------------------
performAction Initialize _ state = void do performAction Initialize _ state = void do
_ <- liftEffect $ log "loading Initial nodes" _ <- logs "loading Initial nodes"
case state.initialized of case state.initialized of
false -> do false -> do
lnodes <- lift $ Tree.loadDefaultNode lnodes <- lift $ Tree.loadDefaultNode
......
module Gargantext.Pages.Layout.Specs.AddCorpus.Actions where module Gargantext.Pages.Layout.Specs.AddCorpus.Actions where
import Prelude hiding (div)
import Affjax (defaultRequest, printResponseFormatError, request) import Affjax (defaultRequest, printResponseFormatError, request)
import Affjax.RequestBody (RequestBody(..)) import Affjax.RequestBody (RequestBody(..))
import Affjax.RequestHeader (RequestHeader(..)) import Affjax.RequestHeader (RequestHeader(..))
...@@ -15,11 +13,13 @@ import Data.MediaType.Common (applicationJSON) ...@@ -15,11 +13,13 @@ import Data.MediaType.Common (applicationJSON)
import Effect.Aff (Aff) import Effect.Aff (Aff)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
import Effect.Console (log) import Effect.Console (log)
import Gargantext.Components.Modals.Modal (modalHide)
import Gargantext.Pages.Layout.Specs.AddCorpus.States (Response, State)
import Routing.Hash (setHash) import Routing.Hash (setHash)
import Thermite (PerformAction, modifyState) import Thermite (PerformAction, modifyState)
import Gargantext.Prelude
import Gargantext.Components.Modals.Modal (modalHide)
import Gargantext.Pages.Layout.Specs.AddCorpus.States (Response, State)
data Action data Action
= SelectDatabase Boolean = SelectDatabase Boolean
| UnselectDatabase Boolean | UnselectDatabase Boolean
...@@ -83,10 +83,10 @@ getDatabaseDetails reqBody = do ...@@ -83,10 +83,10 @@ getDatabaseDetails reqBody = do
} }
case affResp.body of case affResp.body of
Left err -> do Left err -> do
liftEffect $ log $ "error" <> printResponseFormatError err logs $ "error" <> printResponseFormatError err
pure $ Left $ printResponseFormatError err pure $ Left $ printResponseFormatError err
Right json -> do Right json -> do
liftEffect $ log $ "POST method Completed" logs $ "POST method Completed"
liftEffect $ log $ "GET /api response: " <> stringify json logs $ "GET /api response: " <> stringify json
let obj = decodeJson json let obj = decodeJson json
pure obj pure obj
module Gargantext.Pages.Layout.Specs.AddCorpus.Specs where module Gargantext.Pages.Layout.Specs.AddCorpus.Specs where
import Gargantext.Pages.Layout.Specs.AddCorpus.Actions
import Gargantext.Pages.Layout.Specs.AddCorpus.States
import Prelude hiding (div)
import Affjax (defaultRequest, printResponseFormatError, request) import Affjax (defaultRequest, printResponseFormatError, request)
import Affjax.RequestBody (RequestBody(..)) import Affjax.RequestBody (RequestBody(..))
import Affjax.ResponseFormat as ResponseFormat import Affjax.ResponseFormat as ResponseFormat
...@@ -23,6 +19,9 @@ import React.DOM (button, div, h3, h5, li, span, text, ul) ...@@ -23,6 +19,9 @@ import React.DOM (button, div, h3, h5, li, span, text, ul)
import React.DOM.Props (_data, _id, _type, aria, className, onClick, role) import React.DOM.Props (_data, _id, _type, aria, className, onClick, role)
import Thermite (PerformAction, Render, Spec, _render, simpleSpec) import Thermite (PerformAction, Render, Spec, _render, simpleSpec)
import Gargantext.Prelude
import Gargantext.Pages.Layout.Specs.AddCorpus.Actions
import Gargantext.Pages.Layout.Specs.AddCorpus.States
modalSpec :: Boolean -> String -> Spec State {} Action -> Spec State {} Action modalSpec :: Boolean -> String -> Spec State {} Action -> Spec State {} Action
modalSpec sm t = over _render \render d p s c -> modalSpec sm t = over _render \render d p s c ->
...@@ -136,11 +135,11 @@ countResults query = do ...@@ -136,11 +135,11 @@ countResults query = do
} }
case res.body of case res.body of
Left err -> do Left err -> do
_ <- liftEffect $ log $ printResponseFormatError err _ <- logs $ printResponseFormatError err
pure $ Left $ printResponseFormatError err pure $ Left $ printResponseFormatError err
Right json -> do Right json -> do
--_ <- liftEffect $ log $ show a.status --_ <- logs $ show a.status
--_ <- liftEffect $ log $ show a.headers --_ <- logs $ show a.headers
--_ <- liftEffect $ log $ show a.body --_ <- logs $ show a.body
let obj = decodeJson json let obj = decodeJson json
pure obj pure obj
module Gargantext.Prelude (module Prelude, logs) module Gargantext.Prelude (module Prelude, logs)
where where
import Prelude import Prelude hiding (div)
import Effect.Console (log) import Effect.Console (log)
import Effect.Class -- (MonadEffect(), liftEffect) -- TODO fix import import Effect.Class -- (MonadEffect(), liftEffect) -- TODO fix import
......
module Gargantext.Router where module Gargantext.Router where
import Prelude import Gargantext.Prelude
import Control.Alt ((<|>)) import Control.Alt ((<|>))
import Data.Int (floor) import Data.Int (floor)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Effect (Effect) import Effect (Effect)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
import Effect.Console (log)
import Routing.Match (Match, lit, num) import Routing.Match (Match, lit, num)
import Web.HTML (window) import Web.HTML (window)
import Web.HTML.Window (localStorage) import Web.HTML.Window (localStorage)
...@@ -72,19 +71,19 @@ instance showRoutes :: Show Routes where ...@@ -72,19 +71,19 @@ instance showRoutes :: Show Routes where
routeHandler :: (Maybe Routes -> Routes -> Effect Unit) routeHandler :: (Maybe Routes -> Routes -> Effect Unit)
-> Maybe Routes -> Routes -> Effect Unit -> Maybe Routes -> Routes -> Effect Unit
routeHandler dispatchAction old new = do routeHandler dispatchAction old new = do
liftEffect $ log $ "change route : " <> show new logs $ "change route : " <> show new
w <- window w <- window
ls <- localStorage w ls <- localStorage w
token <- getItem "accessToken" ls token <- getItem "accessToken" ls
let tkn = token let tkn = token
liftEffect $ log $ "JWToken : " <> show tkn logs $ "JWToken : " <> show tkn
case tkn of case tkn of
Nothing -> do Nothing -> do
dispatchAction old new dispatchAction old new
liftEffect $ log $ "called SignIn Route :" logs $ "called SignIn Route :"
Just t -> do Just t -> do
dispatchAction old new dispatchAction old new
liftEffect $ log $ "called Route : " <> show new logs $ "called Route : " <> show new
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