Commit 2e80d87a authored by Alexandre Delanoë's avatar Alexandre Delanoë

Merge branch 'factoring' of...

Merge branch 'factoring' of ssh://gitlab.iscpif.fr:20022/gargantext/purescript-gargantext into factoring
parents 7f5c2324 191dfe36
module Gargantext.Chart where module Gargantext.Components.Charts.Charts where
import Prelude (($), (<<<), (<$>)) import Prelude hiding (min)
import CSS (Color, white) import CSS (Color, white)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
......
module Gargantext.Charts.Color module Gargantext.Components.Charts.Options.Color
( ChartColor() ( ChartColor()
, chartColor , chartColor
, transparent , transparent
) where ) where
import Prelude ((<<<)) import Prelude
import CSS (Color, toHexString) import CSS (Color, toHexString)
import Color (rgba) import Color (rgba)
......
module Gargantext.Charts.Data where module Gargantext.Components.Charts.Options.Data where
import Gargantext.Charts.Font (TextStyle, Icon) import Gargantext.Components.Charts.Options.Font (TextStyle, Icon)
import Prelude ((<<<))
import Unsafe.Coerce (unsafeCoerce)
type DataN = type DataN =
{ name :: String { name :: String
......
module Gargantext.Charts.ECharts where module Gargantext.Components.Charts.Options.ECharts where
import Prelude (($), map, class Show, show, (<<<), (==)) import Prelude
import Data.Array (length)
import CSS (black, blue, italic, violet, white, yellow) import CSS (black, italic, violet)
import CSS.Common (normal) import CSS.Common (normal)
import Gargantext.Charts.Series import Data.Array (length)
import Gargantext.Charts.Data
import Gargantext.Charts.Color (chartColor, transparent)
import Gargantext.Charts.Font (IconOptions(..), Shape(..), TextStyle, chartFontStyle, chartFontWeight, icon)
import Gargantext.Charts.Legend (legendType, LegendMode(..), PlainOrScroll(..), selectedMode, Orientation(..), orient)
import Gargantext.Charts.Position (Align(..), LeftRelativePosition(..), TopRelativePosition(..), numberPosition, percentPosition, relativePosition)
import Gargantext.Charts.Type (DataZoom, Echarts, Legend, Option, Title, Tooltip, XAxis, YAxis)
import Data.Either (Either(..))
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Gargantext.Components.Charts.Options.Color (chartColor, transparent)
import Gargantext.Components.Charts.Options.Data (DataN, DataS, DataV)
import Gargantext.Components.Charts.Options.Font (IconOptions(..), Shape(..), TextStyle, chartFontStyle, chartFontWeight, icon)
import Gargantext.Components.Charts.Options.Legend (legendType, LegendMode(..), PlainOrScroll(..), selectedMode, Orientation(..), orient)
import Gargantext.Components.Charts.Options.Position (Align(..), LeftRelativePosition(..), TopRelativePosition(..), numberPosition, percentPosition, relativePosition)
import Gargantext.Components.Charts.Options.Series (Series, SeriesName, SeriesShape(..), seriesType)
import Gargantext.Components.Charts.Options.Type (DataZoom, Echarts, Legend, Option, Title, Tooltip, XAxis, YAxis)
import React as R import React as R
import React.DOM (p)
foreign import eChartsClass :: R.ReactClass Echarts foreign import eChartsClass :: R.ReactClass Echarts
...@@ -157,7 +156,7 @@ tooltip' = ...@@ -157,7 +156,7 @@ tooltip' =
series :: SeriesShape -> SeriesName -> Array DataS -> Series series :: SeriesShape -> SeriesName -> Array DataS -> Series
series sh name ss = { name: name series sh name ss = { name: name
, "type": seriesType sh , "type": seriesType sh
, "data": ss , "data": ss
} }
data YAxisFormat = YAxisFormat { position :: String data YAxisFormat = YAxisFormat { position :: String
...@@ -293,5 +292,3 @@ textStyle = ...@@ -293,5 +292,3 @@ textStyle =
,textShadowOffsetX: 0.0 ,textShadowOffsetX: 0.0
,textShadowOffsetY: 0.0 ,textShadowOffsetY: 0.0
} }
module Gargantext.Charts.Font module Gargantext.Components.Charts.Options.Font
( (
TextStyle, TextStyle,
ChartFontStyle(), ChartFontStyle(),
...@@ -12,12 +12,14 @@ module Gargantext.Charts.Font ...@@ -12,12 +12,14 @@ module Gargantext.Charts.Font
icon icon
) where ) where
import Prelude (Unit, ($), (<<<), (<>))
import CSS (FontStyle(..), FontWeight(..), Prefixed(..), Value(..)) import CSS (FontStyle(..), FontWeight(..), Prefixed(..), Value(..))
import Gargantext.Charts.Color (ChartColor)
import Gargantext.Charts.Position (LeftRelativePosition, Position, TopRelativePosition)
import Data.Generic (class Generic, gShow) import Data.Generic (class Generic, gShow)
import Data.String (toLower) import Data.String (toLower)
import Prelude (Unit, ($), (<<<), (<>)) import Gargantext.Components.Charts.Options.Color (ChartColor)
import Gargantext.Components.Charts.Options.Position (LeftRelativePosition, Position, TopRelativePosition)
type TextStyle = type TextStyle =
{ color :: ChartColor { color :: ChartColor
......
module Gargantext.Charts.Legend module Gargantext.Components.Charts.Options.Legend
( (
LegendType(..), LegendType(..),
PlainOrScroll(..), PlainOrScroll(..),
...@@ -11,9 +11,10 @@ module Gargantext.Charts.Legend ...@@ -11,9 +11,10 @@ module Gargantext.Charts.Legend
selectedMode selectedMode
) where ) where
import Prelude (class Show, show, (<<<))
import Data.Generic (class Generic, gShow) import Data.Generic (class Generic, gShow)
import Data.String (toLower) import Data.String (toLower)
import Prelude (class Show, show, (<<<))
import Unsafe.Coerce (unsafeCoerce) import Unsafe.Coerce (unsafeCoerce)
newtype LegendType = LegendType String newtype LegendType = LegendType String
...@@ -45,4 +46,3 @@ selectedMode :: LegendMode -> SelectedMode ...@@ -45,4 +46,3 @@ selectedMode :: LegendMode -> SelectedMode
selectedMode (Bool b) = unsafeCoerce b selectedMode (Bool b) = unsafeCoerce b
selectedMode (Single) = unsafeCoerce "single" selectedMode (Single) = unsafeCoerce "single"
selectedMode (Multiple) = unsafeCoerce "multiple" selectedMode (Multiple) = unsafeCoerce "multiple"
module Gargantext.Charts.Position module Gargantext.Components.Charts.Options.Position
( (
Position(), Position(),
numberPosition, numberPosition,
...@@ -9,7 +9,8 @@ module Gargantext.Charts.Position ...@@ -9,7 +9,8 @@ module Gargantext.Charts.Position
LeftRelativePosition(..) LeftRelativePosition(..)
) where ) where
import Prelude (class Show, show, ($), (<>)) import Prelude
import Unsafe.Coerce (unsafeCoerce) import Unsafe.Coerce (unsafeCoerce)
-- | The type `Position` is made to render a css position. -- | The type `Position` is made to render a css position.
......
module Gargantext.Charts.Series where module Gargantext.Components.Charts.Options.Series where
import Gargantext.Charts.Data (DataS) import Prelude
import Prelude (class Show, show, (<<<))
import Gargantext.Components.Charts.Options.Data (DataS)
newtype SeriesType = SeriesType String newtype SeriesType = SeriesType String
......
module Gargantext.Charts.Type where module Gargantext.Components.Charts.Options.Type where
import Gargantext.Charts.Font import Prelude
import CSS (Color) import CSS (Color)
import Gargantext.Charts.Series
import Gargantext.Charts.Data
import Gargantext.Charts.Color (ChartColor(..))
import Gargantext.Charts.Font (Icon, icon, TextStyle)
import Gargantext.Charts.Legend (LegendType, SelectedMode, selectedMode, Orient)
import Gargantext.Charts.Position (LeftRelativePosition, Position, TopRelativePosition)
import Data.Either (Either)
import Data.Maybe (Maybe) import Data.Maybe (Maybe)
import Prelude (Unit, (<<<)) import Gargantext.Components.Charts.Options.Color (ChartColor)
import Gargantext.Components.Charts.Options.Data (DataN, DataV)
import Gargantext.Components.Charts.Options.Font (TextStyle)
import Gargantext.Components.Charts.Options.Legend (LegendType, Orient, SelectedMode)
import Gargantext.Components.Charts.Options.Position (LeftRelativePosition, Position, TopRelativePosition)
import Gargantext.Components.Charts.Options.Series (Series)
newtype ChartAlign = ChartAlign String newtype ChartAlign = ChartAlign String
......
module GraphExplorer.Sigmajs where module Gargantext.Components.GraphExplorer.Sigmajs where
import Prelude
import Control.Monad.Eff (Eff) import Control.Monad.Eff (Eff)
import Prelude (Unit)
import React (ReactClass, ReactElement, createElement) import React (ReactClass, ReactElement, createElement)
import Unsafe.Coerce (unsafeCoerce) import Unsafe.Coerce (unsafeCoerce)
......
module Gargantext.Components.Modals.Modal where module Gargantext.Components.Modals.Modal where
import Control.Monad.Eff (Eff)
import Prelude (Unit) import Prelude (Unit)
import Control.Monad.Eff (Eff)
foreign import modalShow :: forall eff. String -> Eff eff Unit foreign import modalShow :: forall eff. String -> Eff eff Unit
foreign import modalHide :: forall eff. String -> Eff eff Unit foreign import modalHide :: forall eff. String -> Eff eff Unit
module Gargantext.Components.Tab where module Gargantext.Components.Tab where
import Prelude hiding (div)
import Data.Array (fold) import Data.Array (fold)
import Data.Lens (Lens', Prism', over, view) import Data.Lens (Lens', Prism', over, view)
import Data.List (List, mapWithIndex, toUnfoldable) import Data.List (List, mapWithIndex, toUnfoldable)
import Data.Tuple (Tuple(..)) import Data.Tuple (Tuple(..))
import Prelude hiding (div)
import React (ReactElement) import React (ReactElement)
import React.DOM (a, div, nav, text) import React.DOM (a, div, nav, text)
import React.DOM.Props (className, onClick) import React.DOM.Props (className, onClick)
......
...@@ -9,7 +9,6 @@ import Control.Monad.Eff.Console (CONSOLE, log) ...@@ -9,7 +9,6 @@ import Control.Monad.Eff.Console (CONSOLE, log)
import Data.Argonaut (class DecodeJson, decodeJson, (.?)) import Data.Argonaut (class DecodeJson, decodeJson, (.?))
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.HTTP.Method (Method(..)) import Data.HTTP.Method (Method(..))
import Data.Newtype (class Newtype)
import Data.Tuple (Tuple(..)) import Data.Tuple (Tuple(..))
import Network.HTTP.Affjax (AJAX, affjax, defaultRequest) import Network.HTTP.Affjax (AJAX, affjax, defaultRequest)
import React (ReactElement) import React (ReactElement)
......
module Gargantext.Config.REST where module Gargantext.Config.REST where
import Data.Argonaut import Prelude
import Data.HTTP.Method (Method(..))
import Network.HTTP.RequestHeader (RequestHeader(..))
import Prelude (bind, ($), pure, show)
import Data.MediaType.Common (applicationJSON)
import Control.Monad.Aff (Aff, attempt) import Control.Monad.Aff (Aff, attempt)
import Control.Monad.Aff.Class (liftAff) import Control.Monad.Aff.Class (liftAff)
import Control.Monad.Eff.Console (CONSOLE) import Control.Monad.Eff.Console (CONSOLE)
import Data.Argonaut (class DecodeJson, decodeJson)
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.HTTP.Method (Method(..))
import Data.MediaType.Common (applicationJSON)
import Network.HTTP.Affjax (AJAX, affjax, defaultRequest) import Network.HTTP.Affjax (AJAX, affjax, defaultRequest)
import Network.HTTP.RequestHeader (RequestHeader(..))
get :: forall eff t2 t31. DecodeJson t31 => String -> get :: forall eff t2 t31. DecodeJson t31 => String ->
Aff (console :: CONSOLE, ajax :: AJAX| eff) Aff (console :: CONSOLE, ajax :: AJAX| eff)
......
...@@ -2,35 +2,35 @@ module Gargantext.Navigation where ...@@ -2,35 +2,35 @@ module Gargantext.Navigation where
import Prelude hiding (div) import Prelude hiding (div)
import AddCorpusview as AC
import Control.Monad.Cont.Trans (lift) import Control.Monad.Cont.Trans (lift)
import Control.Monad.Eff.Class (liftEff) import Control.Monad.Eff.Class (liftEff)
import Control.Monad.Eff.Console (CONSOLE, log) import Control.Monad.Eff.Console (CONSOLE, log)
import CorpusAnalysis as CA import Gargantext.Pages.Corpus.Doc.Body as CA
import DOM (DOM) import DOM (DOM)
import Data.Array (length) import Data.Array (length)
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.Foldable (fold, intercalate) import Data.Foldable (fold, intercalate)
import Data.Lens (Lens', Prism', lens, over, prism) import Data.Lens (Lens', Prism', lens, over, prism)
import Data.Maybe (Maybe(Nothing, Just)) import Data.Maybe (Maybe(Nothing, Just))
import DocAnnotation as D import Gargantext.Pages.Corpus.Doc.Annotation as D
import DocView as DV import Gargantext.Pages.Corpus.Doc.Document as DV
import Gargantext.Components.Data.Lang (Lang(..))
import Gargantext.Components.Login as LN
import Gargantext.Components.Modals.Modal (modalShow)
import Gargantext.Components.Tree as Tree import Gargantext.Components.Tree as Tree
import Gargantext.Dashboard as Dsh import Gargantext.Dashboard as Dsh
import Gargantext.Components.Data.Lang (Lang(..)) import Gargantext.Pages.Corpus as AC
import Gargantext.Router (Routes(..)) import Gargantext.Router (Routes(..))
import Gargantext.Users as U import Gargantext.Users as U
import Graph as GE import Graph as GE
import Landing as L import Gargantext.Pages.Home as L
import Gargantext.Components.Login as LN
import Gargantext.Components.Modals.Modal (modalShow)
import Network.HTTP.Affjax (AJAX) import Network.HTTP.Affjax (AJAX)
import NgramsTable as NG import NgramsTable as NG
import React (ReactElement) import React (ReactElement)
import React.DOM (a, button, div, footer, hr, img, input, li, p, span, text, ul) import React.DOM (a, button, div, footer, hr, img, input, li, p, span, text, ul)
import React.DOM.Props (_data, _id, _type, aria, className, href, onChange, onClick, placeholder, role, src, style, tabIndex, target, title) import React.DOM.Props (_data, _id, _type, aria, className, href, onChange, onClick, placeholder, role, src, style, tabIndex, target, title)
import SearchForm as S import Gargantext.Pages.Search as S
import Tabview as TV import Gargantext.Pages.Corpus.Doc.Facets as TV
import Thermite (PerformAction, Render, Spec, _render, defaultPerformAction, defaultRender, focus, modifyState, simpleSpec, withState) import Thermite (PerformAction, Render, Spec, _render, defaultPerformAction, defaultRender, focus, modifyState, simpleSpec, withState)
import Unsafe.Coerce (unsafeCoerce) import Unsafe.Coerce (unsafeCoerce)
......
module AddCorpusview where module Gargantext.Pages.Corpus where
import Prelude hiding (div)
import Control.Monad.Aff (Aff, attempt) import Control.Monad.Aff (Aff, attempt)
import Control.Monad.Aff.Class (liftAff) import Control.Monad.Aff.Class (liftAff)
import Control.Monad.Aff.Console (log) import Control.Monad.Aff.Console (log)
import Control.Monad.Cont.Trans (lift) import Control.Monad.Cont.Trans (lift)
import Control.Monad.Eff (Eff)
import Control.Monad.Eff.Class (liftEff) import Control.Monad.Eff.Class (liftEff)
import Control.Monad.Eff.Console (CONSOLE) import Control.Monad.Eff.Console (CONSOLE)
import DOM (DOM) import DOM (DOM)
import DOM.HTML (window)
import DOM.HTML.Location (host)
import DOM.HTML.Window (localStorage)
import DOM.WebStorage.Storage (getItem, setItem)
import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, encodeJson, jsonEmptyObject, (.?), (:=), (~>)) import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, encodeJson, jsonEmptyObject, (.?), (:=), (~>))
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.HTTP.Method (Method(..)) import Data.HTTP.Method (Method(..))
import Data.Lens (Lens', Prism', lens, over) import Data.Lens (over)
import Data.List (List, fold, fromFoldable, toUnfoldable) import Data.Maybe (Maybe(Just))
import Data.Maybe (Maybe(..), fromMaybe)
import Data.MediaType.Common (applicationJSON) import Data.MediaType.Common (applicationJSON)
import Data.Tuple (Tuple(..))
import Landing as L
import Gargantext.Components.Modals.Modal (modalHide) import Gargantext.Components.Modals.Modal (modalHide)
import Network.HTTP.Affjax (AJAX, affjax, defaultRequest) import Network.HTTP.Affjax (AJAX, affjax, defaultRequest)
import Network.HTTP.RequestHeader (RequestHeader(..)) import Network.HTTP.RequestHeader (RequestHeader(..))
import Prelude hiding (div)
import React (ReactElement) import React (ReactElement)
import React.DOM (a, button, div, form, h2, h3, h4, h5, i, input, label, li, p, span, text, ul) import React.DOM (button, div, h3, h5, li, span, text, ul)
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, onClick, role)
import Routing.Hash.Aff (setHash) import Routing.Hash.Aff (setHash)
import Thermite (PerformAction, Render, Spec, _render, cotransform, focus, foreach, modifyState, simpleSpec, withState) import Thermite (PerformAction, Render, Spec, _render, cotransform, modifyState, simpleSpec)
import Unsafe.Coerce (unsafeCoerce)
type State = type State =
{ select_database :: Boolean { select_database :: Boolean
......
module DocAnnotation where module Gargantext.Pages.Corpus.Doc.Annotation where
import Prelude hiding (div) import Prelude hiding (div)
import React (ReactElement) import React (ReactElement)
......
module CorpusAnalysis where module Gargantext.Pages.Corpus.Doc.Body where
import Prelude hiding (div)
import Control.Monad.Eff.Console (CONSOLE) import Control.Monad.Eff.Console (CONSOLE)
import DOM (DOM) import DOM (DOM)
import Data.Array (fold) import Data.Array (fold)
import Gargantext.Components.Charts.Options.ECharts (chart)
import Gargantext.Dashboard (globalPublis)
import Gargantext.Pages.Corpus.Doc.Facet as Tab
import Network.HTTP.Affjax (AJAX) import Network.HTTP.Affjax (AJAX)
import Prelude (id, void) import React.DOM (div, h3, hr, i, p, text)
import Prelude hiding (div)
import React.DOM (div, h3, hr, i, p, span, text, input)
import React.DOM.Props (className, style) import React.DOM.Props (className, style)
import Tabview as Tab import Thermite (Render, Spec, defaultPerformAction, simpleSpec)
import Thermite (PerformAction, Render, Spec, defaultPerformAction, modifyState, simpleSpec)
import Gargantext.Charts.ECharts (chart)
import Gargantext.Dashboard (globalPublis)
type State = Tab.State type State = Tab.State
...@@ -50,7 +49,7 @@ corpusAnalysisSpec = simpleSpec defaultPerformAction render ...@@ -50,7 +49,7 @@ corpusAnalysisSpec = simpleSpec defaultPerformAction render
, text " Query: all publications with all schools ids" , text " Query: all publications with all schools ids"
] ]
] ]
, div [ className "col-md-4 content"] , div [ className "col-md-4 content"]
[ p [] [ i [className "fa fa-calendar"] [] [ p [] [ i [className "fa fa-calendar"] []
, text " June. 26 2018, 10:59 am" , text " June. 26 2018, 10:59 am"
] ]
......
module DocView where module Gargantext.Pages.Corpus.Doc.Document where
import Prelude import Prelude
import Control.Monad.Aff (Aff, attempt) import Control.Monad.Aff (Aff)
import Control.Monad.Aff.Class (liftAff)
import Control.Monad.Cont.Trans (lift) import Control.Monad.Cont.Trans (lift)
import Control.Monad.Eff (Eff)
import Control.Monad.Eff.Class (liftEff) import Control.Monad.Eff.Class (liftEff)
import Control.Monad.Eff.Console (CONSOLE, log) import Control.Monad.Eff.Console (CONSOLE, log)
import DOM (DOM) import Data.Argonaut (class DecodeJson, decodeJson, (.?))
import DOM.HTML (window) as DOM import Data.Array (filter)
import DOM.HTML.Types (htmlDocumentToParentNode) as DOM
import DOM.HTML.Window (document) as DOM
import DOM.Node.ParentNode (QuerySelector(..))
import DOM.Node.ParentNode (querySelector) as DOM
import Data.Argonaut
import Data.Array (filter, replicate)
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.Generic (class Generic, gShow) import Data.Generic (class Generic, gShow)
import Data.HTTP.Method (Method(..))
import Data.Maybe (fromJust)
import Data.MediaType.Common (applicationJSON)
import Data.Tuple (Tuple(..)) import Data.Tuple (Tuple(..))
import Gargantext.Chart (p'') import Gargantext.Components.Charts.Charts (p'')
import Gargantext.Charts.ECharts
import Gargantext.Dashboard (globalPublis)
import Gargantext.Config.REST (get) import Gargantext.Config.REST (get)
import Network.HTTP.Affjax (AJAX, affjax, defaultRequest) import Network.HTTP.Affjax (AJAX)
import Network.HTTP.RequestHeader (RequestHeader(..))
import Partial.Unsafe (unsafePartial)
import React (ReactElement) import React (ReactElement)
import React as R import React.DOM (a, b, b', br', div, input, option, select, span, table, tbody, td, text, th, thead, tr)
import React.DOM (a, b, b', br', div, h3, i, input, li, option, select, span, table, tbody, td, text, thead, th, tr, ul, nav) import React.DOM.Props (_type, className, href, onChange, onClick, scope, selected, value)
import React.DOM.Props (Props, _type, className, href, onChange, onClick, selected, value, scope, _id, role, _data, aria) import Thermite (PerformAction, Render, Spec, cotransform, defaultPerformAction, modifyState, simpleSpec)
import ReactDOM as RDOM
import Thermite (PerformAction, Render, Spec, cotransform, createReactSpec, defaultPerformAction, modifyState, simpleSpec)
import Unsafe.Coerce (unsafeCoerce) import Unsafe.Coerce (unsafeCoerce)
......
module Tabview where module Gargantext.Pages.Corpus.Doc.Facets where
import Prelude hiding (div) import Prelude hiding (div)
...@@ -9,7 +9,7 @@ import Data.Either (Either(..)) ...@@ -9,7 +9,7 @@ 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.Tuple (Tuple(..)) import Data.Tuple (Tuple(..))
import DocView as DV import Gargantext.Pages.Corpus.Doc.Document as DV
import Gargantext.Components.Tab as Tab import Gargantext.Components.Tab as Tab
import Network.HTTP.Affjax (AJAX) import Network.HTTP.Affjax (AJAX)
import Sourceview as SV import Sourceview as SV
......
...@@ -4,11 +4,11 @@ module Sourceview where ...@@ -4,11 +4,11 @@ module Sourceview where
import Control.Monad.Eff.Console (CONSOLE) import Control.Monad.Eff.Console (CONSOLE)
import DOM (DOM) import DOM (DOM)
import Data.Array (fold) import Data.Array (fold)
import DocView as D import Gargantext.Pages.Corpus.Doc.Document as D
import Network.HTTP.Affjax (AJAX) import Network.HTTP.Affjax (AJAX)
import Prelude hiding (div) import Prelude hiding (div)
import React.DOM (h3, text) import React.DOM (h3, text)
import Thermite (PerformAction, Render, Spec, defaultPerformAction, modifyState, simpleSpec) import Thermite (Render, Spec, defaultPerformAction, simpleSpec)
type State = D.State type State = D.State
......
...@@ -4,7 +4,7 @@ module Authorview where ...@@ -4,7 +4,7 @@ module Authorview where
import Control.Monad.Eff.Console (CONSOLE) import Control.Monad.Eff.Console (CONSOLE)
import DOM (DOM) import DOM (DOM)
import Data.Array (fold) import Data.Array (fold)
import DocView as D import Gargantext.Pages.Corpus.Doc.Document as D
import Network.HTTP.Affjax (AJAX) import Network.HTTP.Affjax (AJAX)
import Prelude hiding (div) import Prelude hiding (div)
import React.DOM (h3, text) import React.DOM (h3, text)
......
module Gargantext.Dashboard where module Gargantext.Dashboard where
import Prelude (($), (<>), show, pure, unit, map) import Prelude
import Data.Array (zip) import Data.Array (zip)
import Data.Tuple (Tuple(..)) import Data.Tuple (Tuple(..))
import Gargantext.Charts.ECharts import Gargantext.Components.Charts.Options.ECharts
import Gargantext.Charts.Series import Gargantext.Components.Charts.Options.Series
import DOM (DOM) import DOM (DOM)
import Data.Unit (Unit) import Data.Unit (Unit)
import Data.Int (toNumber) import Data.Int (toNumber)
import React.DOM (div, h1, text, title) import React.DOM (div, h1, text, title)
import React.DOM.Props (className) import React.DOM.Props (className)
import Thermite (PerformAction, Render, Spec, simpleSpec) import Thermite (PerformAction, Render, Spec, simpleSpec)
......
...@@ -5,7 +5,7 @@ module Termsview where ...@@ -5,7 +5,7 @@ module Termsview where
import Control.Monad.Eff.Console (CONSOLE) import Control.Monad.Eff.Console (CONSOLE)
import DOM (DOM) import DOM (DOM)
import Data.Array (fold) import Data.Array (fold)
import DocView as D import Gargantext.Pages.Corpus.Doc.Document as D
import Network.HTTP.Affjax (AJAX) import Network.HTTP.Affjax (AJAX)
import Prelude hiding (div) import Prelude hiding (div)
import React.DOM (h3, text) import React.DOM (h3, text)
......
...@@ -17,9 +17,9 @@ import Data.Int (toNumber) ...@@ -17,9 +17,9 @@ import Data.Int (toNumber)
import Data.Maybe (Maybe(..), fromJust) 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 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.Components.GraphExplorer.Types (Cluster(..), Edge(..), GraphData(..), Legend(..), Node(..), getLegendData)
import Gargantext.Utils (getter) import Gargantext.Utils (getter)
import GraphExplorer.Sigmajs (Color(Color), SigmaEasing, SigmaGraphData(SigmaGraphData), SigmaNode, SigmaSettings, canvas, edgeShape, edgeShapes, forceAtlas2, sStyle, sigma, sigmaEasing, sigmaEdge, sigmaEnableWebGL, sigmaNode, sigmaSettings)
import Math (cos, sin) import Math (cos, sin)
import Network.HTTP.Affjax (AJAX, affjax, defaultRequest) import Network.HTTP.Affjax (AJAX, affjax, defaultRequest)
import Network.HTTP.RequestHeader (RequestHeader(..)) import Network.HTTP.RequestHeader (RequestHeader(..))
......
...@@ -19,7 +19,7 @@ import DOM (DOM) ...@@ -19,7 +19,7 @@ import DOM (DOM)
import Data.List (fromFoldable) import Data.List (fromFoldable)
import Data.Tuple (Tuple(..)) import Data.Tuple (Tuple(..))
import Network.HTTP.Affjax (AJAX) import Network.HTTP.Affjax (AJAX)
import Projects as PS import Gargantext.Pages.Folder as PS
import Gargantext.Components.Tab (tabs) import Gargantext.Components.Tab (tabs)
import Thermite (Spec, focus) import Thermite (Spec, focus)
......
...@@ -9,7 +9,7 @@ import Data.Maybe (Maybe) ...@@ -9,7 +9,7 @@ import Data.Maybe (Maybe)
import Gargantext.Users.Types.States (Action(..), State) import Gargantext.Users.Types.States (Action(..), State)
import Gargantext.Users.Types.Types (User) import Gargantext.Users.Types.Types (User)
import Network.HTTP.Affjax (AJAX) import Network.HTTP.Affjax (AJAX)
import Projects as PS import Gargantext.Pages.Folder as PS
import Publications as P import Publications as P
import Gargantext.Components.Tab as Tab import Gargantext.Components.Tab as Tab
import Thermite (Spec, focus) import Thermite (Spec, focus)
......
...@@ -4,7 +4,7 @@ module Gargantext.Users.Types.States ...@@ -4,7 +4,7 @@ module Gargantext.Users.Types.States
import Brevets as B import Brevets as B
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Gargantext.Users.Types.Types (User) import Gargantext.Users.Types.Types (User)
import Projects as PS import Gargantext.Pages.Folder as PS
import Publications as P import Publications as P
import Gargantext.Components.Tab as Tab import Gargantext.Components.Tab as Tab
......
module Projects where module Gargantext.Pages.Folder where
import Prelude (id, void)
import Control.Monad.Eff.Console (CONSOLE) import Control.Monad.Eff.Console (CONSOLE)
import DOM (DOM) import DOM (DOM)
import Network.HTTP.Affjax (AJAX) import Network.HTTP.Affjax (AJAX)
import Prelude (id, void)
import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec) import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec)
......
module Landing where module Gargantext.Pages.Home where
import Prelude hiding (div) import Prelude hiding (div)
......
module SearchForm where module Gargantext.Pages.Search where
import Control.Monad.Aff.Console (CONSOLE) import Control.Monad.Aff.Console (CONSOLE)
import Control.Monad.Cont.Trans (lift) import Control.Monad.Cont.Trans (lift)
...@@ -11,7 +10,7 @@ import React.DOM.Props (_id, _type, className, name, onClick, onInput, placehold ...@@ -11,7 +10,7 @@ import React.DOM.Props (_id, _type, className, name, onClick, onInput, placehold
import Routing.Hash.Aff (setHash) import Routing.Hash.Aff (setHash)
import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec) import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec)
import Unsafe.Coerce (unsafeCoerce) import Unsafe.Coerce (unsafeCoerce)
import Landing as L import Gargantext.Pages.Home as L
type State = type State =
{ {
......
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