Commit 9c650bf5 authored by Sudhir Kumar's avatar Sudhir Kumar

upgrade to 0.12, has many more errors

parent 63b7da04
{
"name": "purescript-gargantext",
"ignore": [
"**/.*",
"node_modules",
"bower_components",
"output"
],
"dependencies": {
"purescript-prelude": "^3.1.0",
"purescript-console": "^3.0.0",
"purescript-thermite": "^5.0.0",
"purescript-affjax": "^5.0.0",
"purescript-routing": "^6.1.2",
"purescript-argonaut-codecs": "^2.0.0",
"purescript-argonaut-traversals": "^2.0.0",
"purescript-argonaut": "^3.1.0",
"purescript-random": "^3.0.0",
"purescript-css": "^3.4.0"
},
"devDependencies": {
"purescript-psci-support": "^3.0.0"
},
"resolutions": {
"purescript-maybe": "^3.0.0",
"purescript-monoid": "^3.0.0",
"purescript-invariant": "^3.0.0",
"purescript-functions": "^3.0.0",
"purescript-functors": "^2.0.0",
"purescript-const": "^3.0.0",
"purescript-contravariant": "^3.0.0",
"purescript-tuples": "^4.0.0",
"purescript-distributive": "^3.0.0",
"purescript-identity": "^3.0.0",
"purescript-transformers": "^3.0.0",
"purescript-arrays": "^4.0.1",
"purescript-nonempty": "^4.0.0",
"purescript-unfoldable": "^3.0.0",
"purescript-lazy": "^3.0.0",
"purescript-unsafe-coerce": "^3.0.0",
"purescript-strings": "^3.0.0",
"purescript-generics": "^4.0.0",
"purescript-tailrec": "^3.0.0",
"purescript-proxy": "^2.0.0",
"purescript-integers": "^3.0.0",
"purescript-globals": "^3.0.0",
"purescript-maps": "^3.0.0",
"purescript-st": "^3.0.0",
"purescript-eff": "^3.0.0",
"purescript-profunctor": "^3.0.0",
"purescript-enums": "^3.1.0",
"purescript-profunctor-lenses": "^3.0.0",
"purescript-sets": "^3.0.0",
"purescript-argonaut-core": "^3.1.0",
"purescript-lists": "^4.0.0",
"purescript-argonaut-codecs": "^3.0.0",
"purescript-argonaut-traversals": "^3.0.0",
"purescript-argonaut": "^3.1.0",
"purescript-prelude": "^3.1.0",
"purescript-either": "^3.1.0",
"purescript-foldable-traversable": "^3.6.1",
"purescript-control": "^3.0.0",
"purescript-bifunctors": "^3.0.0",
"purescript-newtype": "^2.0.0"
}
"name": "purescript-gargantext",
"ignore": [
"**/.*",
"node_modules",
"bower_components",
"output"
],
"dependencies": {
"purescript-console": "^4.1.0",
"purescript-thermite": "git@github.com:sudhirvkumar/purescript-thermite.git#migrate_0_12",
"purescript-affjax": "^7.0.0",
"purescript-routing": "^8.0.0",
"purescript-argonaut": "^4.0.1",
"purescript-random": "^4.0.0",
"purescript-css": "^4.0.0"
},
"devDependencies": {
"purescript-psci-support": "^4.0.0"
},
"resolutions": {
"purescript-react": "exports"
}
}
......@@ -30,7 +30,7 @@ group = unsafeMkProps "group"
-- resizable :: Boolean, -- PropTypes.bool,
-- onEvents :: String -- PropTypes.object
type EchartsProps eff =
type EchartsProps=
{ className :: String,
style :: String, -- objealect-black-altdarkmincnaquadahherry-blossomect,
theme :: String,
......@@ -55,7 +55,7 @@ type OptsLoading =
}
type OpTest =
{option :: Option}
{children :: R.Children, option :: Option}
type Option =
{ title :: Maybe Title
......@@ -202,14 +202,14 @@ type Title =
type Rich = {}
foreign import eChartsClass :: forall props. R.ReactClass props
foreign import eChartsClass :: forall props. R.ReactClass { children :: R.Children | props}
foreign import eChartsClass2 :: R.ReactClass OpTest
echarts :: forall eff. Array Props -> R.ReactElement
echarts p = R.createElementDynamic eChartsClass (unsafeFromPropsArray p) []
echarts :: Array Props -> R.ReactElement
echarts p = R.unsafeCreateElementDynamic eChartsClass (unsafeFromPropsArray p) []
echarts' :: forall eff. Option -> R.ReactElement
echarts' chart = R.createElementDynamic eChartsClass2 {option: chart} []
echarts' :: Option -> R.ReactElement
echarts' chart = R.unsafeCreateElementDynamic eChartsClass2 {option: chart} []
-- Props
......
......@@ -38,7 +38,7 @@ chartWith opts = { className: Nothing
, onEvents: Nothing
}
echarts :: forall eff. Echarts -> R.ReactElement
echarts :: Echarts -> R.ReactElement
echarts chart = R.createElementDynamic eChartsClass chart []
type MainTitle = String
......
......@@ -14,8 +14,9 @@ module Gargantext.Components.Charts.Options.Font
import Prelude (Unit, ($), (<<<), (<>))
import Data.Generic.Rep
import Data.Generic.Rep.Show
import CSS (FontStyle(..), FontWeight(..), Prefixed(..), Value(..))
import Data.Generic (class Generic, gShow)
import Data.String (toLower)
import Gargantext.Components.Charts.Options.Color (ChartColor)
import Gargantext.Components.Charts.Options.Position (LeftRelativePosition, Position, TopRelativePosition)
......@@ -63,10 +64,10 @@ newtype Icon = Icon String
newtype ImageURL = ImageURL String
data Shape = Circle | Rect | RoundRect | Triangle | Diamond | Pin | Arrow
derive instance genericShape :: Generic Shape
derive instance genericShape :: Generic Shape _
data IconOptions = Shape Shape | Image ImageURL
icon :: IconOptions -> Icon
icon (Shape s) = Icon <<< toLower $ gShow s
icon (Shape s) = Icon <<< toLower $ genericShow s
icon (Image (ImageURL url)) = Icon $ "image://" <> url
......@@ -13,7 +13,8 @@ module Gargantext.Components.Charts.Options.Legend
import Prelude (class Show, show, (<<<))
import Data.Generic (class Generic, gShow)
import Data.Generic.Rep
import Data.Generic.Rep.Show
import Data.String (toLower)
import Unsafe.Coerce (unsafeCoerce)
......@@ -31,16 +32,16 @@ legendType = LegendType <<< toLower <<< show
newtype Orient = Orient String
data Orientation = Horizontal | Vertical
derive instance genericOrientation :: Generic Orientation
derive instance genericOrientation :: Generic Orientation _
orient :: Orientation -> Orient
orient = Orient <<< toLower <<< gShow
orient = Orient <<< toLower <<< genericShow
foreign import data SelectedMode :: Type
data LegendMode = Bool Boolean | Single | Multiple
derive instance genericLegendMode :: Generic LegendMode
derive instance genericLegendMode :: Generic LegendMode _
selectedMode :: LegendMode -> SelectedMode
selectedMode (Bool b) = unsafeCoerce b
......
......@@ -10,7 +10,7 @@ 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)
import React as R
newtype ChartAlign = ChartAlign String
type Echarts =
......@@ -38,6 +38,7 @@ type Option =
, yAxis :: YAxis
, series :: Array Series
, dataZoom :: Array DataZoom
, children :: R.Children
}
type Title =
......
......@@ -2,7 +2,7 @@ module Gargantext.Components.GraphExplorer.Sigmajs where
import Prelude
import Control.Monad.Eff (Eff)
import Effect (Effect)
import React (ReactClass, ReactElement, createElement)
import Unsafe.Coerce (unsafeCoerce)
......@@ -22,16 +22,16 @@ foreign import sigmaClass :: forall props. ReactClass props
foreign import sigmaEnableSVGClass :: forall props. ReactClass props
foreign import sigmaEnableWebGLClass :: forall props. ReactClass props
neoCypher :: forall eff o. Optional o (NeoCypherOptProps eff) => NeoCypherReqProps o -> ReactElement
neoCypher :: forall o. Optional o NeoCypherOptProps => NeoCypherReqProps o -> ReactElement
neoCypher props = createElement neoCypherClass props []
loadJSON :: forall eff o. Optional o (onGraphLoaded :: Eff eff Unit) => { "path" :: String | o } -> ReactElement
loadJSON :: forall o. Optional o (onGraphLoaded :: Effect Unit) => { "path" :: String | o } -> ReactElement
loadJSON props = createElement loadJSONClass props []
loadGEXF :: forall eff o. Optional o (onGraphLoaded :: Eff eff Unit) => { "path" :: String | o } -> ReactElement
loadGEXF :: forall o. Optional o (onGraphLoaded :: Effect Unit) => { "path" :: String | o } -> ReactElement
loadGEXF props = createElement loadGEXFClass props []
forceLink :: forall eff o. Optional o (ForceLinkOptProps eff) => { | o} -> ReactElement
forceLink :: forall o. Optional o ForceLinkOptProps => { | o} -> ReactElement
forceLink props = createElement forceLinkClass props []
nOverlap :: forall o. Optional o NOverlapOptProps => { | o } -> ReactElement
......@@ -43,10 +43,10 @@ randomizeNodePositions = createElement randomizeNodePositionsClass {} []
relativeSize :: {initialSize :: Number } -> ReactElement
relativeSize props = createElement randomizeNodePositionsClass props []
forceAtlas2 :: forall eff o. Optional o (ForceAtlas2OptProps eff) => { | o } -> ReactElement
forceAtlas2 :: forall o. Optional o ForceAtlas2OptProps => { | o } -> ReactElement
forceAtlas2 props = createElement forceAtlas2Class props []
sigma :: forall props eff. Optional props (SigmaProps eff) => { | props} -> Array ReactElement -> ReactElement
sigma :: forall props. Optional props SigmaProps => { | props} -> Array ReactElement -> ReactElement
sigma = createElement sigmaClass
sigmaEnableWebGL :: ReactElement
......@@ -69,9 +69,9 @@ instance srInstance :: Union r t s => Optional r s
type NeoCypherOptProps eff =
type NeoCypherOptProps =
( producers :: String
, onGraphLoaded :: Eff eff Unit
, onGraphLoaded :: Effect Unit
)
type NeoCypherReqProps o =
......@@ -84,7 +84,7 @@ type NeoCypherReqProps o =
type ForceLinkOptProps eff =
type ForceLinkOptProps =
( barnesHutOptimize :: Boolean
, barnesHutTheta :: Number
, adjustSizes :: Boolean
......@@ -138,7 +138,7 @@ sigmaEasing =
, cubicInOut : SigmaEasing "cubicInOut"
}
type ForceAtlas2OptProps eff =
type ForceAtlas2OptProps =
( worker :: Boolean
, barnesHutOptimize :: Boolean
, barnesHutTheta :: Number
......@@ -248,17 +248,17 @@ sigmaSettings = unsafeCoerce
foreign import data SigmaStyle :: Type
type SigmaProps eff =
type SigmaProps =
( renderer :: Renderer
, settings :: SigmaSettings
, style :: SigmaStyle
, graph :: SigmaGraphData
, onClickNode :: SigmaNodeEvent -> Unit
, onOverNode :: SigmaNodeEvent -> Unit
, onOutNode :: SigmaNodeEvent -> Eff eff Unit
, onClickEdge :: SigmaEdgeEvent -> Eff eff Unit
, onOverEdge :: SigmaEdgeEvent -> Eff eff Unit
, onOutEdge :: SigmaEdgeEvent -> Eff eff Unit
, onOutNode :: SigmaNodeEvent -> Effect Unit
, onClickEdge :: SigmaEdgeEvent -> Effect Unit
, onOverEdge :: SigmaEdgeEvent -> Effect Unit
, onOutEdge :: SigmaEdgeEvent -> Effect Unit
)
sStyle :: forall style. { | style } -> SigmaStyle
......
......@@ -2,16 +2,7 @@ module Gargantext.Components.Login where
import Prelude hiding (div)
import Control.Monad.Aff (Aff, attempt)
import Control.Monad.Aff.Class (liftAff)
import Control.Monad.Aff.Console (log)
import Control.Monad.Eff (Eff)
import Control.Monad.Eff.Class (liftEff)
import Control.Monad.Eff.Console (CONSOLE)
import DOM (DOM)
import DOM.HTML (window)
import DOM.HTML.Window (localStorage)
import DOM.WebStorage.Storage (getItem, setItem)
import Effect (Effect)
import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, encodeJson, jsonEmptyObject, (.?), (:=), (~>))
import Data.Either (Either(..))
import Data.HTTP.Method (Method(..))
......@@ -19,14 +10,11 @@ import Data.Lens (over)
import Data.Maybe (Maybe(..))
import Data.MediaType.Common (applicationJSON)
import Gargantext.Components.Modals.Modal (modalHide)
import Network.HTTP.Affjax (AJAX, affjax, defaultRequest)
import Network.HTTP.RequestHeader (RequestHeader(..))
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 Thermite (PerformAction, Render, Spec, _render, modifyState, simpleSpec)
import Unsafe.Coerce (unsafeCoerce)
-- 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
......@@ -54,11 +42,7 @@ data Action
| SetPassword String
performAction :: forall eff props. PerformAction ( console :: CONSOLE
, ajax :: AJAX
, dom :: DOM
| eff
) State props Action
performAction :: forall props. PerformAction State props Action
performAction NoOp _ _ = void do
modifyState id
......@@ -85,7 +69,7 @@ performAction Login _ (State state) = void do
-- modifyState \(State s) -> State $ s {response = r, errorMessage = ""}
modalSpec :: forall eff props. Boolean -> String -> Spec eff State props Action -> Spec eff State props Action
modalSpec :: forall props. Boolean -> String -> Spec State props Action -> Spec State props Action
modalSpec sm t = over _render \render d p s c ->
[ div [ _id "loginModal", className $ "modal myModal" <> if sm then "" else " fade"
, role "dialog"
......@@ -113,10 +97,10 @@ modalSpec sm t = over _render \render d p s c ->
]
]
spec' :: forall eff props. Spec (console:: CONSOLE, ajax :: AJAX, dom :: DOM | eff) State props Action
spec' :: forall props. Spec State props Action
spec' = modalSpec true "Login" renderSpec
renderSpec :: forall props eff . Spec (console::CONSOLE, ajax::AJAX, dom::DOM | eff) State props Action
renderSpec :: forall props. Spec State props Action
renderSpec = simpleSpec performAction render
where
render :: Render State props Action
......@@ -219,14 +203,14 @@ unsafeEventValue e = (unsafeCoerce e).target.value
getDeviseID :: forall eff. Eff (dom :: DOM | eff) (Maybe String)
getDeviseID :: Effect (Maybe String)
getDeviseID = do
w <- window
ls <- localStorage w
getItem "token" ls
setToken :: forall e . String -> Eff (dom :: DOM | e) Unit
setToken :: String -> Effect Unit
setToken s = do
w <- window
ls <- localStorage w
......@@ -244,7 +228,7 @@ newtype LoginReq = LoginReq
, password :: String
}
loginReq :: forall eff. LoginReq -> Aff (console :: CONSOLE, ajax :: AJAX, dom :: DOM | eff) (Either String LoginRes)
loginReq :: LoginReq -> Aff (Either String LoginRes)
loginReq encodeData =
let
setting =
......
......@@ -2,8 +2,8 @@ module Gargantext.Components.Modals.Modal where
import Prelude (Unit)
import Control.Monad.Eff (Eff)
import Effect (Effect)
foreign import modalShow :: forall eff. String -> Eff eff Unit
foreign import modalShow :: String -> Effect Unit
foreign import modalHide :: forall eff. String -> Eff eff Unit
foreign import modalHide :: String -> Effect Unit
......@@ -21,8 +21,7 @@ module Gargantext.Components.RandomText where
import Prelude
import Control.Monad.Eff (Eff)
import Control.Monad.Eff.Random (RANDOM, randomInt)
import Effect (Effect)
import Data.Array (drop, dropEnd, filter, foldl, head, length, tail, take, takeEnd, (!!))
import Data.Maybe (Maybe(Nothing, Just), fromJust)
import Data.String (Pattern(..), fromCharArray, split, toCharArray)
......@@ -31,18 +30,18 @@ import Partial.Unsafe (unsafePartial)
-------------------------------------------------------------------
randomSentences :: forall a. String -> Eff ( random :: RANDOM | a ) String
randomSentences :: String -> Effect String
randomSentences ss = case (length (sentences ss)) >= 5 of
true -> foldl (\a b -> a <> "." <> b) "" <$> randomPart (sentences ss)
_ -> pure ss
randomWords :: forall a. String -> Eff ( random :: RANDOM | a ) String
randomWords :: String -> Effect String
randomWords ws = case (length (words ws)) >= 5 of
true -> foldl (\a b -> a <> " " <> b) "" <$> randomPart (words ws)
_ -> pure ws
randomChars :: forall a. String -> Eff ( random :: RANDOM | a ) String
randomChars :: String -> Effect String
randomChars word = case (length (toCharArray word)) >= 5 of
true -> fromCharArray <$> randomPart (toCharArray word)
_ -> pure word
......@@ -61,7 +60,7 @@ data RandomWheel a = RandomWheel { before :: Array a
, after :: Array a
}
randomPart :: forall a b. Array b -> Eff ( random :: RANDOM | a ) (Array b)
randomPart :: forall a b. Array b -> Effect (Array b)
randomPart array = randomArrayPoly middle >>= \(middle') -> pure ( start <> middle' <> end)
where
start = take 2 array
......@@ -69,13 +68,13 @@ randomPart array = randomArrayPoly middle >>= \(middle') -> pure ( start <> midd
end = takeEnd 2 array
randomArrayPoly :: forall a b. Array a -> Eff ( random :: RANDOM | b ) (Array a)
randomArrayPoly :: forall a b. Array a -> Effect (Array a)
randomArrayPoly wheel = case head wheel of
Nothing -> pure []
Just wheel' -> randomWheel (RandomWheel { before:wheel, during:wheel', after:[]})
>>= \(RandomWheel rand) -> (pure rand.after)
randomWheel :: forall a b. RandomWheel b -> Eff ( random :: RANDOM | a ) (RandomWheel b)
randomWheel :: forall a b. RandomWheel b -> Effect (RandomWheel b)
randomWheel (RandomWheel {before:[], during:d, after:a}) =
pure (RandomWheel {before:[], during:d, after:a})
......@@ -84,7 +83,7 @@ randomWheel (RandomWheel {before:b, during:d, after:a}) = do
randomWheel $ RandomWheel {before:b', during:d', after:(a <> [d'])}
randomArray :: forall a b. Array b -> Eff ( random :: RANDOM | a ) (RandomWheel b)
randomArray :: forall a b. Array b -> Effect (RandomWheel b)
randomArray array = unsafePartial $ do
n <- randomInt 0 (length array - 1)
......
......@@ -15,7 +15,7 @@ type State = Int
data Action = ChangeTab Int
tabs :: forall eff state props action . Lens' state State -> Prism' action Action -> List (Tuple String (Spec eff state props action)) -> Spec eff state props action
tabs :: forall state props action . Lens' state State -> Prism' action Action -> List (Tuple String (Spec state props action)) -> Spec state props action
tabs l p ls = withState \st ->
fold
[ focus l p $ simpleSpec performAction (render (activeTab st) ls)
......@@ -26,18 +26,18 @@ tabs l p ls = withState \st ->
wrapper = over _render \render d p s c ->
[div [className "tab-content"] $ render d p s c]
tab :: forall eff state props action. Int -> Int -> Tuple String (Spec eff state props action) -> Spec eff state props action
tab :: forall state props action. Int -> Int -> Tuple String (Spec state props action) -> Spec state props action
tab sid iid (Tuple name spec) = over _render tabRender spec
where
tabRender renderer d p s c =
[div [ className $ "tab-pane " <> if sid ==iid then " show active" else " fade"] $ renderer d p s c]
performAction :: forall eff props. PerformAction eff State props Action
performAction :: forall props. PerformAction State props Action
performAction (ChangeTab i) _ _ = void do
cotransform \_ -> i
render :: forall eff state props action. State -> List (Tuple String (Spec eff state props action)) -> Render State props Action
render :: forall state props action. State -> List (Tuple String (Spec state props action)) -> Render State props Action
render at ls d p s c =
[ nav []
[ div [className "nav nav-tabs"]
......
......@@ -2,15 +2,10 @@ module Gargantext.Components.Tree where
import Prelude hiding (div)
import Control.Monad.Aff (Aff, attempt)
import Control.Monad.Aff.Class (liftAff)
import Control.Monad.Eff.Class (liftEff)
import Control.Monad.Eff.Console (CONSOLE, log)
import Data.Argonaut (class DecodeJson, decodeJson, (.?))
import Data.Either (Either(..))
import Data.HTTP.Method (Method(..))
import Data.Tuple (Tuple(..))
import Network.HTTP.Affjax (AJAX, affjax, defaultRequest)
import React (ReactElement)
import React.DOM (a, div, i, li, text, ul)
import React.DOM.Props (Props, className, href, onClick)
......@@ -87,7 +82,7 @@ nodeOptionsView activated = case activated of
false -> []
treeview :: Spec _ State _ Action
treeview :: Spec State _ Action
treeview = simpleSpec performAction render
where
render :: Render State _ Action
......@@ -130,7 +125,7 @@ instance decodeJsonLNode :: DecodeJson LNode where
name <- obj .? "name"
pure $ LNode {id : id_, name}
loadDefaultNode :: forall eff. Aff (ajax :: AJAX, console :: CONSOLE | eff) (Either String (Array LNode))
loadDefaultNode :: Aff (Either String (Array LNode))
loadDefaultNode = do
res <- liftAff $ attempt $ affjax defaultRequest
{ url = "http://localhost:8008/user"
......
......@@ -2,19 +2,13 @@ module Gargantext.Config.REST where
import Prelude
import Control.Monad.Aff (Aff, attempt)
import Control.Monad.Aff.Class (liftAff)
import Control.Monad.Eff.Console (CONSOLE)
import Data.Argonaut (class DecodeJson, decodeJson)
import Data.Either (Either(..))
import Data.HTTP.Method (Method(..))
import Data.MediaType.Common (applicationJSON)
import Network.HTTP.Affjax (AJAX, affjax, defaultRequest)
import Network.HTTP.RequestHeader (RequestHeader(..))
get :: forall eff t2 t31. DecodeJson t31 => String ->
Aff (console :: CONSOLE, ajax :: AJAX| eff)
(Either String t31)
get :: forall t2 t31. DecodeJson t31 => String ->
Aff (Either String t31)
get url = do
affResp <- liftAff $ attempt $ affjax defaultRequest
{ method = Left GET
......
......@@ -2,13 +2,10 @@ module Gargantext.Pages.Corpus where
import Prelude hiding (div)
import Control.Monad.Eff.Console (CONSOLE)
import DOM (DOM)
import Data.Array (fold)
import Gargantext.Components.Charts.Options.ECharts (chart)
import Gargantext.Pages.Corpus.Doc.Facets.Dashboard (globalPublis)
import Gargantext.Pages.Corpus.Doc.Facets as Tab
import Network.HTTP.Affjax (AJAX)
import React.DOM (div, h3, hr, i, p, text)
import React.DOM.Props (className, style)
import Thermite (Render, Spec, defaultPerformAction, simpleSpec)
......@@ -27,12 +24,12 @@ type Corpus = { title :: String
initialState :: State
initialState = Tab.initialState
spec' :: forall eff props. Spec (dom :: DOM, console :: CONSOLE, ajax :: AJAX | eff) Tab.State props Tab.Action
spec' :: forall props. Spec Tab.State props Tab.Action
spec' = fold [ corpusSpec
, Tab.tab1
]
corpusSpec :: forall props eff . Spec eff Tab.State props Tab.Action
corpusSpec :: forall props. Spec Tab.State props Tab.Action
corpusSpec = simpleSpec defaultPerformAction render
where
render :: Render Tab.State props Tab.Action
......
......@@ -27,7 +27,7 @@ data Action
| SetInput String
performAction :: PerformAction _ State _ Action
performAction :: PerformAction State _ Action
performAction NoOp _ _ = pure unit
performAction (ChangeString ps) _ _ = pure unit
......@@ -39,7 +39,7 @@ performAction (SetInput ps) _ _ = void do
docview :: Spec _ State _ Action
docview :: Spec State _ Action
docview = simpleSpec performAction render
where
render :: Render State _ Action
......
module Gargantext.Pages.Corpus.Doc.Facets.Authors where
import Control.Monad.Eff.Console (CONSOLE)
import DOM (DOM)
import Data.Array (fold)
import Gargantext.Pages.Corpus.Doc.Facets.Documents as D
import Network.HTTP.Affjax (AJAX)
import Prelude hiding (div)
import React.DOM (h3, text)
import Thermite (PerformAction, Render, Spec, defaultPerformAction, modifyState, simpleSpec)
type State = D.State
initialState :: State
initialState = D.tdata
type Action = D.Action
authorSpec :: forall props eff . Spec ( console :: CONSOLE
, ajax :: AJAX
, dom :: DOM
| eff
) State props Action
authorSpec :: forall props. Spec State props Action
authorSpec = simpleSpec defaultPerformAction render
where
render :: Render State props Action
render dispatch _ state _ =
[ h3 [] [text "AuthorView"]]
authorspec' :: forall eff props. Spec (dom :: DOM, console :: CONSOLE, ajax :: AJAX | eff) State props Action
authorspec' :: forall props. Spec State props Action
authorspec' = fold [authorSpec, D.layoutDocview]
......@@ -6,7 +6,6 @@ import Data.Array (zip)
import Data.Tuple (Tuple(..))
import Gargantext.Components.Charts.Options.ECharts
import Gargantext.Components.Charts.Options.Series
import DOM (DOM)
import Data.Unit (Unit)
import Data.Int (toNumber)
import React.DOM (div, h1, text, title)
......@@ -20,7 +19,7 @@ data Action = None
initialState :: State
initialState = unit
performAction :: forall eff props. PerformAction (dom :: DOM | eff) State props Action
performAction :: forall props. PerformAction State props Action
performAction _ _ _ = pure unit
render :: forall props. Render State props Action
......@@ -105,5 +104,5 @@ distriBySchool = Options { mainTitle : "School production in 2017"
}
layoutDashboard :: forall props eff. Spec (dom :: DOM | eff) State props Action
layoutDashboard :: forall props. Spec State props Action
layoutDashboard = simpleSpec performAction render
......@@ -2,18 +2,12 @@ module Gargantext.Pages.Corpus.Doc.Facets.Documents where
import Prelude
import Control.Monad.Aff (Aff)
import Control.Monad.Cont.Trans (lift)
import Control.Monad.Eff.Class (liftEff)
import Control.Monad.Eff.Console (CONSOLE, log)
import Data.Argonaut (class DecodeJson, decodeJson, (.?))
import Data.Array (filter)
import Data.Either (Either(..))
import Data.Generic (class Generic, gShow)
import Data.Tuple (Tuple(..))
import Gargantext.Components.Charts.Charts (p'')
import Gargantext.Config.REST (get)
import Network.HTTP.Affjax (AJAX)
import React (ReactElement)
import React.DOM (a, b, b', br', div, input, option, select, span, table, tbody, td, text, th, thead, tr)
import React.DOM.Props (_type, className, href, onChange, onClick, scope, selected, value)
......@@ -132,14 +126,14 @@ instance decodeResponse :: DecodeJson Response where
-- | Filter
filterSpec :: forall eff props. Spec eff State props Action
filterSpec :: forall props. Spec State props Action
filterSpec = simpleSpec defaultPerformAction render
where
render d p s c = [div [] [ text " Filter "
, input [] []
]]
layoutDocview :: Spec _ State _ Action
layoutDocview :: Spec State _ Action
layoutDocview = simpleSpec performAction render
where
render :: Render State _ Action
......@@ -176,7 +170,7 @@ layoutDocview = simpleSpec performAction render
]
performAction :: PerformAction _ State _ Action
performAction :: PerformAction State _ Action
performAction (ChangePageSize ps) _ _ = void (cotransform (\state -> changePageSize ps state ))
performAction (ChangePage p) _ _ = void (cotransform (\(TableData td) -> TableData $ td { currentPage = p} ))
......@@ -188,7 +182,7 @@ performAction LoadData _ _ = void do
Right resData -> modifyState (\s -> resData)
loadPage :: forall eff. Aff (ajax :: AJAX, console :: CONSOLE | eff) (Either String CorpusTableData)
loadPage :: Aff (Either String CorpusTableData)
loadPage = do
res <- get "http://localhost:8008/node/452132/children"
-- res <- get "http://localhost:8008/corpus/472764/facet/documents/table?offset=0&limit=10"
......
......@@ -2,13 +2,6 @@ module Gargantext.Pages.Corpus.Doc.Facets.Graph where