Commit 8c76b7bc authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

Fix more warning errors

parent c4bee502
module Gargantext.Components.Forest.Tree.Node where module Gargantext.Components.Forest.Tree.Node where
import Prelude import Prelude (class Eq, class Show, show, (&&), (<>), (==))
import Data.Array (foldl) import Data.Array (foldl)
import Gargantext.Types import Gargantext.Types
import Effect.Uncurried (mkEffectFn1)
-- import Data.Set
import Data.Array (filter)
import Reactix.DOM.HTML as H
import Effect.Aff (Aff, launchAff, runAff)
------------------------------------------------------------------------ ------------------------------------------------------------------------
------------------------------------------------------------------------ ------------------------------------------------------------------------
......
...@@ -6,7 +6,6 @@ import Data.Array ((!!), length) ...@@ -6,7 +6,6 @@ import Data.Array ((!!), length)
import Data.Maybe (Maybe(..), fromJust) import Data.Maybe (Maybe(..), fromJust)
import Data.Newtype (class Newtype) import Data.Newtype (class Newtype)
import Partial.Unsafe (unsafePartial) import Partial.Unsafe (unsafePartial)
import Reactix as R
newtype Node = Node newtype Node = Node
{ id_ :: String { id_ :: String
......
module Gargantext.Components.Loader where module Gargantext.Components.Loader where
import Prelude import Prelude
import Data.Maybe (Maybe(..), isNothing, maybe, maybe') import Data.Maybe (Maybe(..), maybe')
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import Effect.Aff (Aff) import Effect.Aff (Aff)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
......
...@@ -2,7 +2,7 @@ module Gargantext.Components.Login.Types where ...@@ -2,7 +2,7 @@ module Gargantext.Components.Login.Types where
import Prelude import Prelude
import Data.Argonaut ( class DecodeJson, class EncodeJson, decodeJson, jsonEmptyObject import Data.Argonaut ( class DecodeJson, class EncodeJson, decodeJson, jsonEmptyObject
, (.:), (.??), (:=), (~>) , (.:), (.:!), (:=), (~>)
) )
import Data.Generic.Rep (class Generic) import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Eq (genericEq) import Data.Generic.Rep.Eq (genericEq)
...@@ -52,8 +52,8 @@ instance decodeAuthInvalid :: DecodeJson AuthInvalid where ...@@ -52,8 +52,8 @@ instance decodeAuthInvalid :: DecodeJson AuthInvalid where
instance decodeAuthResponse :: DecodeJson AuthResponse where instance decodeAuthResponse :: DecodeJson AuthResponse where
decodeJson json = do decodeJson json = do
obj <- decodeJson json obj <- decodeJson json
valid <- obj .?? "valid" valid <- obj .:! "valid"
inval <- obj .?? "inval" inval <- obj .:! "inval"
pure $ AuthResponse {valid, inval} pure $ AuthResponse {valid, inval}
instance decodeAuthData :: DecodeJson AuthData where instance decodeAuthData :: DecodeJson AuthData where
......
...@@ -15,7 +15,7 @@ import Gargantext.Ends (url, Frontends) ...@@ -15,7 +15,7 @@ import Gargantext.Ends (url, Frontends)
import Gargantext.Routes (SessionRoute(..)) import Gargantext.Routes (SessionRoute(..))
import Gargantext.Routes as Routes import Gargantext.Routes as Routes
import Gargantext.Sessions (Session, sessionId, get) import Gargantext.Sessions (Session, sessionId, get)
import Gargantext.Types (NodePath(..), NodeType(..)) import Gargantext.Types (NodeType(..))
import Gargantext.Hooks.Loader (useLoader) import Gargantext.Hooks.Loader (useLoader)
newtype IndividuView = newtype IndividuView =
......
...@@ -2,7 +2,7 @@ module Gargantext.Components.Nodes.Annuaire.User.Contacts.Types where ...@@ -2,7 +2,7 @@ module Gargantext.Components.Nodes.Annuaire.User.Contacts.Types where
import Prelude import Prelude
import Data.Argonaut (class DecodeJson, decodeJson, (.:), (.??)) import Data.Argonaut (class DecodeJson, decodeJson, (.:), (.:!))
import Data.Maybe (Maybe, fromMaybe) import Data.Maybe (Maybe, fromMaybe)
import Data.Map (Map) import Data.Map (Map)
import Gargantext.Utils.DecodeMaybe ((.?|)) import Gargantext.Utils.DecodeMaybe ((.?|))
...@@ -36,11 +36,11 @@ instance decodeContactWho :: DecodeJson ContactWho ...@@ -36,11 +36,11 @@ instance decodeContactWho :: DecodeJson ContactWho
where where
decodeJson json = do decodeJson json = do
obj <- decodeJson json obj <- decodeJson json
idWho <- obj .?? "id" idWho <- obj .:! "id"
firstName <- obj .?? "firstName" firstName <- obj .:! "firstName"
lastName <- obj .?? "lastName" lastName <- obj .:! "lastName"
keywords <- obj .?? "keywords" keywords <- obj .:! "keywords"
freetags <- obj .?? "freetags" freetags <- obj .:! "freetags"
let k = fromMaybe [] keywords let k = fromMaybe [] keywords
let f = fromMaybe [] freetags let f = fromMaybe [] freetags
...@@ -69,15 +69,15 @@ instance decodeContactWhere :: DecodeJson ContactWhere ...@@ -69,15 +69,15 @@ instance decodeContactWhere :: DecodeJson ContactWhere
where where
decodeJson json = do decodeJson json = do
obj <- decodeJson json obj <- decodeJson json
organization <- obj .?? "organization" organization <- obj .:! "organization"
labTeamDepts <- obj .?? "labTeamDepts" labTeamDepts <- obj .:! "labTeamDepts"
role <- obj .?? "role" role <- obj .:! "role"
office <- obj .?? "office" office <- obj .:! "office"
country <- obj .?? "country" country <- obj .:! "country"
city <- obj .?? "city" city <- obj .:! "city"
touch <- obj .?? "touch" touch <- obj .:! "touch"
entry <- obj .?? "entry" entry <- obj .:! "entry"
exit <- obj .?? "exit" exit <- obj .:! "exit"
let o = fromMaybe [] organization let o = fromMaybe [] organization
let l = fromMaybe [] labTeamDepts let l = fromMaybe [] labTeamDepts
...@@ -96,9 +96,9 @@ instance decodeContactTouch :: DecodeJson ContactTouch ...@@ -96,9 +96,9 @@ instance decodeContactTouch :: DecodeJson ContactTouch
where where
decodeJson json = do decodeJson json = do
obj <- decodeJson json obj <- decodeJson json
mail <- obj .?? "mail" mail <- obj .:! "mail"
phone <- obj .?? "phone" phone <- obj .:! "phone"
url <- obj .?? "url" url <- obj .:! "url"
pure $ ContactTouch {mail, phone, url} pure $ ContactTouch {mail, phone, url}
...@@ -118,14 +118,14 @@ instance decodeHyperdataContact :: DecodeJson HyperdataContact ...@@ -118,14 +118,14 @@ instance decodeHyperdataContact :: DecodeJson HyperdataContact
where where
decodeJson json = do decodeJson json = do
obj <- decodeJson json obj <- decodeJson json
bdd <- obj .?? "bdd" bdd <- obj .:! "bdd"
who <- obj .?? "who" who <- obj .:! "who"
ou <- obj .?? "where" ou <- obj .:! "where"
title <- obj .?? "title" title <- obj .:! "title"
source <- obj .?? "source" source <- obj .:! "source"
lastValidation <- obj .?? "lastValidation" lastValidation <- obj .:! "lastValidation"
uniqId <- obj .?? "uniqId" uniqId <- obj .:! "uniqId"
uniqIdBdd <- obj .?? "uniqIdBdd" uniqIdBdd <- obj .:! "uniqIdBdd"
let ou' = fromMaybe [] ou let ou' = fromMaybe [] ou
...@@ -152,9 +152,9 @@ instance decodeUser :: DecodeJson Contact where ...@@ -152,9 +152,9 @@ instance decodeUser :: DecodeJson Contact where
obj <- decodeJson json obj <- decodeJson json
id <- obj .: "id" id <- obj .: "id"
typename <- obj .?| "typename" typename <- obj .?| "typename"
userId <- obj .?? "userId" userId <- obj .:! "userId"
parentId <- obj .?| "parentId" parentId <- obj .?| "parentId"
name <- obj .?? "name" name <- obj .:! "name"
date <- obj .?| "date" date <- obj .?| "date"
hyperdata <- obj .: "hyperdata" hyperdata <- obj .: "hyperdata"
pure $ Contact { id, typename, userId pure $ Contact { id, typename, userId
......
...@@ -11,7 +11,6 @@ import Gargantext.Components.Charts.Options.Series (seriesBarD1) ...@@ -11,7 +11,6 @@ import Gargantext.Components.Charts.Options.Series (seriesBarD1)
import Gargantext.Components.Charts.Options.Color (grey) import Gargantext.Components.Charts.Options.Color (grey)
import Gargantext.Components.Charts.Options.Font (itemStyle, mkTooltip, templateFormatter) import Gargantext.Components.Charts.Options.Font (itemStyle, mkTooltip, templateFormatter)
import Gargantext.Components.Charts.Options.Data (dataSerie) import Gargantext.Components.Charts.Options.Data (dataSerie)
import Gargantext.Ends (url)
import Gargantext.Hooks.Loader (useLoader) import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Components.Nodes.Corpus.Chart.Utils as U import Gargantext.Components.Nodes.Corpus.Chart.Utils as U
import Gargantext.Routes (SessionRoute(..)) import Gargantext.Routes (SessionRoute(..))
......
...@@ -15,7 +15,6 @@ import Gargantext.Components.Charts.Options.Series (Series, seriesScatterD2) ...@@ -15,7 +15,6 @@ import Gargantext.Components.Charts.Options.Series (Series, seriesScatterD2)
import Gargantext.Components.Charts.Options.Color (green, grey, red) import Gargantext.Components.Charts.Options.Color (green, grey, red)
import Gargantext.Components.Charts.Options.Font (itemStyle, mkTooltip, templateFormatter) import Gargantext.Components.Charts.Options.Font (itemStyle, mkTooltip, templateFormatter)
import Gargantext.Components.Charts.Options.Data (dataSerie) import Gargantext.Components.Charts.Options.Data (dataSerie)
import Gargantext.Ends (url)
import Gargantext.Hooks.Loader (useLoader) import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Components.Nodes.Corpus.Chart.Utils as U import Gargantext.Components.Nodes.Corpus.Chart.Utils as U
import Gargantext.Routes (SessionRoute(..)) import Gargantext.Routes (SessionRoute(..))
......
...@@ -15,7 +15,6 @@ import Gargantext.Components.Charts.Options.Series (seriesBarD1, seriesPieD1) ...@@ -15,7 +15,6 @@ import Gargantext.Components.Charts.Options.Series (seriesBarD1, seriesPieD1)
import Gargantext.Components.Charts.Options.Color (blue) import Gargantext.Components.Charts.Options.Color (blue)
import Gargantext.Components.Charts.Options.Font (itemStyle, mkTooltip, templateFormatter) import Gargantext.Components.Charts.Options.Font (itemStyle, mkTooltip, templateFormatter)
import Gargantext.Components.Charts.Options.Data (dataSerie) import Gargantext.Components.Charts.Options.Data (dataSerie)
import Gargantext.Ends (url)
import Gargantext.Hooks.Loader (useLoader) import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Components.Nodes.Corpus.Chart.Utils as U import Gargantext.Components.Nodes.Corpus.Chart.Utils as U
import Gargantext.Routes (SessionRoute(..)) import Gargantext.Routes (SessionRoute(..))
......
...@@ -10,7 +10,6 @@ import Reactix.DOM.HTML as H ...@@ -10,7 +10,6 @@ import Reactix.DOM.HTML as H
import Gargantext.Components.Charts.Options.ECharts (Options(..), chart, xAxis', yAxis') import Gargantext.Components.Charts.Options.ECharts (Options(..), chart, xAxis', yAxis')
import Gargantext.Components.Charts.Options.Series (TreeNode, Trees(..), mkTree) import Gargantext.Components.Charts.Options.Series (TreeNode, Trees(..), mkTree)
import Gargantext.Components.Charts.Options.Font (mkTooltip, templateFormatter) import Gargantext.Components.Charts.Options.Font (mkTooltip, templateFormatter)
import Gargantext.Ends (url)
import Gargantext.Hooks.Loader (useLoader) import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Components.Nodes.Corpus.Chart.Utils as U import Gargantext.Components.Nodes.Corpus.Chart.Utils as U
import Gargantext.Routes (SessionRoute(..)) import Gargantext.Routes (SessionRoute(..))
......
module Gargantext.Components.Search.Types where module Gargantext.Components.Search.Types where
import Prelude (class Eq, class Show, show, ($), (<>), map, (&&), (==)) import Prelude (class Eq, class Show, show, ($), (<>), map)
import Data.Set (Set) import Data.Set (Set)
import Data.Ord import Data.Ord
import Data.Set as Set import Data.Set as Set
import Data.Array (concat) import Data.Array (concat)
import Data.Argonaut (class EncodeJson, class DecodeJson, jsonEmptyObject, (:=), (~>), encodeJson) import Data.Argonaut (class EncodeJson, class DecodeJson, jsonEmptyObject, (:=), (~>), encodeJson)
import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Eq (genericEq)
import Data.Generic.Rep.Show (genericShow)
import Data.Maybe (Maybe(..), fromMaybe, maybe) import Data.Maybe (Maybe(..), fromMaybe, maybe)
import Data.Newtype (class Newtype) import Data.Newtype (class Newtype)
import Data.Tuple (Tuple) import Data.Tuple (Tuple)
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import Effect.Aff (Aff) import Effect.Aff (Aff)
import Gargantext.Ends (class ToUrl, backendUrl) import Gargantext.Ends (class ToUrl, backendUrl)
import Gargantext.Routes (SessionRoute(..)) import Gargantext.Sessions (Session(..), post)
import Gargantext.Sessions (Session(..), post, put) import Gargantext.Types (class ToQuery, toQuery)
import Gargantext.Types (class ToQuery, toQuery, NodeType(..))
import Gargantext.Utils (id) import Gargantext.Utils (id)
import URI.Extra.QueryPairs as QP import URI.Extra.QueryPairs as QP
import URI.Query as Q import URI.Query as Q
......
...@@ -30,7 +30,7 @@ tabsCpt = R.hooksComponent "G.C.Tab.tabs" cpt ...@@ -30,7 +30,7 @@ tabsCpt = R.hooksComponent "G.C.Tab.tabs" cpt
eq = index == selected eq = index == selected
className = "nav-item nav-link" <> (if eq then " active" else "") className = "nav-item nav-link" <> (if eq then " active" else "")
click e = setActiveTab (const index) click e = setActiveTab (const index)
item selected index (_ /\ cpt) = tab { selected, index } [ cpt ] item selected index (_ /\ cpt') = tab { selected, index } [ cpt' ]
-- TODO: document what these are (selection, item indices) -- TODO: document what these are (selection, item indices)
type TabProps = ( selected :: Int, index :: Int ) type TabProps = ( selected :: Int, index :: Int )
......
...@@ -7,8 +7,6 @@ import Data.Generic.Rep.Show (genericShow) ...@@ -7,8 +7,6 @@ import Data.Generic.Rep.Show (genericShow)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Data.Tuple (fst, snd) import Data.Tuple (fst, snd)
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import DOM.Simple.Console (log2)
import Effect (Effect)
import Reactix as R import Reactix as R
import Reactix.DOM.HTML as H import Reactix.DOM.HTML as H
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
......
...@@ -4,7 +4,6 @@ module Gargantext.Data.Array ...@@ -4,7 +4,6 @@ module Gargantext.Data.Array
import Data.Tuple (Tuple(..)) import Data.Tuple (Tuple(..))
import Data.Array as DA import Data.Array as DA
import Data.Maybe as DM
import Data.Sequence as DS import Data.Sequence as DS
......
module Gargantext.Hooks.Loader where module Gargantext.Hooks.Loader where
import Gargantext.Prelude import Gargantext.Prelude
import Data.Maybe (Maybe(..), isJust, isNothing, maybe, maybe') import Data.Maybe (Maybe(..), isJust, maybe)
import Data.Tuple (fst, Tuple(..)) import Data.Tuple (fst)
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import DOM.Simple.Console (log, log2)
import Effect.Aff (Aff) import Effect.Aff (Aff)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
import FFI.Simple (delay)
import Reactix as R import Reactix as R
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import Gargantext.Components.LoadingSpinner (loadingSpinner) import Gargantext.Components.LoadingSpinner (loadingSpinner)
......
...@@ -3,9 +3,9 @@ module Gargantext.Hooks.Sigmax.Sigma where ...@@ -3,9 +3,9 @@ module Gargantext.Hooks.Sigmax.Sigma where
import Prelude import Prelude
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.Nullable (notNull, null, Nullable) import Data.Nullable (notNull, null, Nullable)
import DOM.Simple.Console (log, log2) import DOM.Simple.Console (log2)
import DOM.Simple.Types (Element) import DOM.Simple.Types (Element)
import FFI.Simple (delay, (..)) import FFI.Simple ((..))
import Effect (Effect, foreachE) import Effect (Effect, foreachE)
import Effect.Timer (setTimeout) import Effect.Timer (setTimeout)
import Effect.Uncurried (EffectFn1, mkEffectFn1, runEffectFn1, EffectFn2, runEffectFn2, EffectFn3, runEffectFn3, EffectFn4, runEffectFn4) import Effect.Uncurried (EffectFn1, mkEffectFn1, runEffectFn1, EffectFn2, runEffectFn2, EffectFn3, runEffectFn3, EffectFn4, runEffectFn4)
...@@ -82,19 +82,19 @@ foreign import _killRenderer ...@@ -82,19 +82,19 @@ foreign import _killRenderer
(Either err Unit) (Either err Unit)
getRendererContainer :: Sigma -> Effect Element getRendererContainer :: Sigma -> Effect Element
getRendererContainer sigma = runEffectFn1 _getRendererContainer sigma getRendererContainer = runEffectFn1 _getRendererContainer
foreign import _getRendererContainer foreign import _getRendererContainer
:: EffectFn1 Sigma Element :: EffectFn1 Sigma Element
swapRendererContainer :: R.Ref (Nullable Element) -> Sigma -> Effect Unit swapRendererContainer :: R.Ref (Nullable Element) -> Sigma -> Effect Unit
swapRendererContainer ref sigma = do swapRendererContainer ref s = do
el <- getRendererContainer sigma el <- getRendererContainer s
log2 "[swapRendererContainer] el" el log2 "[swapRendererContainer] el" el
R.setRef ref $ notNull el R.setRef ref $ notNull el
setRendererContainer :: Sigma -> Element -> Effect Unit setRendererContainer :: Sigma -> Element -> Effect Unit
setRendererContainer sigma el = runEffectFn2 _setRendererContainer sigma el setRendererContainer = runEffectFn2 _setRendererContainer
foreign import _setRendererContainer foreign import _setRendererContainer
:: EffectFn2 Sigma Element Unit :: EffectFn2 Sigma Element Unit
...@@ -119,10 +119,10 @@ bind_ s e h = runEffectFn3 _bind s e (mkEffectFn1 h) ...@@ -119,10 +119,10 @@ bind_ s e h = runEffectFn3 _bind s e (mkEffectFn1 h)
foreign import _bind :: forall e. EffectFn3 Sigma String (EffectFn1 e Unit) Unit foreign import _bind :: forall e. EffectFn3 Sigma String (EffectFn1 e Unit) Unit
unbind_ :: forall e. Sigma -> String -> Effect Unit unbind_ :: Sigma -> String -> Effect Unit
unbind_ s e = runEffectFn2 _unbind s e unbind_ s e = runEffectFn2 _unbind s e
foreign import _unbind :: forall e. EffectFn2 Sigma String Unit foreign import _unbind :: EffectFn2 Sigma String Unit
forEachNode :: Sigma -> (Record Types.Node -> Effect Unit) -> Effect Unit forEachNode :: Sigma -> (Record Types.Node -> Effect Unit) -> Effect Unit
forEachNode s f = runEffectFn2 _forEachNode s (mkEffectFn1 f) forEachNode s f = runEffectFn2 _forEachNode s (mkEffectFn1 f)
...@@ -135,17 +135,17 @@ forEachEdge s f = runEffectFn2 _forEachEdge s (mkEffectFn1 f) ...@@ -135,17 +135,17 @@ forEachEdge s f = runEffectFn2 _forEachEdge s (mkEffectFn1 f)
foreign import _forEachEdge :: EffectFn2 Sigma (EffectFn1 (Record Types.Edge) Unit) Unit foreign import _forEachEdge :: EffectFn2 Sigma (EffectFn1 (Record Types.Edge) Unit) Unit
bindClickNode :: Sigma -> (Record Types.Node -> Effect Unit) -> Effect Unit bindClickNode :: Sigma -> (Record Types.Node -> Effect Unit) -> Effect Unit
bindClickNode sigma f = bind_ sigma "clickNode" $ \e -> do bindClickNode s f = bind_ s "clickNode" $ \e -> do
let node = e .. "data" .. "node" :: Record Types.Node let node = e .. "data" .. "node" :: Record Types.Node
f node f node
unbindClickNode :: Sigma -> Effect Unit unbindClickNode :: Sigma -> Effect Unit
unbindClickNode sigma = unbind_ sigma "clickNode" unbindClickNode s = unbind_ s "clickNode"
setSettings :: forall settings. Sigma -> settings -> Effect Unit setSettings :: forall settings. Sigma -> settings -> Effect Unit
setSettings sigma settings = do setSettings s settings = do
runEffectFn2 _setSettings sigma settings runEffectFn2 _setSettings s settings
refresh sigma refresh s
foreign import _setSettings :: forall settings. EffectFn2 Sigma settings Unit foreign import _setSettings :: forall settings. EffectFn2 Sigma settings Unit
...@@ -153,7 +153,7 @@ startForceAtlas2 :: forall settings. Sigma -> settings -> Effect Unit ...@@ -153,7 +153,7 @@ startForceAtlas2 :: forall settings. Sigma -> settings -> Effect Unit
startForceAtlas2 = runEffectFn2 _startForceAtlas2 startForceAtlas2 = runEffectFn2 _startForceAtlas2
restartForceAtlas2 :: Sigma -> Effect Unit restartForceAtlas2 :: Sigma -> Effect Unit
restartForceAtlas2 sigma = runEffectFn2 _startForceAtlas2 sigma null restartForceAtlas2 s = runEffectFn2 _startForceAtlas2 s null
stopForceAtlas2 :: Sigma -> Effect Unit stopForceAtlas2 :: Sigma -> Effect Unit
stopForceAtlas2 = runEffectFn1 _stopForceAtlas2 stopForceAtlas2 = runEffectFn1 _stopForceAtlas2
...@@ -170,15 +170,15 @@ foreign import _killForceAtlas2 :: EffectFn1 Sigma Unit ...@@ -170,15 +170,15 @@ foreign import _killForceAtlas2 :: EffectFn1 Sigma Unit
foreign import _isForceAtlas2Running :: EffectFn1 Sigma Boolean foreign import _isForceAtlas2Running :: EffectFn1 Sigma Boolean
refreshForceAtlas :: Sigma -> Effect Unit refreshForceAtlas :: Sigma -> Effect Unit
refreshForceAtlas sigma = do refreshForceAtlas s = do
isRunning <- isForceAtlas2Running sigma isRunning <- isForceAtlas2Running s
if isRunning then if isRunning then
pure unit pure unit
else do else do
_ <- setTimeout 100 $ do _ <- setTimeout 100 $ do
restartForceAtlas2 sigma restartForceAtlas2 s
_ <- setTimeout 100 $ _ <- setTimeout 100 $
stopForceAtlas2 sigma stopForceAtlas2 s
pure unit pure unit
pure unit pure unit
...@@ -224,6 +224,6 @@ goTo props cam = do ...@@ -224,6 +224,6 @@ goTo props cam = do
foreign import _goTo :: EffectFn2 CameraInstance (Record CameraProps) Unit foreign import _goTo :: EffectFn2 CameraInstance (Record CameraProps) Unit
goToAllCameras :: Sigma -> Record CameraProps -> Effect Unit goToAllCameras :: Sigma -> Record CameraProps -> Effect Unit
goToAllCameras sigma props = do goToAllCameras s props = do
cs <- cameras sigma cs <- cameras s
foreachE cs (goTo props) foreachE cs (goTo props)
...@@ -3,7 +3,7 @@ module Gargantext.Utils.Reactix where ...@@ -3,7 +3,7 @@ module Gargantext.Utils.Reactix where
import Prelude import Prelude
import DOM.Simple as DOM import DOM.Simple as DOM
import DOM.Simple.Console (log, log2) import DOM.Simple.Console (log2)
import DOM.Simple.Document (document) import DOM.Simple.Document (document)
import DOM.Simple.Element as Element import DOM.Simple.Element as Element
import DOM.Simple.Event as DE import DOM.Simple.Event as DE
......
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