Commit fca5b5e1 authored by James Laver's avatar James Laver

Fix most warnings and make code compile again

parent b15eeb79
...@@ -2,7 +2,7 @@ module Gargantext.Components.App where ...@@ -2,7 +2,7 @@ module Gargantext.Components.App where
import Prelude import Prelude
import Data.Array (fromFoldable) import Data.Array (fromFoldable)
import Data.Foldable (fold, intercalate) import Data.Foldable (intercalate)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Data.Tuple (fst, snd) import Data.Tuple (fst, snd)
import Reactix as R import Reactix as R
...@@ -29,7 +29,7 @@ import Gargantext.Router (router) ...@@ -29,7 +29,7 @@ import Gargantext.Router (router)
import Gargantext.Routes (AppRoute(..)) import Gargantext.Routes (AppRoute(..))
import Gargantext.Hooks.Router (useHashRouter) import Gargantext.Hooks.Router (useHashRouter)
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import Gargantext.Sessions (Session, Sessions, useSessions, unSessions) import Gargantext.Sessions (Sessions, useSessions, unSessions)
-- TODO (what does this mean?) -- TODO (what does this mean?)
-- tree changes endConfig state => trigger endConfig change in outerLayout, layoutFooter etc -- tree changes endConfig state => trigger endConfig change in outerLayout, layoutFooter etc
......
module Gargantext.Components.AutoUpdate where module Gargantext.Components.AutoUpdate where
import Control.Monad.Cont.Trans (lift)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Data.Traversable (traverse_) import Data.Traversable (traverse_)
import React as React import React as React
...@@ -8,12 +7,8 @@ import React (ReactClass, ReactElement, Children) ...@@ -8,12 +7,8 @@ import React (ReactClass, ReactElement, Children)
import React.DOM (div') import React.DOM (div')
import Gargantext.Prelude import Gargantext.Prelude
import Effect (Effect) import Effect (Effect)
import Effect.Aff (Aff)
import Effect.Timer (IntervalId, setInterval, clearInterval) import Effect.Timer (IntervalId, setInterval, clearInterval)
import Thermite (Render, PerformAction, simpleSpec, modifyState_,
createReactSpec, defaultRender)
data Action = Update data Action = Update
type PropsRow = type PropsRow =
......
...@@ -321,6 +321,8 @@ instance encodeJsonDDQuery :: EncodeJson DeleteDocumentQuery where ...@@ -321,6 +321,8 @@ instance encodeJsonDDQuery :: EncodeJson DeleteDocumentQuery where
encodeJson (DeleteDocumentQuery post) = encodeJson (DeleteDocumentQuery post) =
"documents" := post.documents ~> jsonEmptyObject "documents" := post.documents ~> jsonEmptyObject
deleteDocuments :: Int -> DeleteDocumentQuery -> Aff (Array Int) deleteDocuments :: Session -> Int -> DeleteDocumentQuery -> Aff (Array Int)
deleteDocuments nodeId = deleteWithBody (toUrl endConfigStateful Back Node (Just nodeId) <> "/documents") deleteDocuments session nodeId =
deleteWithBody $
(url session $ NodeAPI Node $ Just nodeId) <> "/documents"
...@@ -3,7 +3,7 @@ module Gargantext.Components.Forms where ...@@ -3,7 +3,7 @@ module Gargantext.Components.Forms where
import Reactix as R import Reactix as R
import Reactix.DOM.HTML as H import Reactix.DOM.HTML as H
clearfix :: _ -> R.Element clearfix :: {} -> R.Element
clearfix _ = H.div {className: "clearfix"} [] clearfix _ = H.div {className: "clearfix"} []
formGroup :: Array R.Element -> R.Element formGroup :: Array R.Element -> R.Element
......
module Gargantext.Components.GraphExplorer.Types where module Gargantext.Components.GraphExplorer.Types where
import Prelude import Prelude
import Partial.Unsafe (unsafePartial)
import Data.Argonaut (class DecodeJson, decodeJson, (.:)) import Data.Argonaut (class DecodeJson, decodeJson, (.:))
import Data.Array ((!!), length) 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 Reactix as R import Partial.Unsafe (unsafePartial)
import Thermite (PerformAction)
newtype Node = Node newtype Node = Node
{ id_ :: String { id_ :: String
...@@ -175,11 +171,8 @@ instance ordLegend :: Ord Legend where ...@@ -175,11 +171,8 @@ instance ordLegend :: Ord Legend where
compare (Legend l1) (Legend l2) = compare l1.id_ l2.id_ compare (Legend l1) (Legend l2) = compare l1.id_ l2.id_
getLegendData :: GraphData -> Array Legend getLegendData :: GraphData -> Array Legend
getLegendData (GraphData {nodes, edges, metaData}) = getLegend metaData getLegendData (GraphData {metaData: Just (MetaData {legend})}) = legend
where getLegendData _ = []
getLegend (Just (MetaData {legend})) = legend
getLegend Nothing = []
defaultPalette :: Array String defaultPalette :: Array String
defaultPalette = ["#5fa571","#ab9ba2","#da876d","#bdd3ff","#b399df","#ffdfed","#33c8f3","#739e9a","#caeca3","#f6f7e5","#f9bcca","#ccb069","#c9ffde","#c58683","#6c9eb0","#ffd3cf","#ccffc7","#52a1b0","#d2ecff","#99fffe","#9295ae","#5ea38b","#fff0b3","#d99e68"] defaultPalette = ["#5fa571","#ab9ba2","#da876d","#bdd3ff","#b399df","#ffdfed","#33c8f3","#739e9a","#caeca3","#f6f7e5","#f9bcca","#ccb069","#c9ffde","#c58683","#6c9eb0","#ffd3cf","#ccffc7","#52a1b0","#d2ecff","#99fffe","#9295ae","#5ea38b","#fff0b3","#d99e68"]
......
...@@ -116,7 +116,7 @@ formCpt = R.hooksComponent "G.C.Login.form" cpt where ...@@ -116,7 +116,7 @@ formCpt = R.hooksComponent "G.C.Login.form" cpt where
, H.div {} , H.div {}
[ csrfTokenInput {} [ csrfTokenInput {}
, formGroup [ H.p {} [ H.text (fst error) ], usernameInput username ] , formGroup [ H.p {} [ H.text (fst error) ], usernameInput username ]
, formGroup [ passwordInput password, clearfix [] ] , formGroup [ passwordInput password, clearfix {} ]
, center , center
[ H.label {} [ H.label {}
[ H.div {className: "checkbox"} [ H.div {className: "checkbox"}
......
module Gargantext.Components.NgramsTable where module Gargantext.Components.NgramsTable where
import Prelude import Prelude
( class Show, Unit, bind, const, discard, identity, map, mempty, not
, pure, show, unit, (#), ($), (&&), (+), (/=), (<$>), (<<<), (<>), (=<<)
, (==), (||) )
import Data.Array as A import Data.Array as A
import Data.Lens (to, view, (%~), (.~), (^.), (^..)) import Data.Lens (to, view, (%~), (.~), (^.), (^..))
import Data.Lens.Common (_Just) import Data.Lens.Common (_Just)
...@@ -16,21 +19,27 @@ import Data.Monoid.Additive (Additive(..)) ...@@ -16,21 +19,27 @@ import Data.Monoid.Additive (Additive(..))
import Data.Ord.Down (Down(..)) import Data.Ord.Down (Down(..))
import Data.Symbol (SProxy(..)) import Data.Symbol (SProxy(..))
import Data.Tuple (Tuple(..), snd) import Data.Tuple (Tuple(..), snd)
import Data.Tuple.Nested ((/\))
import Effect (Effect) import Effect (Effect)
import Reactix as R import Reactix as R
import Reactix.DOM.HTML as H import Reactix.DOM.HTML as H
import React (ReactElement) import React (ReactElement)
import React.DOM (a, button, div, h2, i, input, li, option, p, select, span, table, tbody, text, thead, ul) import React.DOM (a, i, input, li, span, text, ul)
import React.DOM.Props (_id, _type, checked, className, name, onChange, onClick, onInput, placeholder, style, value) import React.DOM.Props (_type, checked, className, onChange, onClick, style)
import React.DOM.Props as DOM import React.DOM.Props as DOM
import Thermite (PerformAction, Render, Spec, defaultPerformAction, modifyState_, simpleSpec, createClass) import Thermite (PerformAction, Render, Spec, modifyState_, simpleSpec)
import Gargantext.Types
import Gargantext.Types (TermList(..), OrderBy(..), TabType, CTabNgramType(..), readTermList, readTermSize, termLists, termSizes) ( CTabNgramType, OrderBy(..), TabType, TermList(..), readTermList
, readTermSize, termLists, termSizes)
import Gargantext.Components.AutoUpdate (autoUpdateElt) import Gargantext.Components.AutoUpdate (autoUpdateElt)
import Gargantext.Components.NgramsTable.Core import Gargantext.Components.NgramsTable.Core
( CoreState, LoadedNgramsTableProps, NgramsElement(..), NgramsPatch(..)
, NgramsTable, NgramsTerm, PageParams, Replace(..), Versioned(..)
, VersionedNgramsTable, _NgramsElement, _NgramsTable, _children
, _list, _ngrams, _occurrences, _root, addNewNgram, applyNgramsTablePatch
, applyPatchSet, commitPatch, convOrderBy, initialPageParams, loadNgramsTable
, patchSetFromMap, replace, singletonNgramsTablePatch )
import Gargantext.Components.Table as T import Gargantext.Components.Table as T
import Gargantext.Hooks.Loader (useLoader, useLoader2) import Gargantext.Hooks.Loader (useLoader2)
import Gargantext.Sessions (Session) import Gargantext.Sessions (Session)
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
......
module Gargantext.Components.Tab where module Gargantext.Components.Tab where
import Prelude hiding (div) import Prelude hiding (div)
import Data.Array (fold)
import Data.FunctorWithIndex (mapWithIndex) import Data.FunctorWithIndex (mapWithIndex)
import Data.Tuple (Tuple(..)) import Data.Tuple (Tuple)
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import Reactix as R import Reactix as R
import Reactix.DOM.HTML as H import Reactix.DOM.HTML as H
......
...@@ -4,7 +4,7 @@ import Prelude hiding (div) ...@@ -4,7 +4,7 @@ import Prelude hiding (div)
import DOM.Simple.Console (log2) import DOM.Simple.Console (log2)
import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, jsonEmptyObject, (.:), (:=), (~>)) import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, jsonEmptyObject, (.:), (:=), (~>))
import Data.Array (filter, head) import Data.Array (filter)
import Data.Generic.Rep (class Generic) import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Eq (genericEq) import Data.Generic.Rep.Eq (genericEq)
import Data.Generic.Rep.Show (genericShow) import Data.Generic.Rep.Show (genericShow)
......
module Gargantext.Hooks.Sigmax.Sigma where module Gargantext.Hooks.Sigmax.Sigma where
import Prelude import Prelude
import Data.Array (head)
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.Maybe (Maybe(..))
import Data.Nullable (null) import Data.Nullable (null)
import Data.Unit (Unit)
import DOM.Simple.Console (log, log2)
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)
import FFI.Simple.Objects (named, getProperty)
import Type.Row (class Union) import Type.Row (class Union)
foreign import data Sigma :: Type foreign import data Sigma :: Type
......
module Gargantext.Hooks.Sigmax.Types where module Gargantext.Hooks.Sigmax.Types where
import Gargantext.Prelude
import Data.Generic.Rep (class Generic)
import Data.Maybe (Maybe)
import Data.Sequence as Seq
import Data.Sequence (Seq) import Data.Sequence (Seq)
import DOM.Simple.Types (Element) import DOM.Simple.Types (Element)
import Reactix as R
import Prim.RowList (RowToList)
newtype Graph n e = Graph { nodes :: Seq {|n}, edges :: Seq {|e} } newtype Graph n e = Graph { nodes :: Seq {|n}, edges :: Seq {|e} }
......
...@@ -19,7 +19,7 @@ import Gargantext.Hooks.Loader (useLoader) ...@@ -19,7 +19,7 @@ import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Pages.Annuaire.User.Contacts.Types import Gargantext.Pages.Annuaire.User.Contacts.Types
( Contact(..), ContactData, ContactTouch(..), ContactWhere(..) ( Contact(..), ContactData, ContactTouch(..), ContactWhere(..)
, ContactWho(..), HyperData(..), HyperdataContact(..) ) , ContactWho(..), HyperData(..), HyperdataContact(..) )
import Gargantext.Pages.Annuaire.User.Contacts.Tabs.Specs as Tabs import Gargantext.Pages.Annuaire.User.Contacts.Tabs as Tabs
import Gargantext.Routes (SessionRoute(..)) import Gargantext.Routes (SessionRoute(..))
import Gargantext.Sessions (Session) import Gargantext.Sessions (Session)
import Gargantext.Types (NodeType(..)) import Gargantext.Types (NodeType(..))
......
-- TODO copy of Gargantext.Pages.Corpus.Tabs.Specs -- TODO copy of Gargantext.Pages.Corpus.Tabs.Specs
module Gargantext.Pages.Annuaire.User.Contacts.Tabs.Specs where module Gargantext.Pages.Annuaire.User.Contacts.Tabs where
import Prelude hiding (div) import Prelude hiding (div)
import Data.Generic.Rep (class Generic) import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Show (genericShow) import Data.Generic.Rep.Show (genericShow)
import Data.List (fromFoldable)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Data.Tuple (Tuple(..), fst) import Data.Tuple (fst)
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import Reactix as R
import Gargantext.Components.DocsTable as DT import Gargantext.Components.DocsTable as DT
import Gargantext.Components.NgramsTable as NT import Gargantext.Components.NgramsTable as NT
import Gargantext.Components.Tab as Tab import Gargantext.Components.Tab as Tab
import Gargantext.Pages.Annuaire.User.Contacts.Types (ContactData) import Gargantext.Pages.Annuaire.User.Contacts.Types (ContactData)
import Gargantext.Sessions (Session) import Gargantext.Sessions (Session)
import Gargantext.Types (TabType(..), TabSubType(..), CTabNgramType(..), PTabNgramType(..)) import Gargantext.Types (TabType(..), TabSubType(..), CTabNgramType(..), PTabNgramType(..))
import Gargantext.Utils.Reactix as R2
import Reactix as R
import Reactix.DOM.HTML as H
data Mode = Patents | Books | Communication data Mode = Patents | Books | Communication
......
...@@ -2,11 +2,9 @@ module Gargantext.Pages.Annuaire.User.Contacts.Types where ...@@ -2,11 +2,9 @@ module Gargantext.Pages.Annuaire.User.Contacts.Types where
import Prelude import Prelude
import Data.Argonaut (class DecodeJson, decodeJson, (.:), (.:!), (.?), (.??)) import Data.Argonaut (class DecodeJson, decodeJson, (.:), (.:!))
import Data.Either (Either(..)) import Data.Maybe (Maybe, fromMaybe)
import Data.Lens (Lens', Prism', lens, prism) import Data.Map (Map)
import Data.Maybe (Maybe(..), maybe, fromMaybe)
import Data.Map (Map(..))
import Gargantext.Utils.DecodeMaybe ((.?|)) import Gargantext.Utils.DecodeMaybe ((.?|))
import Data.Newtype (class Newtype) import Data.Newtype (class Newtype)
......
...@@ -105,7 +105,7 @@ jumboTitle (LandingData hd) b = ...@@ -105,7 +105,7 @@ jumboTitle (LandingData hd) b =
true -> "jumbotron" true -> "jumbotron"
false -> "" false -> ""
imageEnter :: LandingData -> _ -> R.Element imageEnter :: forall t. LandingData -> t -> R.Element
imageEnter (LandingData hd) action = imageEnter (LandingData hd) action =
H.div {className: "row"} H.div {className: "row"}
[ H.div {className: "col-md-offset-5 col-md-6 content"} [ H.div {className: "col-md-offset-5 col-md-6 content"}
......
module Gargantext.Pages.Lists.Tabs where module Gargantext.Pages.Lists.Tabs where
import Data.Argonaut (class DecodeJson, decodeJson, (.?), (.??)) import Prelude
import Data.Argonaut (class DecodeJson, decodeJson, (.:), (.:!))
import Data.Generic.Rep (class Generic) import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Show (genericShow) import Data.Generic.Rep.Show (genericShow)
import Data.List (fromFoldable)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Data.Tuple (Tuple(..))
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import Reactix as R import Reactix as R
import Reactix.DOM.HTML as H
import Unsafe.Coerce (unsafeCoerce)
import Gargantext.Prelude
import Gargantext.Components.Charts.Options.ECharts (chart) as ECharts
import Gargantext.Components.DocsTable as DT
import Gargantext.Components.Loader as Loader
import Gargantext.Components.NgramsTable as NT import Gargantext.Components.NgramsTable as NT
import Gargantext.Components.Node (NodePoly(..)) import Gargantext.Components.Node (NodePoly(..))
import Gargantext.Components.Tab as Tab import Gargantext.Components.Tab as Tab
import Gargantext.Pages.Corpus.Chart.Histo (histo)
import Gargantext.Pages.Corpus.Chart.Metrics (metrics) import Gargantext.Pages.Corpus.Chart.Metrics (metrics)
import Gargantext.Pages.Corpus.Chart.Pie (pie, bar) import Gargantext.Pages.Corpus.Chart.Pie (pie, bar)
import Gargantext.Pages.Corpus.Chart.Tree (tree) import Gargantext.Pages.Corpus.Chart.Tree (tree)
import Gargantext.Sessions (Session) import Gargantext.Sessions (Session)
import Gargantext.Types (CTabNgramType(..), TabType(..), TabSubType(..)) import Gargantext.Types (CTabNgramType(..), TabType(..), TabSubType(..))
import Gargantext.Utils.Reactix as R2
data Mode = Authors | Sources | Institutes | Terms data Mode = Authors | Sources | Institutes | Terms
...@@ -92,6 +83,7 @@ newtype CorpusInfo = ...@@ -92,6 +83,7 @@ newtype CorpusInfo =
, chart :: (Maybe (Array Number)) , chart :: (Maybe (Array Number))
, totalRecords :: Int } , totalRecords :: Int }
hyperdataDefault :: CorpusInfo
hyperdataDefault = hyperdataDefault =
CorpusInfo CorpusInfo
{ title : "Default title" { title : "Default title"
...@@ -115,11 +107,11 @@ corpusInfoDefault = ...@@ -115,11 +107,11 @@ corpusInfoDefault =
instance decodeCorpusInfo :: DecodeJson CorpusInfo where instance decodeCorpusInfo :: DecodeJson CorpusInfo where
decodeJson json = do decodeJson json = do
obj <- decodeJson json obj <- decodeJson json
title <- obj .? "title" title <- obj .: "title"
desc <- obj .? "desc" desc <- obj .: "desc"
query <- obj .? "query" query <- obj .: "query"
authors <- obj .? "authors" authors <- obj .: "authors"
chart <- obj .?? "chart" chart <- obj .:! "chart"
let totalRecords = 47361 -- TODO let totalRecords = 47361 -- TODO
pure $ CorpusInfo {title, desc, query, authors, chart, totalRecords} pure $ CorpusInfo {title, desc, query, authors, chart, totalRecords}
......
module Gargantext.Prelude (module Prelude, logs) module Gargantext.Prelude (module Prelude, logs)
where where
import Prelude hiding (div) import Prelude (class Applicative, class Apply, class Bind, class BooleanAlgebra, class Bounded, class Category, class CommutativeRing, class Discard, class DivisionRing, class Eq, class EuclideanRing, class Field, class Functor, class HeytingAlgebra, class Monad, class Monoid, class Ord, class Ring, class Semigroup, class Semigroupoid, class Semiring, class Show, type (~>), Ordering(..), Unit, Void, absurd, add, ap, append, apply, between, bind, bottom, clamp, compare, comparing, compose, conj, const, degree, discard, disj, eq, flap, flip, gcd, identity, ifM, join, lcm, liftA1, liftM1, map, max, mempty, min, mod, mul, negate, not, notEq, one, otherwise, pure, recip, show, sub, top, unit, unless, unlessM, void, when, whenM, zero, (#), ($), ($>), (&&), (*), (*>), (+), (-), (/), (/=), (<), (<#>), (<$), (<$>), (<*), (<*>), (<<<), (<=), (<=<), (<>), (<@>), (=<<), (==), (>), (>=), (>=>), (>>=), (>>>), (||))
import Effect.Console (log) import Effect.Console (log)
import Effect.Class -- (MonadEffect(), liftEffect) -- TODO fix import import Effect.Class (MonadEffect, liftEffect)
logs:: forall message effect. logs:: forall message effect.
......
...@@ -2,7 +2,7 @@ module Gargantext.Routes where ...@@ -2,7 +2,7 @@ module Gargantext.Routes where
import Prelude import Prelude
import Data.Maybe (Maybe) import Data.Maybe (Maybe)
import Gargantext.Types import Gargantext.Types (ChartOpts, CorpusMetricOpts, Id, Limit, ListId, NgramsGetOpts, NodeType, Offset, OrderBy, SearchOpts, TabType, TermList)
data AppRoute data AppRoute
= Home = Home
......
...@@ -12,7 +12,7 @@ import Effect.Aff (Aff) ...@@ -12,7 +12,7 @@ import Effect.Aff (Aff)
import Reactix as R import Reactix as R
import Web.HTML (window) import Web.HTML (window)
import Web.HTML.Window (localStorage) import Web.HTML.Window (localStorage)
import Web.Storage.Storage (getItem, setItem, removeItem) import Web.Storage.Storage (removeItem) -- (getItem, setItem, removeItem)
import Gargantext.Components.Login.Types import Gargantext.Components.Login.Types
(AuthRequest(..), AuthResponse(..), AuthInvalid(..), AuthData(..)) (AuthRequest(..), AuthResponse(..), AuthInvalid(..), AuthData(..))
import Gargantext.Config.REST (post) import Gargantext.Config.REST (post)
......
'use strict';
exports._wordRegex = /[a-z]+/gi; exports._wordRegex = /[a-z]+/gi;
exports._cloneRegex = function(r) { return new RegExp(r.source, r.flags); };
exports._getRegexLastIndex = function(r) { return r.lastIndex; };
exports._execRegex = function(r, s) { return r.exec(s); };
...@@ -4,17 +4,13 @@ ...@@ -4,17 +4,13 @@
-- | for highlighting purposes -- | for highlighting purposes
module Gargantext.Text.BreakWords (BrokenWord(..), breakWords) where module Gargantext.Text.BreakWords (BrokenWord(..), breakWords) where
import Prelude import Prelude (Unit, discard, negate, otherwise, pure, ($), (-), (<<<), (==), (>>=))
import Data.Traversable (traverse_) import Data.Traversable (traverse_)
import Effect (Effect) import Effect (Effect)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Data.Unit (Unit, unit)
import Effect.Uncurried (EffectFn2, runEffectFn2)
import Data.Function.Uncurried (Fn1, runFn1)
import Data.String.CodeUnits (length, slice) -- TODO: double check i'm the right choice import Data.String.CodeUnits (length, slice) -- TODO: double check i'm the right choice
import Data.Nullable (Nullable, toMaybe)
import Data.String.Regex (Regex) import Data.String.Regex (Regex)
import Gargantext.Utils.Regex import Gargantext.Utils.Regex (cloneRegex, execRegex, getRegexLastIndex)
import Gargantext.Utils.Array (push) import Gargantext.Utils.Array (push)
data BrokenWord = Word String | Space String data BrokenWord = Word String | Space String
...@@ -31,8 +27,8 @@ breakWords s = loop $ break s ...@@ -31,8 +27,8 @@ breakWords s = loop $ break s
-- Returns whether to continue -- Returns whether to continue
breakNext :: Breaking -> Effect Boolean breakNext :: Breaking -> Effect Boolean
breakNext b = checkStatic b $ lastIndex b breakNext b = checkStatic (lastIndex b)
where checkStatic b origin where checkStatic origin
| origin == length b.source = pure false | origin == length b.source = pure false
| otherwise = search b >>= next' origin | otherwise = search b >>= next' origin
next' origin Nothing = finish b origin next' origin Nothing = finish b origin
......
...@@ -2,7 +2,7 @@ module Gargantext.Types where ...@@ -2,7 +2,7 @@ module Gargantext.Types where
import Prelude import Prelude
import Data.Argonaut ( class DecodeJson, decodeJson, class EncodeJson, encodeJson, (:=), (~>), jsonEmptyObject) import Data.Argonaut ( class DecodeJson, decodeJson, class EncodeJson, encodeJson, (:=), (~>), jsonEmptyObject)
import Data.Maybe (Maybe(..), maybe, fromJust) import Data.Maybe (Maybe(..), maybe)
import Data.Either (Either(..)) import Data.Either (Either(..))
import Prim.Row (class Union) import Prim.Row (class Union)
import URI.Query (Query) import URI.Query (Query)
......
...@@ -28,7 +28,6 @@ import Data.Enum (fromEnum) ...@@ -28,7 +28,6 @@ import Data.Enum (fromEnum)
import Data.Foldable (class Foldable, minimum, foldl) import Data.Foldable (class Foldable, minimum, foldl)
import Data.Int (quot) import Data.Int (quot)
import Data.List as L import Data.List as L
import Data.List (List)
import Data.Map as M import Data.Map as M
import Data.Maybe (Maybe(..), isJust) import Data.Maybe (Maybe(..), isJust)
import Data.String as S import Data.String as S
......
module Gargantext.Utils.Range where module Gargantext.Utils.Range where
import Prelude import Prelude hiding (clamp)
import Data.Newtype (class Newtype) import Data.Newtype (class Newtype)
import Data.Ord (class Ord)
class Range r v where class Range r v where
clamp :: r -> v -> v clamp :: r -> v -> v
......
module Gargantext.Utils.React where
import Prelude
import Data.Array ( (!!) )
import Data.FoldableWithIndex ( foldMapWithIndex )
import Data.Maybe ( fromMaybe )
import React ( ReactElement, Children )
import Reactix as R
import Unsafe.Coerce ( unsafeCoerce )
-- TODO: Upgrade thermite and reapply our changes or upstream them and get rid of this
type WithChildren props = { children :: Children | props }
wrap :: (Array ReactElement -> ReactElement) -> ReactElement -> ReactElement
wrap f e = f [e]
-- many ::
-- forall props extra state action.
-- Spec state { extra :: extra | WithIndex props } action
-- -> Spec state { props :: (Array props), extra :: extra } action
-- many items spec = Spec { performAction, render }
-- where
-- -- performAction :: PerformAction
-- render d p s c = foldMapWithIndex childSpec p.props
-- childSpec props i = cmapProps (\_ -> props { index = i }) spec
-- many
-- :: forall props state action
-- . (Int -> Spec state props action)
-- -> Spec state (List props) (Tuple Int action)
-- foreach f = Spec { performAction: performAction
-- , render: render
-- }
-- where
-- performAction :: PerformAction (List state) props (Tuple Int action)
-- performAction (Tuple i a) p sts =
-- for_ (sts !! i) \st ->
-- case f i of
-- Spec s -> forever (transform (_ >>= (_ !! i)))
-- `transformCoTransformL` s.performAction a p st
-- `transformCoTransformR` forever (transform (modifying i))
-- where
-- modifying :: Int -> (state -> state) -> List state -> List state
-- modifying j g sts' = fromMaybe sts' (modifyAt j g sts')
-- render :: Render (List state) props (Tuple Int action)
-- render k p sts _ = foldWithIndex (\i st els -> case f i of Spec s -> els <> s.render (k <<< Tuple i) p st []) sts []
-- foldWithIndex :: forall a r. (Int -> a -> r -> r) -> List a -> r -> r
-- foldWithIndex g = go 0
-- where
-- go _ Nil r = r
-- go i (Cons x xs) r = go (i + 1) xs (g i x r)
module Gargantext.Utils.Reactix where
import Prelude
import Data.Maybe (Maybe(..))
import Data.Nullable (Nullable, null, toMaybe)
import Data.Tuple (Tuple)
import Data.Tuple.Nested ((/\))
import DOM.Simple as DOM
import DOM.Simple.Document (document)
import DOM.Simple.Event as DE
import DOM.Simple.Element as Element
import Effect (Effect)
import Effect.Class (liftEffect)
import Effect.Aff (Aff, launchAff, launchAff_, killFiber)
import Effect.Exception (error)
import Effect.Uncurried (EffectFn1, mkEffectFn1, mkEffectFn2)
import FFI.Simple ((...), defineProperty, delay, args3)
import React (class ReactPropFields, Children, ReactClass, ReactElement)
import React as React
import Reactix as R
import Reactix.DOM.HTML (ElemFactory, text)
import Reactix.React (react, createDOMElement)
import Reactix.SyntheticEvent as RE
import Reactix.Utils (currySecond, hook, tuple)
import Thermite (Spec, simpleSpec, Render, defaultPerformAction)
import Unsafe.Coerce (unsafeCoerce)
newtype Point = Point { x :: Number, y :: Number }
-- a setter function, for useState
type Setter t = (t -> t) -> Effect Unit
-- a reducer function living in effector, for useReductor
type Actor t a = (t -> a -> Effect t)
-- | Turns a ReactElement into aReactix Element
-- | buff (v.) to polish
buff :: ReactElement -> R.Element
buff = unsafeCoerce
-- | Turns a Reactix Element into a ReactElement.
-- | scuff (v.) to spoil the gloss or finish of.
scuff :: R.Element -> ReactElement
scuff = unsafeCoerce
class ToElement a where
toElement :: a -> R.Element
instance toElementElement :: ToElement R.Element where
toElement = identity
instance toElementReactElement :: ToElement ReactElement where
toElement = buff
instance toElementArray :: ToElement a => ToElement (Array a) where
toElement = R.fragment <<< map toElement
{-
instance isReactElementElement :: IsReactElement R.Element where
toElement = scuff
-}
elSpec :: forall component props
. R.IsComponent component props (Array R.Element)
=> component -> Spec {} (Record props) Void
elSpec cpt = simpleSpec defaultPerformAction render
where
render :: Render {} (Record props) Void
render _ props _ children = [scuff $ R.createElement cpt props (buff <$> children)]
createElement' :: forall required given
. ReactPropFields required given
=> ReactClass { children :: Children | required }
-> Record given -> Array R.Element -> R.Element
createElement' reactClass props children =
buff $ React.createElement reactClass props $ scuff <$> children
{-
instance isComponentReactClass
:: R.IsComponent (ReactClass { children :: Children
| props
}) props (Array R.Element) where
createElement reactClass props children =
React.createElement reactClass props children
-}
-- | Turns an aff into a useEffect-compatible Effect (Effect Unit)
affEffect :: forall a. String -> Aff a -> Effect (Effect Unit)
affEffect errmsg aff = do
fiber <- launchAff aff
pure $ launchAff_ $ killFiber (error errmsg) fiber
mousePosition :: RE.SyntheticEvent DE.MouseEvent -> Point
mousePosition e = Point { x: RE.clientX e, y: RE.clientY e }
domMousePosition :: DE.MouseEvent -> Point
domMousePosition = mousePosition <<< unsafeCoerce
-- | This is naughty, it quietly mutates the input and returns it
named :: forall o. String -> o -> o
named = flip $ defineProperty "name"
overState :: forall t. (t -> t) -> R.State t -> Effect Unit
overState f (_state /\ setState) = setState f
select :: ElemFactory
select = createDOMElement "select"
menu :: ElemFactory
menu = createDOMElement "menu"
effToggler :: forall e. R.State Boolean -> EffectFn1 e Unit
effToggler (value /\ setValue) = mkEffectFn1 $ \e -> setValue $ const $ not value
unsafeEventValue :: forall event. event -> String
unsafeEventValue e = (unsafeCoerce e).target.value
nullRef :: forall t. R.Hooks (R.Ref (Nullable t))
nullRef = R.useRef null
nothingRef :: forall t. R.Hooks (R.Ref (Maybe t))
nothingRef = R.useRef Nothing
useLayoutEffect1' :: forall a. a -> (Unit -> Effect Unit) -> R.Hooks Unit
useLayoutEffect1' a f = R.useLayoutEffect1 a $ do
liftEffect $ f unit
pure $ pure unit
useLayoutRef :: forall a b. (a -> b) -> b -> R.Ref a -> R.Hooks (R.Ref b)
useLayoutRef fn init ref = do
new <- R.useRef init
let old = R.readRef ref
useLayoutEffect1' old $ \_ -> R.setRef new (fn old)
pure new
usePositionRef :: R.Ref (Nullable DOM.Element) -> R.Hooks (R.Ref (Maybe DOM.DOMRect))
usePositionRef = useLayoutRef (map Element.boundingRect <<< toMaybe) Nothing
readPositionRef :: R.Ref (Nullable DOM.Element) -> Maybe DOM.DOMRect
readPositionRef el = do
let posRef = R.readRef el
Element.boundingRect <$> toMaybe posRef
unsafeEventTarget :: forall event. event -> DOM.Element
unsafeEventTarget e = (unsafeCoerce e).target
getElementById :: String -> Effect (Maybe DOM.Element)
getElementById = (flip delay) h
where
h id = pure $ toMaybe $ document ... "getElementById" $ [id]
-- We just assume it works, so make sure it's in the html
getPortalHost :: R.Hooks DOM.Element
getPortalHost = R.unsafeHooksEffect $ delay unit $ \_ -> pure $ document ... "getElementById" $ ["portal"]
useLayoutEffectOnce :: Effect (Effect Unit) -> R.Hooks Unit
useLayoutEffectOnce e = R.unsafeUseLayoutEffect e []
singleParent :: forall props. R.Component props -> Record props -> R.Element -> R.Element
singleParent cpt props child = R.createElement cpt props [ child ]
childless :: forall props. R.Component props -> Record props -> R.Element
childless cpt props = R.createElement cpt props []
showText :: forall s. Show s => s -> R.Element
showText = text <<< show
----- Reactix's new effectful reducer: sneak-peek because anoe wants to demo on tuesday
-- | Like a reducer, but lives in Effect
type Reductor state action = Tuple state (action -> Effect Unit)
-- | Like useReductor, but lives in Effect
useReductor :: forall s a i. Actor s a -> (i -> Effect s) -> i -> R.Hooks (Reductor s a)
useReductor f i j =
hook $ \_ ->
pure $ currySecond $ tuple $ react ... "useReducer" $ args3 (mkEffectFn2 f) j (mkEffectFn1 i)
-- | Like `useReductor`, but takes an initial state instead of an
-- | initialiser function and argument
useReductor' :: forall s a. Actor s a -> s -> R.Hooks (Reductor s a)
useReductor' r = useReductor r pure
...@@ -3,7 +3,7 @@ module Gargantext.Utils.Regex where ...@@ -3,7 +3,7 @@ module Gargantext.Utils.Regex where
import Effect (Effect) import Effect (Effect)
import Prelude ((<$>)) import Prelude ((<$>))
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe)
import Effect.Uncurried (EffectFn2, runEffectFn2) import Effect.Uncurried (EffectFn2, runEffectFn2)
import Data.Function.Uncurried (Fn1, runFn1) import Data.Function.Uncurried (Fn1, runFn1)
import Data.Nullable (Nullable, toMaybe) import Data.Nullable (Nullable, toMaybe)
......
module Gargantext.Utils.Selection where module Gargantext.Utils.Selection where
import Prelude import Prelude
import Data.Maybe (Maybe, fromMaybe, maybe) import Data.Maybe (Maybe, maybe)
import Data.Nullable (Nullable, toMaybe) import Data.Nullable (Nullable, toMaybe)
import DOM.Simple.Types (Element, DOMRect) import DOM.Simple.Types (Element, DOMRect)
import DOM.Simple.Element as Element import DOM.Simple.Element as Element
......
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