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
import Prelude hiding (div)
import Control.Monad.Aff (Aff, attempt)
import Control.Monad.Aff.Class (liftAff)
import Control.Monad.Cont.Trans (lift)
import Control.Monad.Eff.Class (liftEff)
import Control.Monad.Eff.Console (CONSOLE, log)
import Control.Monad.Eff.Unsafe (unsafePerformEff)
import DOM (DOM)
import Data.Argonaut (decodeJson)
import Data.Array (length, mapWithIndex, (!!))
import Data.Either (Either(..))
......@@ -21,8 +14,6 @@ import Gargantext.Components.GraphExplorer.Sigmajs (Color(Color), SigmaEasing, S
import Gargantext.Components.GraphExplorer.Types (Cluster(..), Edge(..), GraphData(..), Legend(..), Node(..), getLegendData)
import Gargantext.Utils (getter)
import Math (cos, sin)
import Network.HTTP.Affjax (AJAX, affjax, defaultRequest)
import Network.HTTP.RequestHeader (RequestHeader(..))
import Partial.Unsafe (unsafePartial)
import React (ReactElement)
import React.DOM (a, br', button, div, form', input, li, li', menu, option, p, select, span, text, ul, ul')
......@@ -56,10 +47,10 @@ initialState = State
, selectedNode : Nothing
}
graphSpec :: forall eff props. Spec (ajax :: AJAX, console :: CONSOLE, dom :: DOM | eff) State props Action
graphSpec :: forall props. Spec State props Action
graphSpec = simpleSpec performAction render
performAction :: forall eff props. PerformAction (ajax :: AJAX, console :: CONSOLE , dom :: DOM | eff) State props Action
performAction :: forall props. PerformAction State props Action
performAction (LoadGraph fp) _ _ = void do
_ <- liftEff $ log fp
case fp of
......@@ -226,7 +217,7 @@ mySettings = sigmaSettings { verbose : true
-- loadJSON {path : "http://localhost:2015/examples/sites_coords.json"}
getGraphData :: forall eff. String -> Aff (console :: CONSOLE, ajax :: AJAX , dom :: DOM | eff ) (Either String GraphData)
getGraphData :: String -> Aff (Either String GraphData)
getGraphData fp = do
resp <- liftAff $ attempt $ affjax defaultRequest
{ url =("http://localhost:2015/examples/" <> fp)
......@@ -296,7 +287,7 @@ dispLegend ary = div [] $ map dl ary
]
specOld :: forall eff props. Spec (console :: CONSOLE, dom :: DOM, ajax :: AJAX | eff) State props Action
specOld :: forall props. Spec State props Action
specOld = simpleSpec performAction render
where
render :: Render State props Action
......
module Gargantext.Pages.Corpus.Doc.Facets.Sources 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 (Render, Spec, defaultPerformAction, simpleSpec)
......@@ -19,16 +16,12 @@ initialState = D.tdata
type Action = D.Action
sourceSpec :: forall props eff . Spec ( console :: CONSOLE
, ajax :: AJAX
, dom :: DOM
| eff
) State props Action
sourceSpec :: forall props. Spec State props Action
sourceSpec = simpleSpec defaultPerformAction render
where
render :: Render State props Action
render dispatch _ state _ =
[ h3 [] [text "Source view"]]
sourcespec' :: forall eff props. Spec (dom :: DOM, console :: CONSOLE, ajax :: AJAX | eff) State props Action
sourcespec' :: forall props. Spec State props Action
sourcespec' = fold [sourceSpec, D.layoutDocview]
......@@ -2,8 +2,6 @@ module Gargantext.Pages.Corpus.Doc.Facets.Specs where
import Prelude hiding (div)
import Control.Monad.Eff.Console (CONSOLE)
import DOM (DOM)
import Data.Lens (Lens', Prism', lens, prism)
import Data.List (fromFoldable)
import Data.Tuple (Tuple(..))
......@@ -17,29 +15,25 @@ import Gargantext.Pages.Corpus.Doc.Facets.Authors as AV
import Gargantext.Pages.Corpus.Doc.Facets.Terms as TV
import Gargantext.Components.Tab as Tab
import Network.HTTP.Affjax (AJAX)
import Thermite (Spec, focus)
tab1 :: forall eff props. Spec ( dom :: DOM, console :: CONSOLE, ajax :: AJAX| eff) State props Action
tab1 :: forall props. Spec State props Action
tab1 = Tab.tabs _tablens _tabAction $ fromFoldable [ Tuple "Doc View" docPageSpec
, Tuple "Author View" authorPageSpec
, Tuple "Source View" sourcePageSpec
, Tuple "Terms View" termsPageSpec
]
docPageSpec :: forall eff props. Spec (dom :: DOM, console :: CONSOLE, ajax :: AJAX | eff) State props Action
docPageSpec :: forall props. Spec State props Action
docPageSpec = focus _doclens _docAction DV.layoutDocview
authorPageSpec :: forall eff props. Spec (dom :: DOM, console::CONSOLE, ajax :: AJAX | eff) State props Action
authorPageSpec :: forall props. Spec State props Action
authorPageSpec = focus _authorlens _authorAction AV.authorspec'
sourcePageSpec :: forall eff props. Spec (dom :: DOM, console :: CONSOLE, ajax :: AJAX | eff) State props Action
sourcePageSpec :: forall props. Spec State props Action
sourcePageSpec = focus _sourcelens _sourceAction SV.sourcespec'
termsPageSpec :: forall eff props. Spec (dom :: DOM, console :: CONSOLE, ajax :: AJAX | eff) State props Action
termsPageSpec :: forall props. Spec State props Action
termsPageSpec = focus _termslens _termsAction TV.termSpec'
module Gargantext.Pages.Corpus.Doc.Facets.Terms 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)
......@@ -20,16 +17,12 @@ initialState = D.tdata
type Action = D.Action
termsSpec :: forall props eff . Spec ( console :: CONSOLE
, ajax :: AJAX
, dom :: DOM
| eff
) State props Action
termsSpec :: forall props. Spec State props Action
termsSpec = simpleSpec defaultPerformAction render
where
render :: Render State props Action
render dispatch _ state _ =
[ h3 [] [text "Terms view"]]
termSpec' :: forall eff props. Spec (dom :: DOM, console :: CONSOLE, ajax :: AJAX | eff) State props Action
termSpec' :: forall props. Spec State props Action
termSpec' = fold [termsSpec, D.layoutDocview]
......@@ -2,10 +2,7 @@ module Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsItem where
import Prelude
import Control.Monad.Eff.Console (CONSOLE)
import DOM (DOM)
import Data.Newtype (class Newtype)
import Network.HTTP.Affjax (AJAX)
import React (ReactElement)
import React.DOM (input, span, td, text, tr)
import React.DOM.Props (_type, checked, className, onChange, style, title)
......@@ -36,14 +33,14 @@ data Action
= SetMap Boolean
| SetStop Boolean
performAction :: forall eff props. PerformAction ( console :: CONSOLE , ajax :: AJAX, dom :: DOM | eff ) State props Action
performAction :: forall props. PerformAction State props Action
performAction (SetMap b) _ _ = void do
modifyState \(State s) -> State s {term = setter (_{_type = (if b then MapTerm else None)}) s.term}
performAction (SetStop b) _ _ = void do
modifyState \(State s) -> State s {term = setter (_{_type = (if b then StopTerm else None)}) s.term}
ngramsItemSpec :: forall props eff . Spec (console::CONSOLE, ajax::AJAX, dom::DOM | eff) State props Action
ngramsItemSpec :: forall props. Spec State props Action
ngramsItemSpec = simpleSpec performAction render
where
render :: Render State props Action
......
module Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsTable where
import CSS.TextAlign (center, textAlign)
import Control.Monad.Eff.Console (CONSOLE)
import DOM (DOM)
import Data.Array (filter, fold, toUnfoldable)
import Data.Either (Either(..))
import Data.Lens (Lens', Prism', lens, over, prism)
import Data.List (List)
import Data.Tuple (Tuple(..), uncurry)
import Network.HTTP.Affjax (AJAX)
import Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsItem as NI
import Prelude (class Eq, class Ord, class Show, Unit, bind, map, not, pure, show, void, ($), (*), (+), (-), (/), (<), (<$>), (<>), (==), (>), (>=), (>>=))
import React (ReactElement)
......@@ -54,7 +51,7 @@ _ItemAction = prism (uncurry ItemAction) \ta ->
ItemAction i a -> Right (Tuple i a)
_ -> Left ta
performAction :: forall eff props. PerformAction ( console :: CONSOLE , ajax :: AJAX, dom :: DOM | eff ) State props Action
performAction :: forall props. PerformAction State props Action
performAction _ _ _ = void do
modifyState \(State state) -> State $ state
......@@ -72,7 +69,7 @@ performAction (ChangeString c) _ _ = void do
performAction (SetInput s) _ _ = void do
modifyState \(State state) -> State $ state { search = s }
tableSpec :: forall eff props .Spec eff State props Action -> Spec eff State props Action
tableSpec :: forall props .Spec State props Action -> Spec eff State props Action
tableSpec = over _render \render dispatch p (State s) c ->
[div [className "container-fluid"]
[
......@@ -149,14 +146,14 @@ tableSpec = over _render \render dispatch p (State s) c ->
]
]
ngramsTableSpec :: forall props eff . Spec (console::CONSOLE, ajax::AJAX, dom::DOM | eff) State props Action
ngramsTableSpec :: forall props . Spec State props Action
ngramsTableSpec = container $ fold
[ tableSpec $ withState \st ->
focus _itemsList _ItemAction $
foreach \_ -> NI.ngramsItemSpec
]
container :: forall eff state props action. Spec eff state props action -> Spec eff state props action
container :: forall state props action. Spec state props action -> Spec state props action
container = over _render \render d p s c ->
[ div [ className "container-fluid" ] $
(render d p s c)
......
module Gargantext.Pages.Corpus.User.Brevets where
import Control.Monad.Eff.Console (CONSOLE)
import DOM (DOM)
import Network.HTTP.Affjax (AJAX)
import Prelude (id, void)
import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec)
......@@ -15,20 +12,12 @@ initialState = ""
data Action = NoOp
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
brevetsSpec :: forall props eff . Spec ( console :: CONSOLE
, ajax :: AJAX
, dom :: DOM
| eff
) State props Action
brevetsSpec :: forall props. Spec State props Action
brevetsSpec = simpleSpec performAction render
where
render :: Render State props Action
......
......@@ -3,26 +3,18 @@ module Gargantext.Pages.Corpus.User.Users.API where
import Prelude
import Gargantext.Pages.Corpus.User.Users.Types (Action(..), State, User, _user)
import Control.Monad.Aff (Aff)
import Control.Monad.Aff.Console (CONSOLE, log)
import Control.Monad.Trans.Class (lift)
import DOM (DOM)
import Data.Either (Either(..))
import Data.Lens (set)
import Data.Maybe (Maybe(..))
import Gargantext.Config.REST (get)
import Network.HTTP.Affjax (AJAX)
import Thermite (PerformAction, modifyState)
getUser :: forall eff. Int -> Aff
(console :: CONSOLE, ajax :: AJAX | eff) (Either String User)
getUser :: Int -> Aff (Either String User)
getUser id = get $ "http://localhost:8008/node/" <> show id
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
performAction (FetchUser userId) _ _ = void do
......
......@@ -5,16 +5,9 @@ module Gargantext.Pages.Corpus.User.Users.Specs
import Gargantext.Pages.Corpus.User.Users.Specs.Renders
import Control.Monad.Aff.Console (CONSOLE)
import DOM (DOM)
import Network.HTTP.Affjax (AJAX)
import Thermite (Spec, simpleSpec)
import Gargantext.Pages.Corpus.User.Users.Types (Action, State)
import Gargantext.Pages.Corpus.User.Users.API (performAction)
layoutUser :: forall props eff . Spec ( console :: CONSOLE
, ajax :: AJAX
, dom :: DOM
| eff
) State props Action
layoutUser :: forall props. Spec State props Action
layoutUser = simpleSpec performAction render
module Gargantext.Pages.Corpus.User.Users.Specs.Documents where
import Control.Monad.Eff.Console (CONSOLE)
import DOM (DOM)
import Network.HTTP.Affjax (AJAX)
import Prelude (id, void)
import React.DOM (table, tbody, td, text, th, thead, tr)
import React.DOM.Props (className, scope)
......@@ -16,21 +13,13 @@ initialState = ""
data Action = NoOp
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
publicationSpec :: forall props eff . Spec ( console :: CONSOLE
, ajax :: AJAX
, dom :: DOM
| eff
) State props Action
publicationSpec :: forall props. Spec State props Action
publicationSpec = simpleSpec performAction render
where
render :: Render State props Action
......
......@@ -14,23 +14,20 @@ import Gargantext.Pages.Corpus.User.Users.Types.Lens
import Gargantext.Pages.Corpus.User.Users.Types.Types
import Gargantext.Pages.Corpus.User.Users.Types.States
import Gargantext.Pages.Corpus.User.Brevets as B
import Control.Monad.Aff.Console (CONSOLE)
import DOM (DOM)
import Data.List (fromFoldable)
import Data.Tuple (Tuple(..))
import Network.HTTP.Affjax (AJAX)
import Gargantext.Pages.Folder as PS
import Gargantext.Components.Tab (tabs)
import Thermite (Spec, focus)
brevetSpec :: forall eff props. Spec (dom :: DOM, console::CONSOLE, ajax :: AJAX | eff) State props Action
brevetSpec :: forall props. Spec State props Action
brevetSpec = focus _brevetslens _brevetsAction B.brevetsSpec
projectSpec :: forall eff props. Spec (dom :: DOM, console :: CONSOLE, ajax :: AJAX | eff) State props Action
projectSpec :: forall props. Spec State props Action
projectSpec = focus _projectslens _projectsAction PS.projets
facets :: forall eff props. Spec ( dom :: DOM, console :: CONSOLE, ajax :: AJAX| eff) State props Action
facets :: forall props. Spec State props Action
facets = tabs _tablens _tabAction $ fromFoldable
[ Tuple "Publications (12)" publicationSpec
, Tuple "Brevets (2)" brevetSpec
......
module Gargantext.Pages.Corpus.User.Users.Types.Lens where
import Gargantext.Pages.Corpus.User.Brevets as B
import Control.Monad.Aff.Console (CONSOLE)
import DOM (DOM)
import Data.Either (Either(..))
import Data.Lens (Lens', Prism', lens, prism)
import Data.Maybe (Maybe)
import Gargantext.Pages.Corpus.User.Users.Types.States (Action(..), State)
import Gargantext.Pages.Corpus.User.Users.Types.Types (User)
import Network.HTTP.Affjax (AJAX)
import Gargantext.Pages.Folder as PS
import Gargantext.Pages.Corpus.User.Users.Specs.Documents as P
import Gargantext.Components.Tab as Tab
......@@ -35,7 +32,7 @@ _pubAction = prism PublicationA \ action ->
PublicationA laction -> Right laction
_-> Left action
publicationSpec :: forall eff props. Spec (dom :: DOM, console :: CONSOLE, ajax :: AJAX | eff) State props Action
publicationSpec :: forall props. Spec State props Action
publicationSpec = focus _publens _pubAction P.publicationSpec
_brevetslens :: Lens' State B.State
......
......@@ -2,9 +2,6 @@ module Gargantext.Pages.Folder where
import Prelude (id, void)
import Control.Monad.Eff.Console (CONSOLE)
import DOM (DOM)
import Network.HTTP.Affjax (AJAX)
import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec)
......@@ -15,20 +12,12 @@ initialState = ""
data Action = NoOp
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
projets :: forall props eff . Spec ( console :: CONSOLE
, ajax :: AJAX
, dom :: DOM
| eff
) State props Action
projets :: forall props. Spec State props Action
projets = simpleSpec performAction render
where
render :: Render State props Action
......
......@@ -3,23 +3,15 @@ module Gargantext.Pages.Home.Actions where
import Prelude hiding (div)
import Control.Monad.Cont.Trans (lift)
import Control.Monad.Eff.Console (CONSOLE)
import DOM (DOM)
import Gargantext.Components.Lang.Landing.EnUS as En
import Gargantext.Components.Lang.Landing.FrFR as Fr
import Gargantext.Components.Data.Landing (BlockText(..), BlockTexts(..), Button(..), LandingData(..))
import Gargantext.Components.Data.Lang (Lang(..))
import Gargantext.Pages.Home.States (State(..))
import Network.HTTP.Affjax (AJAX)
import React (ReactElement)
import React.DOM (a, div, h3, i, img, p, span, text)
import React.DOM.Props (Props, _id, aria, className, href, src, target, title)
import Routing.Hash.Aff (setHash)
import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec)
......@@ -31,11 +23,7 @@ data Action
| SignUp
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 \state -> state
......@@ -52,5 +40,3 @@ performAction Login _ _ = void do
performAction SignUp _ _ = void do
modifyState \state -> state
......@@ -2,10 +2,6 @@ module Gargantext.Pages.Home.Specs where
import Prelude hiding (div)
import Control.Monad.Cont.Trans (lift)
import Control.Monad.Eff.Console (CONSOLE)
import DOM (DOM)
import Gargantext.Components.Lang.Landing.EnUS as En
import Gargantext.Components.Lang.Landing.FrFR as Fr
import Gargantext.Components.Data.Landing (BlockText(..), BlockTexts(..), Button(..), LandingData(..))
......@@ -13,31 +9,21 @@ import Gargantext.Components.Data.Lang (Lang(..))
import Gargantext.Pages.Home.States (State(..))
import Gargantext.Pages.Home.Actions (Action(..), performAction)
import Network.HTTP.Affjax (AJAX)
import React (ReactElement)
import React.DOM (a, div, h3, i, img, p, span, text)
import React.DOM.Props (Props, _id, aria, className, href, src, target, title)
import Routing.Hash.Aff (setHash)
import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec)
-- Layout |
layoutLanding :: forall props eff . Lang -> Spec ( console :: CONSOLE
, ajax :: AJAX
, dom :: DOM
| eff
) State props Action
layoutLanding :: forall props. Lang -> Spec State props Action
layoutLanding FR = layoutLanding' Fr.landingData
layoutLanding EN = layoutLanding' En.landingData
------------------------------------------------------------------------
layoutLanding' :: forall props eff . LandingData -> Spec ( console :: CONSOLE
, ajax :: AJAX
, dom :: DOM
| eff
) State props Action
layoutLanding' :: forall props. LandingData -> Spec State props Action
layoutLanding' hd = simpleSpec performAction render
where
render :: Render State props Action
......
......@@ -2,22 +2,15 @@ module Gargantext.Pages.Home.States where
import Prelude hiding (div)
import Control.Monad.Cont.Trans (lift)
import Control.Monad.Eff.Console (CONSOLE)
import DOM (DOM)
import Gargantext.Components.Lang.Landing.EnUS as En
import Gargantext.Components.Lang.Landing.FrFR as Fr
import Gargantext.Components.Data.Landing (BlockText(..), BlockTexts(..), Button(..), LandingData(..))
import Gargantext.Components.Data.Lang (Lang(..))
import Network.HTTP.Affjax (AJAX)
import React (ReactElement)
import React.DOM (a, div, h3, i, img, p, span, text)
import React.DOM.Props (Props, _id, aria, className, href, src, target, title)
import Routing.Hash.Aff (setHash)
import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec)
newtype State = State
{ userName :: String
, password :: String
......@@ -29,5 +22,3 @@ initialState = State
{userName : ""
, password : ""
}
......@@ -2,10 +2,6 @@ module Gargantext.Pages.Layout.Actions where
import Prelude hiding (div)
import Control.Monad.Cont.Trans (lift)
import Control.Monad.Eff.Class (liftEff)
import Control.Monad.Eff.Console (CONSOLE, log)
import DOM (DOM)
import Data.Array (length)
import Data.Either (Either(..))
import Data.Lens (Prism', prism)
......@@ -27,7 +23,6 @@ import Gargantext.Pages.Layout.States (AppState)
import Gargantext.Pages.Layout.Specs.Search as S
import Gargantext.Router (Routes)
import Network.HTTP.Affjax (AJAX)
import Thermite (PerformAction, modifyState)
......@@ -54,11 +49,7 @@ data Action
| NgramsA NG.Action
performAction :: forall eff props. PerformAction ( dom :: DOM
, ajax :: AJAX
, console :: CONSOLE
| eff
) AppState props Action
performAction :: forall props. PerformAction AppState props Action
performAction (SetRoute route) _ _ = void do
modifyState $ _ {currentRoute = pure route}
performAction (Search s) _ _ = void do
......@@ -187,6 +178,3 @@ _NgramsA = prism NgramsA \action ->
case action of
NgramsA caction -> Right caction
_-> Left action
......@@ -2,8 +2,6 @@ module Gargantext.Pages.Layout.Specs where
import Prelude hiding (div)
import Control.Monad.Eff.Console (CONSOLE)
import DOM (DOM)
import Data.Foldable (fold, intercalate)
import Data.Lens (over)
import Data.Maybe (Maybe(Nothing, Just))
......@@ -57,14 +55,13 @@ import Gargantext.Pages.Layout.States (AppState, E)
import Gargantext.Pages.Layout.Specs.Search as S
import Gargantext.Router (Routes(..))
import Network.HTTP.Affjax (AJAX)
import React (ReactElement)
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 Thermite (Render, Spec, _render, defaultPerformAction, defaultRender, focus, simpleSpec, withState)
import Unsafe.Coerce (unsafeCoerce)
layoutSpec :: forall eff props. Spec (E eff) AppState props Action
layoutSpec :: forall props. Spec AppState props Action
layoutSpec =
fold
[ routingSpec
......@@ -75,22 +72,18 @@ layoutSpec =
]
]
where
container :: Spec (E eff) AppState props Action -> Spec (E eff) AppState props Action
container :: Spec AppState props Action -> Spec AppState props Action
container = over _render \render d p s c ->
(render d p s c)
pagesComponent :: forall props eff. AppState -> Spec (E eff) AppState props Action
pagesComponent :: forall props. AppState -> Spec AppState props Action
pagesComponent s =
case s.currentRoute of
Just route -> selectSpec route
Nothing -> selectSpec Home
where
selectSpec :: Routes -> Spec ( ajax :: AJAX
, console :: CONSOLE
, dom :: DOM
| eff
) AppState props Action
selectSpec :: Routes -> Spec AppState props Action
selectSpec CorpusAnalysis = layout0 $ focus _corpusState _corpusAction CA.spec'
selectSpec Login = focus _loginState _loginAction LN.renderSpec
selectSpec Home = layout0 $ focus _landingState _LandingA (L.layoutLanding EN)
......@@ -107,11 +100,11 @@ pagesComponent s =
-- selectSpec _ = simpleSpec defaultPerformAction defaultRender
routingSpec :: forall props eff. Spec (ajax :: AJAX, console :: CONSOLE, dom :: DOM |eff) AppState props Action
routingSpec :: forall props. Spec AppState props Action
routingSpec = simpleSpec performAction defaultRender
layout0 :: forall eff props. Spec (E eff) AppState props Action
-> Spec (E eff) AppState props Action
layout0 :: forall props. Spec AppState props Action
-> Spec AppState props Action
layout0 layout =
fold
[ layoutSidebar divSearchBar
......@@ -124,7 +117,7 @@ layout0 layout =
outerLayout =
cont $ fold
[ withState \st ->
if ((\(LN.State s) -> s.loginC) st.loginState == true)
if ((\(LN.State s) -> s.loginC) st.loginState == true)
then ls as
else outerLayout1
, rs bs ]
......@@ -136,8 +129,8 @@ layout0 layout =
bs = innerLayout $ layout
innerLayout :: Spec (E eff) AppState props Action
-> Spec (E eff) AppState props Action
innerLayout :: Spec AppState props Action
-> Spec AppState props Action
innerLayout = over _render \render d p s c ->
[ div [_id "page-wrapper"]
[
......@@ -145,7 +138,7 @@ layout0 layout =
]
]
layoutSidebar :: forall props eff. Spec (E eff) AppState props Action
layoutSidebar :: forall props. Spec AppState props Action
-> Spec (E eff) AppState props Action
layoutSidebar = over _render \render d p s c ->
[ div [ _id "dafixedtop"
......@@ -280,7 +273,7 @@ liNav (LiNav { title : title'
]
-- TODO put the search form in the center of the navBar
divSearchBar :: forall props eff. Spec (ajax :: AJAX, console :: CONSOLE, dom :: DOM |eff) AppState props Action
divSearchBar :: forall props. Spec AppState props Action
divSearchBar = simpleSpec performAction render
where
render :: Render AppState props Action
......@@ -324,7 +317,7 @@ divDropdownRight d =
]
]
layoutFooter :: forall props eff. Spec (ajax :: AJAX, console :: CONSOLE, dom :: DOM |eff) AppState props Action
layoutFooter :: forall props. Spec AppState props Action
layoutFooter = simpleSpec performAction render
where
render :: Render AppState props Action
......@@ -349,5 +342,3 @@ layoutFooter = simpleSpec performAction render
, text "."
]
]
......@@ -2,13 +2,6 @@ module Gargantext.Pages.Layout.Specs.AddCorpus.Actions 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.Cont.Trans (lift)
import Control.Monad.Eff.Class (liftEff)
import Control.Monad.Eff.Console (CONSOLE)
import DOM (DOM)
import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, encodeJson, jsonEmptyObject, (.?), (:=), (~>))
import Data.Either (Either(..))
import Data.HTTP.Method (Method(..))
......@@ -19,12 +12,9 @@ import Data.MediaType.Common (applicationJSON)
import Gargantext.Components.Modals.Modal (modalHide)
import Gargantext.Pages.Layout.Specs.AddCorpus.States
import Network.HTTP.Affjax (AJAX, affjax, defaultRequest)
import Network.HTTP.RequestHeader (RequestHeader(..))
import React (ReactElement)
import React.DOM (button, div, h3, h5, li, span, text, ul)
import React.DOM.Props (_data, _id, _type, aria, className, onClick, role)
import Routing.Hash.Aff (setHash)
import Thermite (PerformAction, Render, Spec, _render, cotransform, modifyState, simpleSpec)
data Action
......@@ -34,10 +24,7 @@ data Action
| LoadDatabaseDetails
| GO
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
......@@ -84,7 +71,7 @@ instance encodeJsonQueryString :: EncodeJson QueryString where
getDatabaseDetails :: forall eff. QueryString -> Aff (console::CONSOLE,ajax :: AJAX | eff) (Either String (Array Response))
getDatabaseDetails :: QueryString -> Aff (Either String (Array Response))
getDatabaseDetails reqBody = do
let token = "eyJ0eXAiOiJKV1QiLCJhbGciOiJIUzI1NiJ9.eyJleHAiOjE1MTk5OTg1ODMsInVzZXJfaWQiOjUsImVtYWlsIjoiYWxleGFuZHJlLmRlbGFub2VAaXNjcGlmLmZyIiwidXNlcm5hbWUiOiJkZXZlbG9wZXIifQ.Os-3wuFNSmRIxCZi98oFNBu2zqGc0McO-dgDayozHJg"
affResp <- liftAff $ attempt $ affjax defaultRequest
......@@ -106,6 +93,3 @@ getDatabaseDetails reqBody = do
liftAff $ log $ "GET /api response: " <> show a.response
let res = decodeJson a.response
pure res
......@@ -2,13 +2,7 @@ module Gargantext.Pages.Layout.Specs.AddCorpus.Specs 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.Cont.Trans (lift)
import Control.Monad.Eff.Class (liftEff)
import Control.Monad.Eff.Console (CONSOLE)
import DOM (DOM)
import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, encodeJson, jsonEmptyObject, (.?), (:=), (~>))
import Data.Either (Either(..))
import Data.HTTP.Method (Method(..))
......@@ -21,22 +15,19 @@ import Gargantext.Components.Modals.Modal (modalHide)
import Gargantext.Pages.Layout.Specs.AddCorpus.States
import Gargantext.Pages.Layout.Specs.AddCorpus.Actions
import Network.HTTP.Affjax (AJAX, affjax, defaultRequest)
import Network.HTTP.RequestHeader (RequestHeader(..))
import React (ReactElement)
import React.DOM (button, div, h3, h5, li, span, text, ul)
import React.DOM.Props (_data, _id, _type, aria, className, onClick, role)
import Routing.Hash.Aff (setHash)
import Thermite (PerformAction, Render, Spec, _render, cotransform, modifyState, simpleSpec)
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 "addCorpus", className $ "modal myModal" <> if sm then "" else " fade"
, role "dialog"
, _data {show : true}
][ div [ className "modal-dialog", role "document"]
[ div [ className "modal-content"]
[ div [ className "modal-content"]
[ div [ className "modal-header"]
[ h5 [ className "modal-title" ] [ text $ t ]
, button [ _type "button"
......@@ -52,7 +43,7 @@ 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 "Search Results" layoutAddcorpus
......@@ -102,7 +93,7 @@ layoutModal state =
]
layoutAddcorpus :: forall props eff . Spec (console::CONSOLE, ajax::AJAX, dom::DOM | eff) State props Action
layoutAddcorpus :: forall props. Spec State props Action
layoutAddcorpus = simpleSpec performAction render
where
render :: Render State props Action
......@@ -128,6 +119,3 @@ layoutAddcorpus = simpleSpec performAction render
span [] [text o.name]
, span [className "badge badge-default badge-pill"] [ text $ show o.count]
]
module Gargantext.Pages.Layout.Specs.Search where
import Control.Monad.Aff.Console (CONSOLE)
import Control.Monad.Cont.Trans (lift)
import DOM (DOM)
import Network.HTTP.Affjax (AJAX)
import Prelude hiding (div)
import React.DOM (br', button, div, h3, input, text, i, span, img)
import React.DOM.Props (_id, _type, className, name, onClick, onInput, placeholder, value, aria, src, title)
import Routing.Hash.Aff (setHash)
import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec)
import Unsafe.Coerce (unsafeCoerce)
import Gargantext.Pages.Home as L
......@@ -31,7 +26,7 @@ data Action
| SetQuery 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
......@@ -48,11 +43,7 @@ performAction GO _ _ = void do
unsafeEventValue :: forall event. event -> String
unsafeEventValue e = (unsafeCoerce e).target.value
searchSpec :: forall props eff . Spec ( console :: CONSOLE
, ajax :: AJAX
, dom :: DOM
| eff
) State props Action
searchSpec :: forall props. Spec State props Action
searchSpec = simpleSpec performAction render
where
render :: Render State props Action
......
......@@ -2,8 +2,6 @@ module Gargantext.Pages.Layout.States where
import Prelude hiding (div)
import Control.Monad.Eff.Console (CONSOLE)
import DOM (DOM)
import Data.Lens (Lens', lens)
import Data.Maybe (Maybe(Just))
......@@ -22,14 +20,11 @@ import Gargantext.Pages.Home as L
import Gargantext.Pages.Layout.Specs.Search as S
import Gargantext.Router (Routes(..))
import Network.HTTP.Affjax (AJAX)
type E e = (dom :: DOM, ajax :: AJAX, console :: CONSOLE | e)
type AppState =
{ currentRoute :: Maybe Routes
, landingState :: L.State
, loginState :: LN.State
, loginState :: LN.State
, addCorpusState :: AC.State
, docViewState :: DV.State
, searchState :: S.State
......@@ -108,5 +103,3 @@ _graphExplorerState = lens (\s -> s.graphExplorerState) (\s ss -> s{graphExplore
_ngramState :: Lens' AppState NG.State
_ngramState = lens (\s -> s.ngramState) (\s ss -> s{ngramState = ss})
......@@ -3,17 +3,11 @@ module Gargantext.Router where
import Prelude
import Control.Alt ((<|>))
import Control.Monad.Eff (Eff)
import Control.Monad.Eff.Class (liftEff)
import Control.Monad.Eff.Console (CONSOLE, log)
import DOM (DOM)
import DOM.HTML (window)
import DOM.HTML.Window (localStorage)
import DOM.WebStorage.Storage (getItem)
import Effect (Effect)
import Effect.Class (liftEffect)
import Data.Int (floor)
import Data.Maybe (Maybe(..))
import Routing.Match (Match)
import Routing.Match.Class (lit, num)
data Routes
= Home
......@@ -64,16 +58,7 @@ routing =
where
route str = lit "" *> lit str
routeHandler :: forall e. ( Maybe Routes -> Routes -> Eff
( dom :: DOM
, console :: CONSOLE
| e
) Unit
) -> Maybe Routes -> Routes -> Eff
( dom :: DOM
, console :: CONSOLE
| e
) Unit
routeHandler :: (Maybe Routes -> Routes -> Effect Unit) -> Maybe Routes -> Routes -> Effect Unit
routeHandler dispatchAction old new = do
liftEff $ log $ "change route : " <> show new
w <- window
......
......@@ -2,14 +2,7 @@ module Main where
import Prelude
import Control.Monad.Eff (Eff)
import Control.Monad.Eff.Console (CONSOLE)
import DOM (DOM)
import DOM.HTML (window) as DOM
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 Effect (Effect)
import Data.Maybe (fromJust)
import Gargantext.Pages.Layout (dispatchAction)
......@@ -17,7 +10,6 @@ import Gargantext.Pages.Layout.Specs (layoutSpec)
import Gargantext.Pages.Layout.States (initAppState)
import Gargantext.Router (routeHandler, routing)
import Network.HTTP.Affjax (AJAX)
import Partial.Unsafe (unsafePartial)
import React as R
import ReactDOM as RDOM
......@@ -25,7 +17,7 @@ import Routing (matches)
import Routing.Hash (getHash, setHash)
import Thermite as T
main :: forall e. Eff (dom:: DOM, console :: CONSOLE, ajax :: AJAX | e ) Unit
main :: Effect Unit
main = do
case T.createReactSpec layoutSpec initAppState of
{ spec, dispatcher } -> void $ do
......
......@@ -734,7 +734,7 @@ core-js@^2.4.0, core-js@^2.5.0:
version "2.5.5"
resolved "https://registry.yarnpkg.com/core-js/-/core-js-2.5.5.tgz#b14dde936c640c0579a6b50cabcc132dd6127e3b"
create-react-class@^15.6.2:
create-react-class@^15.6.3:
version "15.6.3"
resolved "https://registry.yarnpkg.com/create-react-class/-/create-react-class-15.6.3.tgz#2d73237fb3f970ae6ebe011a9e66f46dbca80036"
dependencies:
......@@ -754,11 +754,12 @@ detect-indent@^4.0.0:
dependencies:
repeating "^2.0.0"
echarts-for-react@^2.0.0:
version "2.0.8"
resolved "https://registry.yarnpkg.com/echarts-for-react/-/echarts-for-react-2.0.8.tgz#cf56641d8a3bc50852310aeec06a464c4fc72b67"
echarts-for-react@^2.0.14:
version "2.0.14"
resolved "https://registry.yarnpkg.com/echarts-for-react/-/echarts-for-react-2.0.14.tgz#6df7a31eea43ef35321e20a5854109cbc52c9df3"
dependencies:
element-resize-event "2.0.9"
fast-deep-equal "^2.0.1"
size-sensor "^0.2.0"
echarts@^3.8.5:
version "3.8.5"
......@@ -772,10 +773,6 @@ element-resize-detector@latest:
dependencies:
batch-processor "^1.0.0"
element-resize-event@2.0.9:
version "2.0.9"
resolved "https://registry.yarnpkg.com/element-resize-event/-/element-resize-event-2.0.9.tgz#2f5e1581a296eb5275210c141bc56342e218f876"
emojis-list@^2.0.0:
version "2.1.0"
resolved "https://registry.yarnpkg.com/emojis-list/-/emojis-list-2.1.0.tgz#4daa4d9db00f9819880c79fa457ae5b09a1fd389"
......@@ -794,6 +791,10 @@ esutils@^2.0.2:
version "2.0.2"
resolved "https://registry.yarnpkg.com/esutils/-/esutils-2.0.2.tgz#0abf4f1caa5bcb1f7a9d8acc6dea4faaa04bac9b"
fast-deep-equal@^2.0.1:
version "2.0.1"
resolved "https://registry.yarnpkg.com/fast-deep-equal/-/fast-deep-equal-2.0.1.tgz#7b05218ddf9667bf7f370bf7fdb2cb15fdd0aa49"
fbjs@^0.8.16:
version "0.8.16"
resolved "https://registry.yarnpkg.com/fbjs/-/fbjs-0.8.16.tgz#5e67432f550dc41b572bf55847b8aca64e5337db"
......@@ -839,12 +840,12 @@ iconv-lite@~0.4.13:
version "0.4.18"
resolved "https://registry.yarnpkg.com/iconv-lite/-/iconv-lite-0.4.18.tgz#23d8656b16aae6742ac29732ea8f0336a4789cf2"
imports-loader@^0.7.1:
version "0.7.1"
resolved "https://registry.yarnpkg.com/imports-loader/-/imports-loader-0.7.1.tgz#f204b5f34702a32c1db7d48d89d5e867a0441253"
imports-loader@^0.8.0:
version "0.8.0"
resolved "https://registry.yarnpkg.com/imports-loader/-/imports-loader-0.8.0.tgz#030ea51b8ca05977c40a3abfd9b4088fe0be9a69"
dependencies:
loader-utils "^1.0.2"
source-map "^0.5.6"
source-map "^0.6.1"
invariant@^2.2.2:
version "2.2.4"
......@@ -960,11 +961,10 @@ promise@^7.1.1:
dependencies:
asap "~2.0.3"
prop-types@15.6.0:
version "15.6.0"
resolved "https://registry.yarnpkg.com/prop-types/-/prop-types-15.6.0.tgz#ceaf083022fc46b4a35f69e13ef75aed0d639856"
prop-types@15.6.2:
version "15.6.2"
resolved "https://registry.yarnpkg.com/prop-types/-/prop-types-15.6.2.tgz#05d5ca77b4453e985d60fc7ff8c859094a497102"
dependencies:
fbjs "^0.8.16"
loose-envify "^1.3.1"
object-assign "^4.1.1"
......@@ -976,16 +976,16 @@ prop-types@^15.6.0:
loose-envify "^1.3.1"
object-assign "^4.1.1"
react-dom@^16.2.0:
version "16.2.0"
resolved "https://registry.yarnpkg.com/react-dom/-/react-dom-16.2.0.tgz#69003178601c0ca19b709b33a83369fe6124c044"
react-dom@^16.4.2:
version "16.4.2"
resolved "https://registry.yarnpkg.com/react-dom/-/react-dom-16.4.2.tgz#4afed569689f2c561d2b8da0b819669c38a0bda4"
dependencies:
fbjs "^0.8.16"
loose-envify "^1.1.0"
object-assign "^4.1.1"
prop-types "^15.6.0"
react-echarts-v3@^1.0.14:
react-echarts-v3@^1.0.19:
version "1.0.19"
resolved "https://registry.yarnpkg.com/react-echarts-v3/-/react-echarts-v3-1.0.19.tgz#04148f16e3e7f01c2f6f3e6f0654bb32f238c2dc"
dependencies:
......@@ -996,9 +996,9 @@ react-sigma@^1.2.30:
version "1.2.30"
resolved "https://registry.yarnpkg.com/react-sigma/-/react-sigma-1.2.30.tgz#794f88e796c4f763158afe404d10d9635f848846"
react@^16.2.0:
version "16.2.0"
resolved "https://registry.yarnpkg.com/react/-/react-16.2.0.tgz#a31bd2dab89bff65d42134fa187f24d054c273ba"
react@^16.4.2:
version "16.4.2"
resolved "https://registry.yarnpkg.com/react/-/react-16.4.2.tgz#2cd90154e3a9d9dd8da2991149fdca3c260e129f"
dependencies:
fbjs "^0.8.16"
loose-envify "^1.1.0"
......@@ -1049,6 +1049,10 @@ setimmediate@^1.0.5:
version "1.0.5"
resolved "https://registry.yarnpkg.com/setimmediate/-/setimmediate-1.0.5.tgz#290cbb232e306942d7d7ea9b83732ab7856f8285"
size-sensor@^0.2.0:
version "0.2.0"
resolved "https://registry.yarnpkg.com/size-sensor/-/size-sensor-0.2.0.tgz#f929368b025b0e69013f30fa24dd473008885eb3"
slash@^1.0.0:
version "1.0.0"
resolved "https://registry.yarnpkg.com/slash/-/slash-1.0.0.tgz#c41f2f6c39fc16d1cd17ad4b5d896114ae470d55"
......@@ -1063,6 +1067,10 @@ source-map@^0.5.6, source-map@^0.5.7:
version "0.5.7"
resolved "https://registry.yarnpkg.com/source-map/-/source-map-0.5.7.tgz#8a039d2d1021d22d1ea14c80d8ea468ba2ef3fcc"
source-map@^0.6.1:
version "0.6.1"
resolved "https://registry.yarnpkg.com/source-map/-/source-map-0.6.1.tgz#74722af32e9614e9c287a8d0bbde48b5e2f1a263"
strip-ansi@^3.0.0:
version "3.0.1"
resolved "https://registry.yarnpkg.com/strip-ansi/-/strip-ansi-3.0.1.tgz#6a385fb8853d952d5ff05d0e8aaf94278dc63dcf"
......
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