Commit 69d93c2b authored by Alexandre Delanoë's avatar Alexandre Delanoë

[Merge]

parents f962c84b ba53e379
...@@ -8,7 +8,7 @@ ...@@ -8,7 +8,7 @@
], ],
"dependencies": { "dependencies": {
"purescript-console": "^4.1.0", "purescript-console": "^4.1.0",
"purescript-thermite": "https://github.com/np/purescript-thermite.git#migrate_0_12", "purescript-thermite": "https://github.com/np/purescript-thermite.git#hide",
"purescript-affjax": "^7.0.0", "purescript-affjax": "^7.0.0",
"purescript-routing": "^8.0.0", "purescript-routing": "^8.0.0",
"purescript-argonaut": "^4.0.1", "purescript-argonaut": "^4.0.1",
......
...@@ -39,6 +39,7 @@ ...@@ -39,6 +39,7 @@
"babel-runtime": "^6.26.0", "babel-runtime": "^6.26.0",
"babelify": "^8.0.0", "babelify": "^8.0.0",
"bower": "^1.8.4", "bower": "^1.8.4",
"http-server": "^0.11.1",
"pulp": "^12.3.0", "pulp": "^12.3.0",
"purescript": "^0.12.0" "purescript": "^0.12.0"
} }
......
...@@ -46,15 +46,12 @@ initialState = State ...@@ -46,15 +46,12 @@ initialState = State
} }
data Action data Action
= NoOp = Login
| Login
| SetUserName String | SetUserName String
| SetPassword String | SetPassword String
performAction :: forall props. PerformAction State props Action performAction :: PerformAction State {} Action
performAction NoOp _ _ = void do
modifyState identity
performAction (SetUserName usr) _ _ = void do performAction (SetUserName usr) _ _ = void do
modifyState \(State state) -> State $ state { username = usr } modifyState \(State state) -> State $ state { username = usr }
...@@ -107,13 +104,13 @@ modalSpec sm t = over _render \render d p s c -> ...@@ -107,13 +104,13 @@ modalSpec sm t = over _render \render d p s c ->
] ]
] ]
spec' :: forall props. Spec State props Action spec' :: Spec State {} Action
spec' = modalSpec true "Login" renderSpec spec' = modalSpec true "Login" renderSpec
renderSpec :: forall props. Spec State props Action renderSpec :: Spec State {} Action
renderSpec = simpleSpec performAction render renderSpec = simpleSpec performAction render
where where
render :: Render State props Action render :: Render State {} Action
render dispatch _ (State state) _ = render dispatch _ (State state) _ =
[ [
div [className "row"] div [className "row"]
......
...@@ -9,7 +9,7 @@ import Data.Tuple (Tuple(..)) ...@@ -9,7 +9,7 @@ import Data.Tuple (Tuple(..))
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)
import Thermite (PerformAction, Render, Spec, _render, cotransform, focus, simpleSpec, withState) import Thermite (PerformAction, Render, Spec, _render, modifyState, focus, simpleSpec, withState)
type State = Int type State = Int
...@@ -34,8 +34,7 @@ tab sid iid (Tuple name spec) = over _render tabRender spec ...@@ -34,8 +34,7 @@ tab sid iid (Tuple name spec) = over _render tabRender spec
performAction :: forall props. PerformAction State props Action performAction :: forall props. PerformAction State props Action
performAction (ChangeTab i) _ _ = void do performAction (ChangeTab i) _ _ = void $ modifyState $ const i
cotransform \_ -> i
render :: forall state props action. State -> List (Tuple String (Spec 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 = render at ls d p s c =
......
...@@ -3,11 +3,15 @@ module Gargantext.Components.Tree where ...@@ -3,11 +3,15 @@ module Gargantext.Components.Tree where
import Prelude hiding (div) import Prelude hiding (div)
import Affjax (defaultRequest, printResponseFormatError, request) import Affjax (defaultRequest, printResponseFormatError, request)
import Affjax.RequestBody (RequestBody(..))
import Affjax.ResponseFormat as ResponseFormat import Affjax.ResponseFormat as ResponseFormat
import Data.Argonaut (class DecodeJson, decodeJson, (.?)) import Control.Monad.Cont.Trans (lift)
import Data.Argonaut (class DecodeJson, Json, decodeJson, encodeJson, (.?))
import Data.Argonaut.Core (Json)
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.HTTP.Method (Method(..)) import Data.HTTP.Method (Method(..))
import Data.Tuple (Tuple(..)) import Data.Maybe (Maybe(..))
import Data.Newtype (class Newtype)
import Effect (Effect) import Effect (Effect)
import Effect.Aff (Aff) import Effect.Aff (Aff)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
...@@ -15,58 +19,66 @@ import Effect.Console (log) ...@@ -15,58 +19,66 @@ import Effect.Console (log)
import React (ReactElement) import React (ReactElement)
import React.DOM (a, div, i, li, text, ul) import React.DOM (a, div, i, li, text, ul)
import React.DOM.Props (Props, className, href, onClick) import React.DOM.Props (Props, className, href, onClick)
import Thermite (PerformAction, Render, Spec, cotransform, simpleSpec) import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec)
import Gargantext.Config (NodeType(..), toUrl, readNodeType, End(..), ApiVersion)
type Name = String type Name = String
type Open = Boolean type Open = Boolean
type URL = String type URL = String
type ID = Int type ID = Int
data NTree a = NLeaf a | NNode ID Open Name (Array (NTree a)) data NTree a = NTree a (Array (NTree a))
type FTree = NTree (Tuple Name URL) type FTree = NTree LNode
data Action = ToggleFolder ID data Action = ToggleFolder ID --| Initialize
type State = FTree type State = FTree
initialState :: State initialState :: State
initialState = NLeaf (Tuple "" "") initialState = NTree (LNode {id : 1, name : "", nodeType : "", open : true}) []
performAction :: forall props. PerformAction State props Action performAction :: PerformAction State {} Action
performAction (ToggleFolder i) _ _ = void $ performAction (ToggleFolder i) _ _ = void $ modifyState $ toggleNode i
cotransform (\td -> toggleNode i td)
toggleNode :: forall t10. Int -> NTree t10 -> NTree t10 -- performAction Initialize _ _ = void $ do
toggleNode sid (NNode iid open name ary) = -- s <- lift $ loadDefaultNode
NNode iid nopen name $ map (toggleNode sid) ary -- case s of
where -- Left err -> modifyState identity
nopen = if sid == iid then not open else open -- Right d -> modifyState (\state -> d)
toggleNode sid a = a
toggleNode :: Int -> NTree LNode -> NTree LNode
toggleNode sid (NTree (LNode {id, name, nodeType, open}) ary) =
NTree (LNode {id,name, nodeType, open : nopen}) $ map (toggleNode sid) ary
where
nopen = if sid == id then not open else open
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- Realistic Tree for the UI -- Realistic Tree for the UI
exampleTree :: NTree (Tuple String String) exampleTree :: NTree LNode
exampleTree = exampleTree = NTree (LNode {id : 1, name : "", nodeType : "", open : false}) []
NNode 1 true "françois.pineau"
[ annuaire 2 "Annuaire"
, corpus 3 "IMT publications"
]
annuaire :: Int -> String -> NTree (Tuple String String) -- exampleTree :: NTree LNode
annuaire n name = NNode n false name -- exampleTree =
[ NLeaf (Tuple "IMT community" "#/docView") -- NTree 1 true "françois.pineau"
] -- [ --annuaire 2 "Annuaire"
-- --, corpus 3 "IMT publications"
-- ]
corpus :: Int -> String -> NTree (Tuple String String) -- annuaire :: Int -> String -> NTree (Tuple String String)
corpus n name = NNode n false name -- annuaire n name = NTree n false name
[ NLeaf (Tuple "Facets" "#/corpus") -- [ NTree (Tuple "IMT community" "#/docView")
, NLeaf (Tuple "Dashboard" "#/dashboard") -- ]
, NLeaf (Tuple "Graph" "#/graphExplorer")
] -- corpus :: Int -> String -> NTree (Tuple String String)
-- corpus n name = NTree (LNode {id : n, name, nodeType : "", open : false})
-- [ NTree (Tuple "Facets" "#/corpus") []
-- , NTree (Tuple "Dashboard" "#/dashboard") []
-- , NTree (Tuple "Graph" "#/graphExplorer") []
-- ]
------------------------------------------------------------------------ ------------------------------------------------------------------------
...@@ -89,27 +101,32 @@ nodeOptionsView activated = case activated of ...@@ -89,27 +101,32 @@ nodeOptionsView activated = case activated of
false -> [] false -> []
treeview :: forall props. Spec State props Action treeview :: Spec State {} Action
treeview = simpleSpec performAction render treeview = simpleSpec performAction render
where where
render :: Render State props Action render :: Render State {} Action
render dispatch _ state _ = render dispatch _ state _ =
[div [className "tree"] [toHtml dispatch state]] [div [className "tree"] [toHtml dispatch state]]
toHtml :: (Action -> Effect Unit) -> FTree -> ReactElement toHtml :: (Action -> Effect Unit) -> FTree -> ReactElement
toHtml d (NLeaf (Tuple name link)) = toHtml d (NTree (LNode {id, name, nodeType, open}) []) =
li [] ul []
[ a [ href link] [
( [ text (name <> " ") li []
] <> nodeOptionsView false [
) a [ href (toUrl Front (readNodeType nodeType) id)]
( [ text (name <> " ")
] <> nodeOptionsView false
)
]
] ]
toHtml d (NNode id open name ary) = toHtml d (NTree (LNode {id, name, nodeType, open}) ary) =
ul [ ] ul [ ]
[ li [] $ [ li [] $
( [ a [onClick $ (\e-> d $ ToggleFolder id)] [i [fldr open] []] ( [ a [onClick $ (\e-> d $ ToggleFolder id)] [i [fldr open] []]
, text $ " " <> name <> " " , a [ href (toUrl Front (readNodeType nodeType) id )]
[ text $ " " <> name <> " " ]
] <> nodeOptionsCorp false <> ] <> nodeOptionsCorp false <>
if open then if open then
map (toHtml d) ary map (toHtml d) ary
...@@ -121,21 +138,31 @@ fldr :: Boolean -> Props ...@@ -121,21 +138,31 @@ fldr :: Boolean -> Props
fldr open = if open then className "fas fa-folder-open" else className "fas fa-folder" fldr open = if open then className "fas fa-folder-open" else className "fas fa-folder"
newtype LNode = LNode {id :: Int, name :: String} newtype LNode = LNode {id :: Int, name :: String, nodeType :: String, open :: Boolean}
-- derive instance newtypeLNode :: Newtype LNode _ derive instance newtypeLNode :: Newtype LNode _
instance decodeJsonLNode :: DecodeJson LNode where instance decodeJsonLNode :: DecodeJson LNode where
decodeJson json = do decodeJson json = do
obj <- decodeJson json obj <- decodeJson json
id_ <- obj .? "id" id_ <- obj .? "id"
name <- obj .? "name" name <- obj .? "name"
pure $ LNode {id : id_, name} nodeType <- obj .? "type"
pure $ LNode {id : id_, name, nodeType, open : true}
instance decodeJsonFTree :: DecodeJson (NTree LNode) where
decodeJson json = do
obj <- decodeJson json
node <- obj .? "node"
nodes <- obj .? "children"
node' <- decodeJson node
nodes' <- decodeJson nodes
pure $ NTree node' nodes'
loadDefaultNode :: Aff (Either String (Array LNode)) loadDefaultNode :: Aff (Either String (NTree LNode))
loadDefaultNode = do loadDefaultNode = do
res <- request $ defaultRequest res <- request $ defaultRequest
{ url = "http://localhost:8008/user" { url = toUrl Back Tree 1
, responseFormat = ResponseFormat.json , responseFormat = ResponseFormat.json
, method = Left GET , method = Left GET
, headers = [] , headers = []
...@@ -151,6 +178,93 @@ loadDefaultNode = do ...@@ -151,6 +178,93 @@ loadDefaultNode = do
let obj = decodeJson json let obj = decodeJson json
pure obj pure obj
----- TREE CRUD Operations
renameNode :: Aff (Either String (Int)) --- need to change return type herre
renameNode = do
res <- request $ defaultRequest
{ url = toUrl Back Tree 1
, responseFormat = ResponseFormat.json
, method = Left PUT
, headers = []
}
case res.body of
Left err -> do
_ <- liftEffect $ log $ printResponseFormatError err
pure $ Left $ printResponseFormatError err
Right json -> do
--_ <- liftEffect $ log $ show a.status
--_ <- liftEffect $ log $ show a.headers
--_ <- liftEffect $ log $ show a.body
let obj = decodeJson json
pure obj
deleteNode :: Aff (Either String (Int))
deleteNode = do
res <- request $ defaultRequest
{ url = toUrl Back Tree 1
, responseFormat = ResponseFormat.json
, method = Left DELETE
, headers = []
}
case res.body of
Left err -> do
_ <- liftEffect $ log $ printResponseFormatError err
pure $ Left $ printResponseFormatError err
Right json -> do
--_ <- liftEffect $ log $ show a.status
--_ <- liftEffect $ log $ show a.headers
--_ <- liftEffect $ log $ show a.body
let obj = decodeJson json
pure obj
deleteNodes :: String -> Aff (Either String Int)
deleteNodes reqbody = do
res <- request $ defaultRequest
{ url = toUrl Back Tree 1
, responseFormat = ResponseFormat.json
, method = Left DELETE
, headers = []
, content = Just $ Json $ encodeJson reqbody
}
case res.body of
Left err -> do
_ <- liftEffect $ log $ printResponseFormatError err
pure $ Left $ printResponseFormatError err
Right json -> do
--_ <- liftEffect $ log $ show a.status
--_ <- liftEffect $ log $ show a.headers
--_ <- liftEffect $ log $ show a.body
let obj = decodeJson json
pure obj
createNode :: String -> Aff (Either String (Int))
createNode reqbody= do
res <- request $ defaultRequest
{ url = toUrl Back Tree 1
, responseFormat = ResponseFormat.json
, method = Left POST
, headers = []
, content = Just $ Json $ encodeJson reqbody
}
case res.body of
Left err -> do
_ <- liftEffect $ log $ printResponseFormatError err
pure $ Left $ printResponseFormatError err
Right json -> do
--_ <- liftEffect $ log $ show a.status
--_ <- liftEffect $ log $ show a.headers
--_ <- liftEffect $ log $ show a.body
let obj = decodeJson json
pure obj
fnTransform :: LNode -> FTree fnTransform :: LNode -> FTree
fnTransform (LNode r) = NNode r.id false r.name [] fnTransform n = NTree n []
{- | Main Configuration of Gargantext Front-End
The main function to use for internal link in the Front-End
developpement is : toUrl.
* Example usage:
- for Mock config:
- toUrl Front Corpus 3 == "http://localhost:2015/corpus/3"
- (this mode supposes you have the mock haskell backend running)
- for Dev config:
- toUrl Front Corpus 3 == "http://localhost:8008/corpus/3"
- (this mode supposes you have the dev haskell backend running)
- for Prod config:
- toUrl Front Corpus 3 == "https://gargantext.org:8080/corpus/3"
- (this mode supposes you have a prod haskell backend running on the specified url)
-}
module Gargantext.Config where
import Prelude ( class Eq, class Ord, class Show
, compare, eq, show, (<>), identity)
import Data.Map (Map)
import Data.Map as DM
import Data.Maybe (maybe)
import Data.Tuple (Tuple(..))
------------------------------------------------------------
-- | Versions will used later after the release
data ApiVersion = V10 | V11
instance showApiVersion :: Show ApiVersion where
show V10 = "v1.0"
show V11 = "v1.1"
data End = Back | Front
-- | Main options of the configuration
data Mode = Mock | Dev | Prod
config :: FrontEndConfig
config = mkConfig Dev V10
mkAdress :: Mode -> String
mkAdress Mock = "localhost"
mkAdress Dev = "localhost"
mkAdress Prod = "gargantext.org"
mkPort :: Mode -> Int
mkPort Mock = 2015
mkPort Dev = 8008
mkPort Prod = 8080
mkProto :: Mode -> String
mkProto Mock = "http://"
mkProto Dev = "http://"
mkProto Prod = "https://"
------------------------------------------------------------
urlConfig :: Map NodeType Url
urlConfig = DM.fromFoldable [ Tuple UserPage "user"
, easy Corpus
, easy Project
, easy Document
, easy Annuaire
, easy Individu
, easy Tree
]
where
easy :: NodeType -> Tuple NodeType Url
easy n = Tuple n (show n)
------------------------------------------------------------
type FrontEndConfig = { proto :: String
, port :: Int
, address :: String
, apiVersion :: ApiVersion
, urls :: Map NodeType Url
}
mkConfig :: Mode -> ApiVersion -> FrontEndConfig
mkConfig mode v = { proto : mkProto mode
, address : mkAdress mode
, port : mkPort mode
, apiVersion : v
, urls : urlConfig
}
------------------------------------------------------------
------------------------------------------------------------
-- | Main function to use in the Front-End developpement
-- for more complex urls, use urlConfig and smart constructors
toUrl :: End -> NodeType -> Id -> Url
toUrl end nt i = config.proto <> config.address <> ":" <> show config.port <> end' <> path
where
end' = case end of
Back -> "/api/" <> show config.apiVersion <> "/"
Front -> "/"
path = subPath <> "/" <> show i
subPath = maybe "errorSubPath" identity (DM.lookup nt config.urls)
------------------------------------------------------------
type Url = String
type Id = Int
------------------------------------------------------------
data NodeType = UserPage | Corpus | Document | Annuaire | Individu | Project | Tree | Error
------------------------------------------------------------
instance showNodeType :: Show NodeType where
show UserPage = "user"
show Corpus = "corpus"
show Document = "document"
show Annuaire = "annuaire"
show Individu = "individu"
show Project = "project"
show Tree = "tree"
show Error = "errNodeType"
readNodeType :: String -> NodeType
readNodeType "NodeUser" = UserPage
readNodeType "NodeCorpus" = Corpus
readNodeType "Document" = Document
readNodeType "Annuaire" = Annuaire
readNodeType "Individu" = Individu
readNodeType "Project" = Project
readNodeType "Tree" = Tree
readNodeType _ = Error
instance ordNodeType :: Ord NodeType where
compare n1 n2 = compare (show n1) (show n2)
instance eqNodeType :: Eq NodeType where
eq n1 n2 = eq (show n1) (show n2)
------------------------------------------------------------
...@@ -2,7 +2,6 @@ module Gargantext.Pages.Corpus where ...@@ -2,7 +2,6 @@ module Gargantext.Pages.Corpus where
import Prelude hiding (div) import Prelude hiding (div)
import Data.Array (fold)
import Gargantext.Components.Charts.Options.ECharts (chart) import Gargantext.Components.Charts.Options.ECharts (chart)
import Gargantext.Pages.Corpus.Doc.Facets.Dashboard (globalPublis) import Gargantext.Pages.Corpus.Doc.Facets.Dashboard (globalPublis)
import Gargantext.Pages.Corpus.Doc.Facets as Tab import Gargantext.Pages.Corpus.Doc.Facets as Tab
...@@ -10,10 +9,6 @@ import React.DOM (div, h3, hr, i, p, text) ...@@ -10,10 +9,6 @@ import React.DOM (div, h3, hr, i, p, text)
import React.DOM.Props (className, style) import React.DOM.Props (className, style)
import Thermite (Render, Spec, defaultPerformAction, simpleSpec) import Thermite (Render, Spec, defaultPerformAction, simpleSpec)
type State = Tab.State
type Action = Tab.Action
type Corpus = { title :: String type Corpus = { title :: String
, desc :: String , desc :: String
, query :: String , query :: String
...@@ -21,19 +16,14 @@ type Corpus = { title :: String ...@@ -21,19 +16,14 @@ type Corpus = { title :: String
, authors :: String , authors :: String
} }
initialState :: State spec' :: Spec {} {} Void
initialState = Tab.initialState spec' = corpusSpec <> Tab.pureTab1
spec' :: forall props. Spec Tab.State props Tab.Action
spec' = fold [ corpusSpec
, Tab.tab1
]
corpusSpec :: forall props. Spec Tab.State props Tab.Action corpusSpec :: Spec {} {} Void
corpusSpec = simpleSpec defaultPerformAction render corpusSpec = simpleSpec defaultPerformAction render
where where
render :: Render Tab.State props Tab.Action render :: Render {} {} Void
render dispatch _ state _ = render _ _ _ _ =
[ div [className "row"] [ div [className "row"]
[ div [className "col-md-3"] [ h3 [] [text corpus.title] ] [ div [className "col-md-3"] [ h3 [] [text corpus.title] ]
, div [className "col-md-9"] [ hr [style {height : "2px",backgroundColor : "black"}] ] , div [className "col-md-9"] [ hr [style {height : "2px",backgroundColor : "black"}] ]
......
...@@ -21,28 +21,25 @@ initialState = ...@@ -21,28 +21,25 @@ initialState =
data Action data Action
= NoOp = ChangeString String
| ChangeString String
| ChangeAnotherString String | ChangeAnotherString String
| SetInput String | SetInput String
performAction :: forall props. PerformAction State props Action performAction :: PerformAction State {} Action
performAction NoOp _ _ = pure unit
performAction (ChangeString ps) _ _ = pure unit performAction (ChangeString ps) _ _ = pure unit
performAction (ChangeAnotherString ps) _ _ = pure unit performAction (ChangeAnotherString ps) _ _ = pure unit
performAction (SetInput ps) _ _ = void do performAction (SetInput ps) _ _ = void do
modifyState \( state) -> state { inputValue = ps } modifyState $ _ { inputValue = ps }
docview :: forall props. Spec State props Action docview :: Spec State {} Action
docview = simpleSpec performAction render docview = simpleSpec performAction render
where where
render :: Render State props Action render :: Render State {} Action
render dispatch _ state _ = render dispatch _ state _ =
[ [
div [className "container1"] div [className "container1"]
......
...@@ -11,12 +11,11 @@ import Gargantext.Pages.Corpus.Doc.Facets.Terms as TV ...@@ -11,12 +11,11 @@ import Gargantext.Pages.Corpus.Doc.Facets.Terms as TV
import Gargantext.Components.Tab as Tab import Gargantext.Components.Tab as Tab
data Action data Action
= DocviewA DV.Action = DocviewA DV.Action
| SourceviewA SV.Action | SourceviewA SV.Action
| AuthorviewA AV.Action | AuthorviewA AV.Action
| TermsviewA TV.Action | TermsviewA TV.Action
| TabViewA Tab.Action | TabViewA Tab.Action
| NoOp
_docAction :: Prism' Action DV.Action _docAction :: Prism' Action DV.Action
_docAction = prism DocviewA \ action -> _docAction = prism DocviewA \ action ->
......
...@@ -5,7 +5,7 @@ import Data.Array (fold) ...@@ -5,7 +5,7 @@ import Data.Array (fold)
import Gargantext.Pages.Corpus.Doc.Facets.Documents as D import Gargantext.Pages.Corpus.Doc.Facets.Documents as D
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 (PerformAction, Render, Spec, defaultPerformAction, simpleSpec)
type State = D.State type State = D.State
...@@ -14,13 +14,12 @@ initialState = D.tdata ...@@ -14,13 +14,12 @@ initialState = D.tdata
type Action = D.Action type Action = D.Action
authorSpec :: Spec State {} Action
authorSpec :: forall props. Spec State props Action
authorSpec = simpleSpec defaultPerformAction render authorSpec = simpleSpec defaultPerformAction render
where where
render :: Render State props Action render :: Render State {} Action
render dispatch _ state _ = render dispatch _ state _ =
[ h3 [] [text "AuthorView"]] [ h3 [] [text "AuthorView"]]
authorspec' :: forall props. Spec State props Action authorspec' :: Spec State {} Action
authorspec' = fold [authorSpec, D.layoutDocview] authorspec' = fold [authorSpec, D.layoutDocview]
module Gargantext.Pages.Corpus.Doc.Facets.Dashboard where module Gargantext.Pages.Corpus.Doc.Facets.Dashboard where
import Prelude import Prelude hiding (div)
import Data.Array (zip) import Data.Array (zip)
import Data.Tuple (Tuple(..)) import Data.Tuple (Tuple(..))
...@@ -9,21 +9,11 @@ import Gargantext.Components.Charts.Options.Series ...@@ -9,21 +9,11 @@ import Gargantext.Components.Charts.Options.Series
import Gargantext.Components.Charts.Options.Type (Option) import Gargantext.Components.Charts.Options.Type (Option)
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)
import React.DOM.Props (className) import React.DOM.Props (className)
import Thermite (PerformAction, Render, Spec, simpleSpec) import Thermite (Render, Spec, simpleSpec, defaultPerformAction)
type State = Unit render :: Render {} {} Void
data Action = None
initialState :: State
initialState = unit
performAction :: forall props. PerformAction State props Action
performAction _ _ _ = pure unit
render :: forall props. Render State props Action
render dispatch _ state _ = [ render dispatch _ state _ = [
h1 [] [text "IMT DashBoard"] h1 [] [text "IMT DashBoard"]
, div [className "row"] [ div [className "col-md-9 content"] [chart globalPublis] , div [className "row"] [ div [className "col-md-9 content"] [chart globalPublis]
...@@ -59,9 +49,12 @@ render dispatch _ state _ = [ ...@@ -59,9 +49,12 @@ render dispatch _ state _ = [
----------------------------------------------------------------------------------------------------------- -----------------------------------------------------------------------------------------------------------
naturePublis_x :: Array String
naturePublis_x = ["Com","Articles","Thèses","Reports"] naturePublis_x = ["Com","Articles","Thèses","Reports"]
naturePublis_y' :: Array Int
naturePublis_y' = [23901,17417,1188,1176] naturePublis_y' = [23901,17417,1188,1176]
naturePublis_y :: Array {name :: String, value :: Number}
naturePublis_y = map (\(Tuple n v) -> {name: n, value: toNumber v }) (zip naturePublis_x naturePublis_y') naturePublis_y = map (\(Tuple n v) -> {name: n, value: toNumber v }) (zip naturePublis_x naturePublis_y')
naturePublis :: Options naturePublis :: Options
...@@ -77,7 +70,9 @@ naturePublis = Options { mainTitle : "Nature of publications" ...@@ -77,7 +70,9 @@ naturePublis = Options { mainTitle : "Nature of publications"
----------------------------------------------------------------------------------------------------------- -----------------------------------------------------------------------------------------------------------
globalPublis_x :: Array Int
globalPublis_x = [1982,1986,1987,1988,1990,1993,1996,1997,1998,1999,2000,2001,2002,2003,2004,2005,2006,2007,2008,2009,2010,2011,2012,2013,2014,2015,2016,2017] globalPublis_x = [1982,1986,1987,1988,1990,1993,1996,1997,1998,1999,2000,2001,2002,2003,2004,2005,2006,2007,2008,2009,2010,2011,2012,2013,2014,2015,2016,2017]
globalPublis_y :: Array Int
globalPublis_y = [1,4,2,1,1,2,1,1,8,38,234,76,40,82,75,202,1475,1092,1827,2630,4978,3668,4764,5915,4602,5269,6814,4018] globalPublis_y = [1,4,2,1,1,2,1,1,8,38,234,76,40,82,75,202,1475,1092,1827,2630,4978,3668,4764,5915,4602,5269,6814,4018]
...@@ -94,6 +89,7 @@ globalPublis = (Options { mainTitle : "Global Scientific Publications" ...@@ -94,6 +89,7 @@ globalPublis = (Options { mainTitle : "Global Scientific Publications"
distriBySchool_y :: Array (Tuple String Int)
distriBySchool_y = [Tuple "Télécom Bretagne" 1150,Tuple "Télécom SudParis" 946,Tuple "Mines Nantes" 547,Tuple "Télécom ParisTech" 429,Tuple "IMT Atlantique" 205,Tuple "Mines Alès" 56 distriBySchool_y = [Tuple "Télécom Bretagne" 1150,Tuple "Télécom SudParis" 946,Tuple "Mines Nantes" 547,Tuple "Télécom ParisTech" 429,Tuple "IMT Atlantique" 205,Tuple "Mines Alès" 56
,Tuple "Télécom Ecole de Management" 52,Tuple "Mines Albi-Carmaux" 6] ,Tuple "Télécom Ecole de Management" 52,Tuple "Mines Albi-Carmaux" 6]
...@@ -210,5 +206,5 @@ treeEx = Options { mainTitle : "Tree" ...@@ -210,5 +206,5 @@ treeEx = Options { mainTitle : "Tree"
} }
layoutDashboard :: forall props. Spec State props Action layoutDashboard :: Spec {} {} Void
layoutDashboard = simpleSpec performAction render layoutDashboard = simpleSpec defaultPerformAction render
...@@ -2,22 +2,26 @@ module Gargantext.Pages.Corpus.Doc.Facets.Documents where ...@@ -2,22 +2,26 @@ module Gargantext.Pages.Corpus.Doc.Facets.Documents where
import Prelude hiding (div) import Prelude hiding (div)
import Affjax (defaultRequest, printResponseFormatError, request)
import Affjax.ResponseFormat as ResponseFormat
import Control.Monad.Cont.Trans (lift) import Control.Monad.Cont.Trans (lift)
import Data.Argonaut (class DecodeJson, decodeJson, (.?)) import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, jsonEmptyObject, (.?), (:=), (~>))
import Data.Array (filter) import Data.Array (filter)
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.Generic.Rep (class Generic) import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Show (genericShow) import Data.Generic.Rep.Show (genericShow)
import Data.HTTP.Method (Method(..))
import Data.Tuple (Tuple(..)) import Data.Tuple (Tuple(..))
import Effect (Effect) import Effect (Effect)
import Effect.Aff (Aff) import Effect.Aff (Aff)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
import Effect.Console (log) import Effect.Console (log)
import Gargantext.Config.REST (get) import Gargantext.Config.REST (get)
import Gargantext.Utils.DecodeMaybe ((.|))
import React (ReactElement) import React (ReactElement)
import React.DOM (a, b, b', br', div, input, option, select, span, table, tbody, td, text, th, thead, tr, p) import React.DOM (a, b, b', br', div, input, option, select, span, table, tbody, td, text, th, thead, tr, p)
import React.DOM.Props (_type, className, href, onChange, onClick, scope, selected, value) import React.DOM.Props (_type, className, href, onChange, onClick, scope, selected, value)
import Thermite (PerformAction, Render, Spec, cotransform, defaultPerformAction, modifyState, simpleSpec) import Thermite (PerformAction, Render, Spec, modifyState, defaultPerformAction, simpleSpec)
import Unsafe.Coerce (unsafeCoerce) import Unsafe.Coerce (unsafeCoerce)
p'' :: ReactElement p'' :: ReactElement
...@@ -116,8 +120,8 @@ newtype Hyperdata = Hyperdata ...@@ -116,8 +120,8 @@ newtype Hyperdata = Hyperdata
instance decodeHyperdata :: DecodeJson Hyperdata where instance decodeHyperdata :: DecodeJson Hyperdata where
decodeJson json = do decodeJson json = do
obj <- decodeJson json obj <- decodeJson json
title <- obj .? "nom" title <- obj .| "title"
source <- obj .? "fonction" source <- obj .| "source"
pure $ Hyperdata { title,source } pure $ Hyperdata { title,source }
instance decodeResponse :: DecodeJson Response where instance decodeResponse :: DecodeJson Response where
...@@ -134,17 +138,17 @@ instance decodeResponse :: DecodeJson Response where ...@@ -134,17 +138,17 @@ instance decodeResponse :: DecodeJson Response where
-- | Filter -- | Filter
filterSpec :: forall props. Spec State props Action filterSpec :: Spec State {} Action
filterSpec = simpleSpec defaultPerformAction render filterSpec = simpleSpec defaultPerformAction render
where where
render d p s c = [div [] [ text " Filter " render d p s c = [div [] [ text " Filter "
, input [] , input []
]] ]]
layoutDocview :: forall props. Spec State props Action layoutDocview :: Spec State {} Action
layoutDocview = simpleSpec performAction render layoutDocview = simpleSpec performAction render
where where
render :: Render State props Action render :: Render State {} Action
render dispatch _ state@(TableData d) _ = render dispatch _ state@(TableData d) _ =
[ div [className "container1"] [ div [className "container1"]
[ div [className "row"] [ div [className "row"]
...@@ -178,16 +182,16 @@ layoutDocview = simpleSpec performAction render ...@@ -178,16 +182,16 @@ layoutDocview = simpleSpec performAction render
] ]
performAction :: forall props. PerformAction State props Action performAction :: PerformAction State {} Action
performAction (ChangePageSize ps) _ _ = void (cotransform (\state -> changePageSize ps state )) performAction (ChangePageSize ps) _ _ = void $ modifyState $ changePageSize ps
performAction (ChangePage p) _ _ = void (cotransform (\(TableData td) -> TableData $ td { currentPage = p} )) performAction (ChangePage p) _ _ = void $ modifyState \(TableData td) -> TableData $ td { currentPage = p }
performAction LoadData _ _ = void do performAction LoadData _ _ = do
res <- lift $ loadPage res <- lift $ loadPage
case res of case res of
Left err -> cotransform $ \state -> state Left err -> pure unit
Right resData -> modifyState (\s -> resData) Right resData -> void $ modifyState $ const resData
loadPage :: Aff (Either String CorpusTableData) loadPage :: Aff (Either String CorpusTableData)
...@@ -418,3 +422,37 @@ lessthan x y = x < y ...@@ -418,3 +422,37 @@ lessthan x y = x < y
greaterthan :: forall t28. Ord t28 => t28 -> t28 -> Boolean greaterthan :: forall t28. Ord t28 => t28 -> t28 -> Boolean
greaterthan x y = x > y greaterthan x y = x > y
newtype SearchQuery = SearchQuery
{
query :: Array String
, parent_id :: Int
}
instance encodeJsonSQuery :: EncodeJson SearchQuery where
encodeJson (SearchQuery post)
= "query" := post.query
~> "parent_id" := post.parent_id
~> jsonEmptyObject
searchResults :: SearchQuery -> Aff (Either String (Int))
searchResults squery = do
res <- request $ defaultRequest
{ url = "http://localhost:8008/count"
, responseFormat = ResponseFormat.json
, method = Left POST
, headers = []
}
case res.body of
Left err -> do
_ <- liftEffect $ log $ printResponseFormatError err
pure $ Left $ printResponseFormatError err
Right json -> do
--_ <- liftEffect $ log $ show a.status
--_ <- liftEffect $ log $ show a.headers
--_ <- liftEffect $ log $ show a.body
let obj = decodeJson json
pure obj
...@@ -28,8 +28,8 @@ import React.DOM.Props (_id, _type, checked, className, href, name, onChange, pl ...@@ -28,8 +28,8 @@ import React.DOM.Props (_id, _type, checked, className, href, name, onChange, pl
import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec) import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec)
import Unsafe.Coerce (unsafeCoerce) import Unsafe.Coerce (unsafeCoerce)
data Action = NoOp data Action
| LoadGraph String = LoadGraph String
| SelectNode SelectedNode | SelectNode SelectedNode
newtype SelectedNode = SelectedNode {id :: String, label :: String} newtype SelectedNode = SelectedNode {id :: String, label :: String}
...@@ -54,10 +54,10 @@ initialState = State ...@@ -54,10 +54,10 @@ initialState = State
, selectedNode : Nothing , selectedNode : Nothing
} }
graphSpec :: forall props. Spec State props Action graphSpec :: Spec State {} Action
graphSpec = simpleSpec performAction render graphSpec = simpleSpec performAction render
performAction :: forall props. PerformAction State props Action performAction :: PerformAction State {} Action
performAction (LoadGraph fp) _ _ = void do performAction (LoadGraph fp) _ _ = void do
_ <- liftEffect $ log fp _ <- liftEffect $ log fp
case fp of case fp of
...@@ -75,10 +75,6 @@ performAction (LoadGraph fp) _ _ = void do ...@@ -75,10 +75,6 @@ performAction (LoadGraph fp) _ _ = void do
performAction (SelectNode node) _ _ = void do performAction (SelectNode node) _ _ = void do
modifyState $ \(State s) -> State s {selectedNode = pure node} modifyState $ \(State s) -> State s {selectedNode = pure node}
performAction NoOp _ _ = void do
modifyState identity
convert :: GraphData -> SigmaGraphData convert :: GraphData -> SigmaGraphData
convert (GraphData r) = SigmaGraphData { nodes, edges} convert (GraphData r) = SigmaGraphData { nodes, edges}
where where
...@@ -97,7 +93,7 @@ convert (GraphData r) = SigmaGraphData { nodes, edges} ...@@ -97,7 +93,7 @@ convert (GraphData r) = SigmaGraphData { nodes, edges}
edges = map edgeFn r.edges edges = map edgeFn r.edges
edgeFn (Edge e) = sigmaEdge {id : e.id_, source : e.source, target : e.target} edgeFn (Edge e) = sigmaEdge {id : e.id_, source : e.source, target : e.target}
render :: forall props. Render State props Action render :: Render State {} Action
render d p (State s) c = render d p (State s) c =
[ select [ onChange $ \e -> d $ LoadGraph (unsafeCoerce e).target.value, value s.filePath] [ select [ onChange $ \e -> d $ LoadGraph (unsafeCoerce e).target.value, value s.filePath]
[ option [value ""] [text ""] [ option [value ""] [text ""]
...@@ -296,10 +292,10 @@ dispLegend ary = div [] $ map dl ary ...@@ -296,10 +292,10 @@ dispLegend ary = div [] $ map dl ary
] ]
specOld :: forall props. Spec State props Action specOld :: Spec State {} Action
specOld = simpleSpec performAction render' specOld = simpleSpec performAction render'
where where
render' :: Render State props Action render' :: Render State {} Action
render' d _ (State st) _ = render' d _ (State st) _ =
[ div [className "row"] [ [ div [className "row"] [
div [className "col-md-12", style {marginTop : "21px", marginBottom : "21px"}] div [className "col-md-12", style {marginTop : "21px", marginBottom : "21px"}]
......
...@@ -16,12 +16,12 @@ initialState = D.tdata ...@@ -16,12 +16,12 @@ initialState = D.tdata
type Action = D.Action type Action = D.Action
sourceSpec :: forall props. Spec State props Action sourceSpec :: Spec State {} Action
sourceSpec = simpleSpec defaultPerformAction render sourceSpec = simpleSpec defaultPerformAction render
where where
render :: Render State props Action render :: Render State {} Action
render dispatch _ state _ = render dispatch _ state _ =
[ h3 [] [text "Source view"]] [ h3 [] [text "Source view"]]
sourcespec' :: forall props. Spec State props Action sourcespec' :: Spec State {} Action
sourcespec' = fold [sourceSpec, D.layoutDocview] sourcespec' = fold [sourceSpec, D.layoutDocview]
...@@ -2,12 +2,11 @@ module Gargantext.Pages.Corpus.Doc.Facets.Specs where ...@@ -2,12 +2,11 @@ module Gargantext.Pages.Corpus.Doc.Facets.Specs where
import Prelude hiding (div) import Prelude hiding (div)
import Data.Lens (Lens', Prism', lens, prism)
import Data.List (fromFoldable) import Data.List (fromFoldable)
import Data.Tuple (Tuple(..)) import Data.Tuple (Tuple(..))
import Gargantext.Pages.Corpus.Doc.Facets.States (State(..), _doclens, _sourcelens, _authorlens, _termslens, _tablens) import Gargantext.Pages.Corpus.Doc.Facets.States (State(), _doclens, _sourcelens, _authorlens, _termslens, _tablens, initialState)
import Gargantext.Pages.Corpus.Doc.Facets.Actions (Action(..), _docAction, _sourceAction, _authorAction, _termsAction, _tabAction) import Gargantext.Pages.Corpus.Doc.Facets.Actions (Action(), _docAction, _sourceAction, _authorAction, _termsAction, _tabAction)
import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV
import Gargantext.Pages.Corpus.Doc.Facets.Sources as SV import Gargantext.Pages.Corpus.Doc.Facets.Sources as SV
...@@ -15,25 +14,28 @@ import Gargantext.Pages.Corpus.Doc.Facets.Authors as AV ...@@ -15,25 +14,28 @@ import Gargantext.Pages.Corpus.Doc.Facets.Authors as AV
import Gargantext.Pages.Corpus.Doc.Facets.Terms as TV import Gargantext.Pages.Corpus.Doc.Facets.Terms as TV
import Gargantext.Components.Tab as Tab import Gargantext.Components.Tab as Tab
import Thermite (Spec, focus) import Thermite (Spec, focus, hide)
pureTab1 :: Spec {} {} Void
pureTab1 = hide initialState statefulTab1
tab1 :: forall props. Spec State props Action statefulTab1 :: Spec State {} Action
tab1 = Tab.tabs _tablens _tabAction $ fromFoldable [ Tuple "Doc View" docPageSpec statefulTab1 =
, Tuple "Author View" authorPageSpec Tab.tabs _tablens _tabAction $ fromFoldable [ Tuple "Doc View" docPageSpec
, Tuple "Source View" sourcePageSpec , Tuple "Author View" authorPageSpec
, Tuple "Terms View" termsPageSpec , Tuple "Source View" sourcePageSpec
] , Tuple "Terms View" termsPageSpec
]
docPageSpec :: forall props. Spec State props Action docPageSpec :: Spec State {} Action
docPageSpec = focus _doclens _docAction DV.layoutDocview docPageSpec = focus _doclens _docAction DV.layoutDocview
authorPageSpec :: forall props. Spec State props Action authorPageSpec :: Spec State {} Action
authorPageSpec = focus _authorlens _authorAction AV.authorspec' authorPageSpec = focus _authorlens _authorAction AV.authorspec'
sourcePageSpec :: forall props. Spec State props Action sourcePageSpec :: Spec State {} Action
sourcePageSpec = focus _sourcelens _sourceAction SV.sourcespec' sourcePageSpec = focus _sourcelens _sourceAction SV.sourcespec'
termsPageSpec :: forall props. Spec State props Action termsPageSpec :: Spec State {} Action
termsPageSpec = focus _termslens _termsAction TV.termSpec' termsPageSpec = focus _termslens _termsAction TV.termSpec'
...@@ -4,7 +4,7 @@ import Data.Array (fold) ...@@ -4,7 +4,7 @@ import Data.Array (fold)
import Gargantext.Pages.Corpus.Doc.Facets.Documents as D import Gargantext.Pages.Corpus.Doc.Facets.Documents as D
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 (PerformAction, Render, Spec, defaultPerformAction, simpleSpec)
...@@ -17,12 +17,12 @@ initialState = D.tdata ...@@ -17,12 +17,12 @@ initialState = D.tdata
type Action = D.Action type Action = D.Action
termsSpec :: forall props. Spec State props Action termsSpec :: Spec State {} Action
termsSpec = simpleSpec defaultPerformAction render termsSpec = simpleSpec defaultPerformAction render
where where
render :: Render State props Action render :: Render State {} Action
render dispatch _ state _ = render dispatch _ state _ =
[ h3 [] [text "Terms view"]] [ h3 [] [text "Terms view"]]
termSpec' :: forall props. Spec State props Action termSpec' :: Spec State {} Action
termSpec' = fold [termsSpec, D.layoutDocview] termSpec' = fold [termsSpec, D.layoutDocview]
...@@ -2,17 +2,21 @@ module Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsItem where ...@@ -2,17 +2,21 @@ module Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsItem where
import Prelude import Prelude
import Data.Newtype (class Newtype) import Data.Newtype (class Newtype, unwrap)
import Data.Lens.Iso (re)
import Data.Lens.Iso.Newtype (_Newtype)
import React (ReactElement) import React (ReactElement)
import React.DOM (input, span, td, text, tr) import React.DOM (input, span, td, text, tr)
import React.DOM.Props (_type, checked, className, onChange, style, title) import React.DOM.Props (_type, checked, className, onChange, style, title)
import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec) import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec, hide, focusState)
import Gargantext.Utils (getter, setter) import Gargantext.Utils (getter, setter)
newtype State = State newtype State = State
{ term :: Term { term :: Term
} }
derive instance newtypeState :: Newtype State _
initialState :: State initialState :: State
initialState = State {term : Term {id : 10, term : "hello", occurrence : 10, _type : None, children : []}} initialState = State {term : Term {id : 10, term : "hello", occurrence : 10, _type : None, children : []}}
...@@ -33,17 +37,19 @@ data Action ...@@ -33,17 +37,19 @@ data Action
= SetMap Boolean = SetMap Boolean
| SetStop Boolean | SetStop Boolean
performAction :: forall props. PerformAction State props Action performAction :: PerformAction State {} Action
performAction (SetMap b) _ _ = void do performAction (SetMap b) _ _ = void do
modifyState \(State s) -> State s {term = setter (_{_type = (if b then MapTerm else None)}) s.term} modifyState \(State s) -> State s {term = setter (_{_type = (if b then MapTerm else None)}) s.term}
performAction (SetStop b) _ _ = void do performAction (SetStop b) _ _ = void do
modifyState \(State s) -> State s {term = setter (_{_type = (if b then StopTerm else None)}) s.term} modifyState \(State s) -> State s {term = setter (_{_type = (if b then StopTerm else None)}) s.term}
ngramsItemSpec :: forall props. Spec State props Action ngramsItemSpec :: Spec {} {} Void
ngramsItemSpec = simpleSpec performAction render ngramsItemSpec = hide (unwrap initialState) $
focusState (re _Newtype) $
simpleSpec performAction render
where where
render :: Render State props Action render :: Render State {} Action
render dispatch _ (State state) _ = render dispatch _ (State state) _ =
[ [
tr [] tr []
......
module Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsTable where module Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsTable where
import Data.Array (filter, fold, toUnfoldable) import Data.Array (filter, toUnfoldable)
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.Newtype (class Newtype, unwrap)
import Data.Lens (Lens', Prism', lens, over, prism) import Data.Lens (Lens', Prism', lens, over, prism)
import Data.Lens.Iso (re)
import Data.Lens.Iso.Newtype (_Newtype)
import Data.List (List) import Data.List (List)
import Data.Tuple (Tuple(..), uncurry) import Data.Tuple (Tuple(..), uncurry)
import Data.Void (Void)
import Data.Unit (Unit)
import Effect (Effect)
import Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsItem as NI import Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsItem as NI
import Prelude (class Eq, class Ord, class Show, map, show, void, ($), (*), (+), (-), (/), (<), (<>), (==), (>), (>=)) import Prelude (class Eq, class Ord, class Show, map, show, void, ($), (*), (+), (-), (/), (<), (<>), (==), (>), (>=), pure, unit)
import React (ReactElement) import React (ReactElement)
import React.DOM hiding (style, map) import React.DOM hiding (style, map)
import React.DOM.Props (_id, _type, className, href, name, onChange, onClick, onInput, placeholder, scope, selected, style, value) import React.DOM.Props (_id, _type, className, href, name, onChange, onClick, onInput, placeholder, scope, selected, style, value)
import Thermite (PerformAction, Spec, _render, cotransform, focus, foreach, modifyState, withState) import Thermite (PerformAction, Spec, _render, focus, foreach, modifyState, focusState, hide)
import Unsafe.Coerce (unsafeCoerce) import Unsafe.Coerce (unsafeCoerce)
newtype State = State newtype State = State
{ items :: List NI.State { items :: List {}
, search :: String , search :: String
, selectString :: String , selectString :: String
, totalPages :: Int , totalPages :: Int
, currentPage :: Int , currentPage :: Int
...@@ -24,36 +30,39 @@ newtype State = State ...@@ -24,36 +30,39 @@ newtype State = State
, totalRecords :: Int , totalRecords :: Int
} }
derive instance newtypeState :: Newtype State _
initialState :: State initialState :: State
initialState = State { items : toUnfoldable [NI.initialState] initialState = State { items : toUnfoldable [{}]
, search : "" , search : ""
, selectString : "" , selectString : ""
,totalPages : 10 , totalPages : 10
, currentPage : 1 , currentPage : 1
, pageSize : PS10 , pageSize : PS10
, totalRecords : 100 , totalRecords : 100
} }
data Action data Action
= NoOp = ItemAction Int Void
| ItemAction Int NI.Action
| ChangeString String | ChangeString String
| SetInput String | SetInput String
| ChangePageSize PageSizes | ChangePageSize PageSizes
| ChangePage Int | ChangePage Int
_itemsList :: Lens' State (List NI.State) _itemsList :: Lens' State (List {})
_itemsList = lens (\(State s) -> s.items) (\(State s) v -> State s { items = v }) _itemsList = lens (\(State s) -> s.items) (\(State s) v -> State s { items = v })
_ItemAction :: Prism' Action (Tuple Int NI.Action) _ItemAction :: Prism' Action (Tuple Int Void)
_ItemAction = prism (uncurry ItemAction) \ta -> _ItemAction = prism (uncurry ItemAction) \ta ->
case ta of case ta of
ItemAction i a -> Right (Tuple i a) ItemAction i a -> Right (Tuple i a)
_ -> Left ta _ -> Left ta
performAction :: forall props. PerformAction State props Action type Dispatch = Action -> Effect Unit
performAction :: PerformAction State {} Action
performAction (ChangePageSize ps) _ _ = void (cotransform (\state -> changePageSize ps state )) performAction (ChangePageSize ps) _ _ = void $ modifyState $ changePageSize ps
performAction (ChangePage p) _ _ = void do performAction (ChangePage p) _ _ = void do
modifyState \(State state) -> State $ state {currentPage = p} modifyState \(State state) -> State $ state {currentPage = p}
...@@ -67,10 +76,9 @@ performAction (ChangeString c) _ _ = void do ...@@ -67,10 +76,9 @@ performAction (ChangeString c) _ _ = void do
performAction (SetInput s) _ _ = void do performAction (SetInput s) _ _ = void do
modifyState \(State state) -> State $ state { search = s } modifyState \(State state) -> State $ state { search = s }
performAction _ _ _ = void do performAction _ _ _ = pure unit
modifyState \(State state) -> State $ state
tableSpec :: forall props .Spec State props Action -> Spec State props Action tableSpec :: Spec State {} Action -> Spec State {} Action
tableSpec = over _render \render dispatch p (State s) c -> tableSpec = over _render \render dispatch p (State s) c ->
[div [className "container-fluid"] [div [className "container-fluid"]
[ [
...@@ -147,12 +155,15 @@ tableSpec = over _render \render dispatch p (State s) c -> ...@@ -147,12 +155,15 @@ tableSpec = over _render \render dispatch p (State s) c ->
] ]
] ]
ngramsTableSpec :: forall props . Spec State props Action ngramsTableSpec :: Spec {} {} Void
ngramsTableSpec = container $ fold ngramsTableSpec =
[ tableSpec $ withState \st -> hide (unwrap initialState) $
focus _itemsList _ItemAction $ focusState (re _Newtype) $
foreach \_ -> NI.ngramsItemSpec container $
] tableSpec $
focus _itemsList _ItemAction $
foreach $ \ _ ->
NI.ngramsItemSpec
container :: forall state props action. Spec state props action -> Spec state props action container :: forall state props action. Spec state props action -> Spec state props action
container = over _render \render d p s c -> container = over _render \render d p s c ->
...@@ -212,7 +223,7 @@ string2PageSize "50" = PS50 ...@@ -212,7 +223,7 @@ string2PageSize "50" = PS50
string2PageSize "100" = PS100 string2PageSize "100" = PS100
string2PageSize _ = PS10 string2PageSize _ = PS10
sizeDD :: PageSizes -> _ -> ReactElement sizeDD :: PageSizes -> Dispatch -> ReactElement
sizeDD ps d sizeDD ps d
= p [] = p []
[ text "Show : " [ text "Show : "
...@@ -235,7 +246,7 @@ textDescription currPage pageSize totalRecords ...@@ -235,7 +246,7 @@ textDescription currPage pageSize totalRecords
end = if end' > totalRecords then totalRecords else end' end = if end' > totalRecords then totalRecords else end'
pagination :: _ -> Int -> Int -> ReactElement pagination :: Dispatch -> Int -> Int -> ReactElement
pagination d tp cp pagination d tp cp
= span [] $ = span [] $
[ text "Pages: " [ text "Pages: "
...@@ -306,7 +317,7 @@ pagination d tp cp ...@@ -306,7 +317,7 @@ pagination d tp cp
lnums = map (\i -> fnmid d i) $ filter (lessthan 1) [cp - 2, cp - 1] lnums = map (\i -> fnmid d i) $ filter (lessthan 1) [cp - 2, cp - 1]
rnums = map (\i -> fnmid d i) $ filter (greaterthan tp) [cp + 1, cp + 2] rnums = map (\i -> fnmid d i) $ filter (greaterthan tp) [cp + 1, cp + 2]
fnmid :: _ -> Int -> ReactElement fnmid :: Dispatch -> Int -> ReactElement
fnmid d i fnmid d i
= span [] = span []
[ text " " [ text " "
......
module Gargantext.Pages.Corpus.User.Brevets where module Gargantext.Pages.Corpus.User.Brevets where
import Prelude import Prelude
import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec) import Thermite (Render, Spec, defaultPerformAction, simpleSpec)
brevetsSpec :: Spec {} {} Void
type State = String brevetsSpec = simpleSpec defaultPerformAction render
initialState :: State
initialState = ""
data Action = NoOp
performAction :: forall props. PerformAction State props Action
performAction NoOp _ _ = void do
modifyState identity
brevetsSpec :: forall props. Spec State props Action
brevetsSpec = simpleSpec performAction render
where where
render :: Render State props Action render :: Render {} {} Void
render dispatch _ state _ = render dispatch _ state _ =
[] []
...@@ -4,7 +4,7 @@ import Prelude ...@@ -4,7 +4,7 @@ import Prelude
import Control.Monad.Trans.Class (lift) import Control.Monad.Trans.Class (lift)
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.Lens (set) import Data.Lens ((?~))
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Effect.Aff (Aff) import Effect.Aff (Aff)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
...@@ -17,16 +17,12 @@ getUser :: Int -> Aff (Either String User) ...@@ -17,16 +17,12 @@ getUser :: Int -> Aff (Either String User)
getUser id = get $ "http://localhost:8008/node/" <> show id getUser id = get $ "http://localhost:8008/node/" <> show id
performAction :: forall props. PerformAction State props Action performAction :: PerformAction State {} Action
performAction NoOp _ _ = void do performAction (FetchUser userId) _ _ = do
modifyState identity
performAction (FetchUser userId) _ _ = void do
value <- lift $ getUser userId value <- lift $ getUser userId
_ <- case value of _ <- case value of
(Right user) -> modifyState \state -> set _user (Just user) state (Right user) -> void $ modifyState $ _user ?~ user
(Left err) -> do (Left err) -> do
_ <- liftEffect $ log err liftEffect $ log err
modifyState identity
liftEffect <<< log $ "Fetching user..." liftEffect <<< log $ "Fetching user..."
performAction _ _ _ = void do performAction _ _ _ = pure unit
modifyState identity
...@@ -9,5 +9,5 @@ import Thermite (Spec, simpleSpec) ...@@ -9,5 +9,5 @@ import Thermite (Spec, simpleSpec)
import Gargantext.Pages.Corpus.User.Users.Types (Action, State) import Gargantext.Pages.Corpus.User.Users.Types (Action, State)
import Gargantext.Pages.Corpus.User.Users.API (performAction) import Gargantext.Pages.Corpus.User.Users.API (performAction)
layoutUser :: forall props. Spec State props Action layoutUser :: Spec State {} Action
layoutUser = simpleSpec performAction render layoutUser = simpleSpec performAction render
...@@ -3,24 +3,12 @@ module Gargantext.Pages.Corpus.User.Users.Specs.Documents where ...@@ -3,24 +3,12 @@ module Gargantext.Pages.Corpus.User.Users.Specs.Documents where
import Prelude import Prelude
import React.DOM (table, tbody, td, text, th, thead, tr) import React.DOM (table, tbody, td, text, th, thead, tr)
import React.DOM.Props (className, scope) import React.DOM.Props (className, scope)
import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec) import Thermite (Render, Spec, defaultPerformAction, simpleSpec)
publicationSpec :: Spec {} {} Void
type State = String publicationSpec = simpleSpec defaultPerformAction render
initialState :: State
initialState = ""
data Action = NoOp
performAction :: forall props. PerformAction State props Action
performAction NoOp _ _ = void do
modifyState identity
publicationSpec :: forall props. Spec State props Action
publicationSpec = simpleSpec performAction render
where where
render :: Render State props Action render :: Render {} {} Void
render dispatch _ state _ = render dispatch _ state _ =
[ table [ className "table"] [ table [ className "table"]
[ thead [ className "thead-dark"] [ thead [ className "thead-dark"]
......
...@@ -12,7 +12,7 @@ import React.DOM.Props (_id, className, src) ...@@ -12,7 +12,7 @@ import React.DOM.Props (_id, className, src)
import Thermite (Render) import Thermite (Render)
render :: forall props. Render State props Action render :: Render State {} Action
render dispatch _ state _ = render dispatch _ state _ =
[ [
div [className "col-md-12"] div [className "col-md-12"]
......
...@@ -18,18 +18,17 @@ import Data.List (fromFoldable) ...@@ -18,18 +18,17 @@ import Data.List (fromFoldable)
import Data.Tuple (Tuple(..)) import Data.Tuple (Tuple(..))
import Gargantext.Pages.Folder 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, noState)
brevetSpec :: forall props. Spec State props Action brevetSpec :: Spec State {} Action
brevetSpec = focus _brevetslens _brevetsAction B.brevetsSpec brevetSpec = noState B.brevetsSpec
projectSpec :: forall props. Spec State props Action projectSpec :: Spec State {} Action
projectSpec = focus _projectslens _projectsAction PS.projets projectSpec = noState PS.projets
facets :: Spec State {} Action
facets :: forall props. Spec State props Action
facets = tabs _tablens _tabAction $ fromFoldable facets = tabs _tablens _tabAction $ fromFoldable
[ Tuple "Publications (12)" publicationSpec [ Tuple "Publications (12)" publicationSpec
, Tuple "Brevets (2)" brevetSpec , Tuple "Brevets (2)" brevetSpec
, Tuple "Projets IMT (5)" projectSpec , Tuple "Projets IMT (5)" projectSpec
] ]
...@@ -6,10 +6,9 @@ import Data.Lens (Lens', Prism', lens, prism) ...@@ -6,10 +6,9 @@ import Data.Lens (Lens', Prism', lens, prism)
import Data.Maybe (Maybe) import Data.Maybe (Maybe)
import Gargantext.Pages.Corpus.User.Users.Types.States (Action(..), State) import Gargantext.Pages.Corpus.User.Users.Types.States (Action(..), State)
import Gargantext.Pages.Corpus.User.Users.Types.Types (User) import Gargantext.Pages.Corpus.User.Users.Types.Types (User)
import Gargantext.Pages.Folder as PS
import Gargantext.Pages.Corpus.User.Users.Specs.Documents as P import Gargantext.Pages.Corpus.User.Users.Specs.Documents as P
import Gargantext.Components.Tab as Tab import Gargantext.Components.Tab as Tab
import Thermite (Spec, focus) import Thermite (Spec, noState)
_user :: Lens' State (Maybe User) _user :: Lens' State (Maybe User)
_user = lens (\s -> s.user) (\s ss -> s{user = ss}) _user = lens (\s -> s.user) (\s ss -> s{user = ss})
...@@ -23,32 +22,5 @@ _tabAction = prism TabA \ action -> ...@@ -23,32 +22,5 @@ _tabAction = prism TabA \ action ->
TabA laction -> Right laction TabA laction -> Right laction
_-> Left action _-> Left action
_publens :: Lens' State P.State publicationSpec :: Spec State {} Action
_publens = lens (\s -> s.publications) (\s ss -> s { publications= ss}) publicationSpec = noState P.publicationSpec
_pubAction :: Prism' Action P.Action
_pubAction = prism PublicationA \ action ->
case action of
PublicationA laction -> Right laction
_-> Left action
publicationSpec :: forall props. Spec State props Action
publicationSpec = focus _publens _pubAction P.publicationSpec
_brevetslens :: Lens' State B.State
_brevetslens = lens (\s -> s.brevets) (\s ss -> s {brevets = ss})
_brevetsAction :: Prism' Action B.Action
_brevetsAction = prism BrevetsA \ action ->
case action of
BrevetsA laction -> Right laction
_-> Left action
_projectslens :: Lens' State PS.State
_projectslens = lens (\s -> s.projects) (\s ss -> s {projects = ss})
_projectsAction :: Prism' Action PS.Action
_projectsAction = prism ProjectsA \ action ->
case action of
ProjectsA laction -> Right laction
_-> Left action
module Gargantext.Pages.Corpus.User.Users.Types.States where module Gargantext.Pages.Corpus.User.Users.Types.States where
import Gargantext.Pages.Corpus.User.Brevets as B
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Gargantext.Pages.Corpus.User.Users.Types.Types (User) import Gargantext.Pages.Corpus.User.Users.Types.Types (User)
import Gargantext.Pages.Folder as PS
import Gargantext.Pages.Corpus.User.Users.Specs.Documents as P import Gargantext.Pages.Corpus.User.Users.Specs.Documents as P
import Gargantext.Components.Tab as Tab import Gargantext.Components.Tab as Tab
data Action data Action
= NoOp = TabA Tab.Action
| PublicationA P.Action
| BrevetsA B.Action
| ProjectsA PS.Action
| TabA Tab.Action
| FetchUser Int | FetchUser Int
type State = type State =
{ activeTab :: Int { activeTab :: Int
, publications :: P.State
, brevets :: B.State
, projects :: PS.State
, user :: Maybe User , user :: Maybe User
} }
initialState :: State initialState :: State
initialState = initialState =
{ activeTab : 0 { activeTab : 0
, publications : P.initialState
, brevets : B.initialState
, projects : PS.initialState
, user: Nothing , user: Nothing
} }
...@@ -2,23 +2,12 @@ module Gargantext.Pages.Folder where ...@@ -2,23 +2,12 @@ module Gargantext.Pages.Folder where
import Prelude import Prelude
import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec) import Thermite (Render, Spec, defaultPerformAction, simpleSpec)
type State = String projets :: Spec {} {} Void
projets = simpleSpec defaultPerformAction render
initialState :: State
initialState = ""
data Action = NoOp
performAction :: forall props. PerformAction State props Action
performAction NoOp _ _ = void do
modifyState identity
projets :: forall props. Spec State props Action
projets = simpleSpec performAction render
where where
render :: Render State props Action render :: Render {} {} Void
render dispatch _ state _ = render dispatch _ state _ =
[] []
...@@ -5,30 +5,22 @@ import Prelude hiding (div) ...@@ -5,30 +5,22 @@ import Prelude hiding (div)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
import Gargantext.Pages.Home.States (State) import Gargantext.Pages.Home.States (State)
import Routing.Hash (setHash) import Routing.Hash (setHash)
import Thermite (PerformAction, modifyState) import Thermite (PerformAction)
data Action data Action
= NoOp = Documentation
| Documentation
| Enter | Enter
| Login | Login
| SignUp | SignUp
performAction :: forall props. PerformAction State props Action performAction :: PerformAction State {} Action
performAction NoOp _ _ = void do performAction Documentation _ _ = pure unit
modifyState \state -> state
performAction Documentation _ _ = void do
modifyState \state -> state
performAction Enter _ _ = void do performAction Enter _ _ = void do
liftEffect $ setHash "/search" liftEffect $ setHash "/search"
modifyState \state -> state
performAction Login _ _ = void do performAction Login _ _ = void do
liftEffect $ setHash "/login" liftEffect $ setHash "/login"
modifyState \state -> state
performAction SignUp _ _ = void do performAction SignUp _ _ = pure unit
modifyState \state -> state
...@@ -2,31 +2,40 @@ module Gargantext.Pages.Home.Specs where ...@@ -2,31 +2,40 @@ module Gargantext.Pages.Home.Specs where
import Prelude hiding (div) import Prelude hiding (div)
import Data.Lens (re)
import Data.Lens.Iso.Newtype (_Newtype)
import Data.Newtype (unwrap)
import Gargantext.Components.Lang.Landing.EnUS as En import Gargantext.Components.Lang.Landing.EnUS as En
import Gargantext.Components.Lang.Landing.FrFR as Fr import Gargantext.Components.Lang.Landing.FrFR as Fr
import Gargantext.Components.Data.Landing (BlockText(..), BlockTexts(..), Button(..), LandingData(..)) import Gargantext.Components.Data.Landing (BlockText(..), BlockTexts(..), Button(..), LandingData(..))
import Gargantext.Components.Data.Lang (Lang(..)) import Gargantext.Components.Data.Lang (Lang(..))
import Gargantext.Pages.Home.States (State) import Gargantext.Pages.Home.States (State, initialState)
import Gargantext.Pages.Home.Actions (Action, performAction) import Gargantext.Pages.Home.Actions (Action, performAction)
import React (ReactElement) import React (ReactElement)
import React.DOM (a, div, h3, i, img, p, span, text) import React.DOM (a, div, h3, i, img, p, span, text)
import React.DOM.Props (Props, _id, aria, className, href, src, target, title) import React.DOM.Props (Props, _id, aria, className, href, src, target, title)
import Thermite (Render, Spec, simpleSpec) import Thermite (Render, Spec, simpleSpec, hide, focusState)
-- Layout | -- Layout |
layoutLanding :: forall props. Lang -> Spec State props Action landingData :: Lang -> LandingData
layoutLanding FR = layoutLanding' Fr.landingData landingData FR = Fr.landingData
layoutLanding EN = layoutLanding' En.landingData landingData EN = En.landingData
layoutLanding :: Lang -> Spec {} {} Void
layoutLanding = hide (unwrap initialState)
<<< focusState (re _Newtype)
<<< layoutLanding' <<< landingData
------------------------------------------------------------------------ ------------------------------------------------------------------------
layoutLanding' :: forall props. LandingData -> Spec State props Action layoutLanding' :: LandingData -> Spec State {} Action
layoutLanding' hd = simpleSpec performAction render layoutLanding' hd = simpleSpec performAction render
where where
render :: Render State props Action render :: Render State {} Action
render dispatch _ state _ = render dispatch _ state _ =
[ div [ className "container1" ] [ jumboTitle hd false ] [ div [ className "container1" ] [ jumboTitle hd false ]
, div [ className "container1" ] [] -- put research here , div [ className "container1" ] [] -- put research here
...@@ -69,7 +78,7 @@ jumboTitle :: LandingData -> Boolean -> ReactElement ...@@ -69,7 +78,7 @@ jumboTitle :: LandingData -> Boolean -> ReactElement
jumboTitle (LandingData hd) b = div jumbo jumboTitle (LandingData hd) b = div jumbo
[ div [className "row" ] [ div [className "row" ]
[ div [ className "col-md-8 content"] [ div [ className "col-md-8 content"]
[ p [ className "left" ] [ div [ className "left" ]
[ div [_id "logo-designed" ] [ div [_id "logo-designed" ]
[ img [ src "images/logo.png" [ img [ src "images/logo.png"
, title hd.logoTitle , title hd.logoTitle
......
module Gargantext.Pages.Home.States where module Gargantext.Pages.Home.States where
import Prelude hiding (div) import Data.Newtype (class Newtype)
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 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 Thermite (PerformAction, Render, Spec, modifyState, simpleSpec)
newtype State = State newtype State = State
{ userName :: String { userName :: String
, password :: String , password :: String
} }
derive instance newtypeState :: Newtype State _
initialState :: State initialState :: State
initialState = State initialState = State
{userName : "" { userName : ""
, password : "" , password : ""
} }
module Gargantext.Pages.Layout where module Gargantext.Pages.Layout where
import Prelude hiding (div) import Prelude hiding (div)
import Gargantext.Components.Login as LN -- import Gargantext.Components.Login as LN
import Gargantext.Pages.Layout.Actions (Action(..)) import Gargantext.Pages.Layout.Actions (Action(..))
import Gargantext.Pages.Layout.Specs.AddCorpus as AC import Gargantext.Pages.Layout.Specs.AddCorpus as AC
import Gargantext.Pages.Corpus.Doc.Facets as TV -- import Gargantext.Pages.Corpus.Doc.Facets as TV
import Gargantext.Pages.Corpus.Doc.Annotation as D -- import Gargantext.Pages.Corpus.Doc.Annotation as D
import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV
import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE
import Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsTable as NG -- import Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsTable as NG
import Gargantext.Pages.Corpus.User.Users as U import Gargantext.Pages.Corpus.User.Users as U
import Gargantext.Pages.Home as L -- import Gargantext.Pages.Home as L
import Gargantext.Pages.Layout.Specs.Search as S -- import Gargantext.Pages.Layout.Specs.Search as S
import Gargantext.Router (Routes(..)) import Gargantext.Router (Routes(..))
dispatchAction :: forall t115 t445 t447. dispatchAction :: forall ignored m.
Bind t445 => Applicative t445 => Monad m =>
(Action -> t445 t447) -> t115 -> Routes -> t445 Unit (Action -> m Unit) -> ignored -> Routes -> m Unit
dispatchAction dispatcher _ Home = do dispatchAction dispatcher _ Home = do
_ <- dispatcher Initialize dispatcher Initialize
_ <- dispatcher $ SetRoute Home dispatcher $ SetRoute Home
_ <- dispatcher $ LandingA L.NoOp -- dispatcher $ LandingA TODO
pure unit
dispatchAction dispatcher _ Login = do dispatchAction dispatcher _ Login = do
_ <- dispatcher Initialize dispatcher Initialize
_ <- dispatcher $ SetRoute Login dispatcher $ SetRoute Login
_ <- dispatcher $ LoginA LN.NoOp -- dispatcher $ LoginA TODO
pure unit
dispatchAction dispatcher _ AddCorpus = do dispatchAction dispatcher _ AddCorpus = do
_ <- dispatcher $ SetRoute AddCorpus dispatcher $ SetRoute AddCorpus
_ <- dispatcher $ AddCorpusA AC.LoadDatabaseDetails dispatcher $ AddCorpusA AC.LoadDatabaseDetails
pure unit
dispatchAction dispatcher _ DocView = do dispatchAction dispatcher _ DocView = do
_ <- dispatcher $ SetRoute $ DocView dispatcher $ SetRoute DocView
_ <- dispatcher $ DocViewA $ DV.LoadData dispatcher $ DocViewA $ DV.LoadData
pure unit
dispatchAction dispatcher _ SearchView = do dispatchAction dispatcher _ SearchView = do
_ <- dispatcher $ SetRoute $ SearchView dispatcher $ SetRoute SearchView
_ <- dispatcher $ SearchA $ S.NoOp -- dispatcher $ SearchA TODO
pure unit
dispatchAction dispatcher _ (UserPage id) = do dispatchAction dispatcher _ (UserPage id) = do
_ <- dispatcher $ SetRoute $ UserPage id dispatcher $ SetRoute $ UserPage id
_ <- dispatcher $ UserPageA $ U.NoOp -- dispatcher $ UserPageA TODO
_ <- dispatcher $ UserPageA $ U.FetchUser id dispatcher $ UserPageA $ U.FetchUser id
pure unit
dispatchAction dispatcher _ (DocAnnotation i) = do dispatchAction dispatcher _ (DocAnnotation i) = do
_ <- dispatcher $ SetRoute $ DocAnnotation i dispatcher $ SetRoute $ DocAnnotation i
_ <- dispatcher $ DocAnnotationViewA $ D.NoOp -- dispatcher $ DocAnnotationViewA TODO
pure unit
dispatchAction dispatcher _ Tabview = do dispatchAction dispatcher _ Tabview = do
_ <- dispatcher $ SetRoute $ Tabview dispatcher $ SetRoute Tabview
_ <- dispatcher $ TabViewA $ TV.NoOp -- dispatcher $ TabViewA TODO
pure unit
dispatchAction dispatcher _ CorpusAnalysis = do dispatchAction dispatcher _ CorpusAnalysis = do
_ <- dispatcher $ SetRoute $ CorpusAnalysis dispatcher $ SetRoute CorpusAnalysis
--_ <- dispatcher $ CorpusAnalysisA $ CA.NoOp -- dispatcher $ CorpusAnalysisA TODO
pure unit
dispatchAction dispatcher _ PGraphExplorer = do dispatchAction dispatcher _ PGraphExplorer = do
_ <- dispatcher $ SetRoute $ PGraphExplorer dispatcher $ SetRoute PGraphExplorer
_ <- dispatcher $ GraphExplorerA $ GE.LoadGraph "imtNew.json" dispatcher $ GraphExplorerA $ GE.LoadGraph "imtNew.json"
pure unit
dispatchAction dispatcher _ NGramsTable = do dispatchAction dispatcher _ NGramsTable = do
_ <- dispatcher $ SetRoute $ NGramsTable dispatcher $ SetRoute NGramsTable
_ <- dispatcher $ NgramsA $ NG.NoOp -- dispatcher $ NgramsA TODO
pure unit
dispatchAction dispatcher _ Dashboard = do dispatchAction dispatcher _ Dashboard = do
_ <- dispatcher $ SetRoute $ Dashboard dispatcher $ SetRoute Dashboard
pure unit
...@@ -3,7 +3,6 @@ module Gargantext.Pages.Layout.Actions where ...@@ -3,7 +3,6 @@ module Gargantext.Pages.Layout.Actions where
import Prelude hiding (div) import Prelude hiding (div)
import Control.Monad.Cont.Trans (lift) import Control.Monad.Cont.Trans (lift)
import Data.Array (length)
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.Lens (Prism', prism) import Data.Lens (Prism', prism)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
...@@ -11,15 +10,10 @@ import Effect.Console (log) ...@@ -11,15 +10,10 @@ import Effect.Console (log)
import Gargantext.Components.Login as LN import Gargantext.Components.Login as LN
import Gargantext.Components.Modals.Modal (modalShow) import Gargantext.Components.Modals.Modal (modalShow)
import Gargantext.Components.Tree as Tree import Gargantext.Components.Tree as Tree
import Gargantext.Pages.Corpus as CA
import Gargantext.Pages.Corpus.Doc.Annotation as D import Gargantext.Pages.Corpus.Doc.Annotation as D
import Gargantext.Pages.Corpus.Doc.Facets as TV
import Gargantext.Pages.Corpus.Doc.Facets.Dashboard as Dsh
import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV
import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE
import Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsTable as NG
import Gargantext.Pages.Corpus.User.Users as U import Gargantext.Pages.Corpus.User.Users as U
import Gargantext.Pages.Home as L
import Gargantext.Pages.Layout.Specs.AddCorpus as AC import Gargantext.Pages.Layout.Specs.AddCorpus as AC
import Gargantext.Pages.Layout.Specs.Search as S import Gargantext.Pages.Layout.Specs.Search as S
import Gargantext.Pages.Layout.States (AppState) import Gargantext.Pages.Layout.States (AppState)
...@@ -29,7 +23,6 @@ import Thermite (PerformAction, modifyState) ...@@ -29,7 +23,6 @@ import Thermite (PerformAction, modifyState)
data Action data Action
= Initialize = Initialize
| LandingA L.Action
| LoginA LN.Action | LoginA LN.Action
| SetRoute Routes | SetRoute Routes
| AddCorpusA AC.Action | AddCorpusA AC.Action
...@@ -38,18 +31,14 @@ data Action ...@@ -38,18 +31,14 @@ data Action
| UserPageA U.Action | UserPageA U.Action
| DocAnnotationViewA D.Action | DocAnnotationViewA D.Action
| TreeViewA Tree.Action | TreeViewA Tree.Action
| TabViewA TV.Action
| GraphExplorerA GE.Action | GraphExplorerA GE.Action
| DashboardA Dsh.Action
| Search String | Search String
| Go | Go
| CorpusAnalysisA CA.Action
| ShowLogin | ShowLogin
| ShowAddcorpus | ShowAddcorpus
| NgramsA NG.Action
performAction :: forall props. PerformAction AppState props Action performAction :: PerformAction AppState {} Action
performAction (SetRoute route) _ _ = void do performAction (SetRoute route) _ _ = void do
modifyState $ _ {currentRoute = pure route} modifyState $ _ {currentRoute = pure route}
performAction (Search s) _ _ = void do performAction (Search s) _ _ = void do
...@@ -78,35 +67,37 @@ performAction Initialize _ state = void do ...@@ -78,35 +67,37 @@ performAction Initialize _ state = void do
case lnodes of case lnodes of
Left err -> do Left err -> do
modifyState identity pure unit
Right d -> do Right d -> do
_ <- modifyState $ _ { initialized = true, ntreeState = d}
page <- lift $ DV.loadPage page <- lift $ DV.loadPage
case page of case page of
Left err -> do Left err -> do
modifyState identity pure unit
Right docs -> do Right docs -> void do
modifyState $ _ { initialized = true modifyState $ _ { initialized = true
, ntreeState = if length d > 0 , ntreeState = d
then Tree.exampleTree -- if length d > 0
--then fnTransform $ unsafePartial $ fromJust $ head d -- then Tree.exampleTree
else Tree.initialState -- --then fnTransform $ unsafePartial $ fromJust $ head d
-- else Tree.initialState
, docViewState = docs , docViewState = docs
} }
_ -> do _ -> do
modifyState identity pure unit
performAction _ _ _ = void do performAction (LoginA _) _ _ = pure unit
modifyState identity performAction (AddCorpusA _) _ _ = pure unit
performAction (DocViewA _) _ _ = pure unit
performAction (SearchA _) _ _ = pure unit
performAction (UserPageA _) _ _ = pure unit
performAction (DocAnnotationViewA _) _ _ = pure unit
performAction (TreeViewA _) _ _ = pure unit
performAction (GraphExplorerA _) _ _ = pure unit
---------------------------------------------------------- ----------------------------------------------------------
_LandingA :: Prism' Action L.Action
_LandingA = prism LandingA \action ->
case action of
LandingA caction -> Right caction
_-> Left action
_loginAction :: Prism' Action LN.Action _loginAction :: Prism' Action LN.Action
_loginAction = prism LoginA \action -> _loginAction = prism LoginA \action ->
case action of case action of
...@@ -137,12 +128,6 @@ _userPageAction = prism UserPageA \action -> ...@@ -137,12 +128,6 @@ _userPageAction = prism UserPageA \action ->
UserPageA caction -> Right caction UserPageA caction -> Right caction
_-> Left action _-> Left action
_dashBoardAction :: Prism' Action Dsh.Action
_dashBoardAction = prism DashboardA \action ->
case action of
DashboardA caction -> Right caction
_ -> Left action
_docAnnotationViewAction :: Prism' Action D.Action _docAnnotationViewAction :: Prism' Action D.Action
_docAnnotationViewAction = prism DocAnnotationViewA \action -> _docAnnotationViewAction = prism DocAnnotationViewA \action ->
case action of case action of
...@@ -155,26 +140,8 @@ _treeAction = prism TreeViewA \action -> ...@@ -155,26 +140,8 @@ _treeAction = prism TreeViewA \action ->
TreeViewA caction -> Right caction TreeViewA caction -> Right caction
_-> Left action _-> Left action
_tabviewAction :: Prism' Action TV.Action
_tabviewAction = prism TabViewA \action ->
case action of
TabViewA caction -> Right caction
_-> Left action
_corpusAction :: Prism' Action CA.Action
_corpusAction = prism CorpusAnalysisA \action ->
case action of
CorpusAnalysisA caction -> Right caction
_-> Left action
_graphExplorerAction :: Prism' Action GE.Action _graphExplorerAction :: Prism' Action GE.Action
_graphExplorerAction = prism GraphExplorerA \action -> _graphExplorerAction = prism GraphExplorerA \action ->
case action of case action of
GraphExplorerA caction -> Right caction GraphExplorerA caction -> Right caction
_-> Left action _-> Left action
_NgramsA :: Prism' Action NG.Action
_NgramsA = prism NgramsA \action ->
case action of
NgramsA caction -> Right caction
_-> Left action
...@@ -18,18 +18,18 @@ import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE ...@@ -18,18 +18,18 @@ import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE
import Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsTable as NG import Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsTable as NG
import Gargantext.Pages.Corpus.User.Users as U import Gargantext.Pages.Corpus.User.Users as U
import Gargantext.Pages.Home as L import Gargantext.Pages.Home as L
import Gargantext.Pages.Layout.Actions (Action(..), _LandingA, _NgramsA, _addCorpusAction, _corpusAction, _dashBoardAction, _docAnnotationViewAction, _docViewAction, _graphExplorerAction, _loginAction, _searchAction, _tabviewAction, _treeAction, _userPageAction, performAction) import Gargantext.Pages.Layout.Actions (Action(..), _addCorpusAction, _docAnnotationViewAction, _docViewAction, _graphExplorerAction, _loginAction, _searchAction, _treeAction, _userPageAction, performAction)
import Gargantext.Pages.Layout.Specs.AddCorpus as AC import Gargantext.Pages.Layout.Specs.AddCorpus as AC
import Gargantext.Pages.Layout.Specs.Search as S import Gargantext.Pages.Layout.Specs.Search as S
import Gargantext.Pages.Layout.States (AppState, _addCorpusState, _corpusState, _dashBoardSate, _docAnnotationViewState, _docViewState, _graphExplorerState, _landingState, _loginState, _ngramState, _searchState, _tabviewState, _treeState, _userPageState) import Gargantext.Pages.Layout.States (AppState, _addCorpusState, _docAnnotationViewState, _docViewState, _graphExplorerState, _loginState, _searchState, _treeState, _userPageState)
import Gargantext.Router (Routes(..)) import Gargantext.Router (Routes(..))
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 Thermite (Render, Spec, _render, defaultPerformAction, defaultRender, focus, simpleSpec, withState) import Thermite (Render, Spec, _render, defaultPerformAction, defaultRender, focus, simpleSpec, withState, noState)
import Unsafe.Coerce (unsafeCoerce) import Unsafe.Coerce (unsafeCoerce)
layoutSpec :: forall props. Spec AppState props Action layoutSpec :: Spec AppState {} Action
layoutSpec = layoutSpec =
fold fold
[ routingSpec [ routingSpec
...@@ -40,39 +40,39 @@ layoutSpec = ...@@ -40,39 +40,39 @@ layoutSpec =
] ]
] ]
where where
container :: Spec AppState props Action -> Spec AppState props Action -- NP: what is it for ?
container :: Spec AppState {} Action -> Spec AppState {} Action
container = over _render \render d p s c -> container = over _render \render d p s c ->
(render d p s c) (render d p s c)
pagesComponent :: AppState -> Spec AppState {} Action
pagesComponent :: forall props. AppState -> Spec AppState props Action
pagesComponent s = pagesComponent s =
case s.currentRoute of case s.currentRoute of
Just route -> selectSpec route Just route -> selectSpec route
Nothing -> selectSpec Home Nothing -> selectSpec Home
where where
selectSpec :: Routes -> Spec AppState props Action selectSpec :: Routes -> Spec AppState {} Action
selectSpec CorpusAnalysis = layout0 $ focus _corpusState _corpusAction CA.spec' selectSpec CorpusAnalysis = layout0 $ noState CA.spec'
selectSpec Login = focus _loginState _loginAction LN.renderSpec selectSpec Login = focus _loginState _loginAction LN.renderSpec
selectSpec Home = layout0 $ focus _landingState _LandingA (L.layoutLanding EN) selectSpec Home = layout0 $ noState (L.layoutLanding EN)
selectSpec AddCorpus = layout0 $ focus _addCorpusState _addCorpusAction AC.layoutAddcorpus selectSpec AddCorpus = layout0 $ focus _addCorpusState _addCorpusAction AC.layoutAddcorpus
selectSpec DocView = layout0 $ focus _docViewState _docViewAction DV.layoutDocview selectSpec DocView = layout0 $ focus _docViewState _docViewAction DV.layoutDocview
selectSpec (UserPage i) = layout0 $ focus _userPageState _userPageAction U.layoutUser selectSpec (UserPage i) = layout0 $ focus _userPageState _userPageAction U.layoutUser
selectSpec (DocAnnotation i) = layout0 $ focus _docAnnotationViewState _docAnnotationViewAction D.docview selectSpec (DocAnnotation i) = layout0 $ focus _docAnnotationViewState _docAnnotationViewAction D.docview
selectSpec Tabview = layout0 $ focus _tabviewState _tabviewAction TV.tab1 selectSpec Tabview = layout0 $ noState TV.pureTab1
-- To be removed -- To be removed
selectSpec SearchView = layout0 $ focus _searchState _searchAction S.searchSpec selectSpec SearchView = layout0 $ focus _searchState _searchAction S.searchSpec
selectSpec NGramsTable = layout0 $ focus _ngramState _NgramsA NG.ngramsTableSpec selectSpec NGramsTable = layout0 $ noState NG.ngramsTableSpec
selectSpec PGraphExplorer = focus _graphExplorerState _graphExplorerAction GE.specOld selectSpec PGraphExplorer = focus _graphExplorerState _graphExplorerAction GE.specOld
selectSpec Dashboard = layout0 $ focus _dashBoardSate _dashBoardAction Dsh.layoutDashboard selectSpec Dashboard = layout0 $ noState Dsh.layoutDashboard
-- selectSpec _ = simpleSpec defaultPerformAction defaultRender -- selectSpec _ = simpleSpec defaultPerformAction defaultRender
routingSpec :: forall props. Spec AppState props Action routingSpec :: Spec AppState {} Action
routingSpec = simpleSpec performAction defaultRender routingSpec = simpleSpec performAction defaultRender
layout0 :: forall props. Spec AppState props Action layout0 :: Spec AppState {} Action
-> Spec AppState props Action -> Spec AppState {} Action
layout0 layout = layout0 layout =
fold fold
[ layoutSidebar divSearchBar [ layoutSidebar divSearchBar
...@@ -81,7 +81,7 @@ layout0 layout = ...@@ -81,7 +81,7 @@ layout0 layout =
] ]
where where
outerLayout1 = simpleSpec defaultPerformAction defaultRender outerLayout1 = simpleSpec defaultPerformAction defaultRender
outerLayout :: Spec AppState props Action outerLayout :: Spec AppState {} Action
outerLayout = outerLayout =
cont $ fold cont $ fold
[ withState \st -> [ withState \st ->
...@@ -97,8 +97,8 @@ layout0 layout = ...@@ -97,8 +97,8 @@ layout0 layout =
bs = innerLayout $ layout bs = innerLayout $ layout
innerLayout :: Spec AppState props Action innerLayout :: Spec AppState {} Action
-> Spec AppState props Action -> Spec AppState {} Action
innerLayout = over _render \render d p s c -> innerLayout = over _render \render d p s c ->
[ div [_id "page-wrapper"] [ div [_id "page-wrapper"]
[ [
...@@ -106,8 +106,8 @@ layout0 layout = ...@@ -106,8 +106,8 @@ layout0 layout =
] ]
] ]
layoutSidebar :: forall props. Spec AppState props Action layoutSidebar :: Spec AppState {} Action
-> Spec AppState props Action -> Spec AppState {} Action
layoutSidebar = over _render \render d p s c -> layoutSidebar = over _render \render d p s c ->
[ div [ _id "dafixedtop" [ div [ _id "dafixedtop"
, className "navbar navbar-inverse navbar-fixed-top" , className "navbar navbar-inverse navbar-fixed-top"
...@@ -241,10 +241,10 @@ liNav (LiNav { title : title' ...@@ -241,10 +241,10 @@ liNav (LiNav { title : title'
] ]
-- TODO put the search form in the center of the navBar -- TODO put the search form in the center of the navBar
divSearchBar :: forall props. Spec AppState props Action divSearchBar :: Spec AppState {} Action
divSearchBar = simpleSpec performAction render divSearchBar = simpleSpec performAction render
where where
render :: Render AppState props Action render :: Render AppState {} Action
render dispatch _ state _ = [div [ className "" ] [ searchbar']] render dispatch _ state _ = [div [ className "" ] [ searchbar']]
where where
searchbar' = ul [ className "nav navbar-nav col-md-6 col-md-offset-3" searchbar' = ul [ className "nav navbar-nav col-md-6 col-md-offset-3"
...@@ -262,7 +262,7 @@ divSearchBar = simpleSpec performAction render ...@@ -262,7 +262,7 @@ divSearchBar = simpleSpec performAction render
] ]
] ]
--divDropdownRight :: Render AppState props Action --divDropdownRight :: Render AppState {} Action
divDropdownRight :: (Action -> Effect Unit) -> ReactElement divDropdownRight :: (Action -> Effect Unit) -> ReactElement
divDropdownRight d = divDropdownRight d =
ul [className "nav navbar-nav pull-right"] ul [className "nav navbar-nav pull-right"]
...@@ -285,10 +285,10 @@ divDropdownRight d = ...@@ -285,10 +285,10 @@ divDropdownRight d =
] ]
] ]
layoutFooter :: forall props. Spec AppState props Action layoutFooter :: Spec AppState {} Action
layoutFooter = simpleSpec performAction render layoutFooter = simpleSpec performAction render
where where
render :: Render AppState props Action render :: Render AppState {} Action
render dispatch _ state _ = [div [ className "container1" ] [ hr', footerLegalInfo']] render dispatch _ state _ = [div [ className "container1" ] [ hr', footerLegalInfo']]
where where
footerLegalInfo' = footer [] [ p [] [ text "Gargantext " footerLegalInfo' = footer [] [ p [] [ text "Gargantext "
......
...@@ -21,33 +21,29 @@ import Routing.Hash (setHash) ...@@ -21,33 +21,29 @@ import Routing.Hash (setHash)
import Thermite (PerformAction, modifyState) import Thermite (PerformAction, modifyState)
data Action data Action
= NoOp = SelectDatabase Boolean
| SelectDatabase Boolean
| UnselectDatabase Boolean | UnselectDatabase Boolean
| LoadDatabaseDetails | LoadDatabaseDetails
| GO | GO
performAction :: forall props. PerformAction State props Action performAction :: PerformAction State {} Action
performAction NoOp _ _ = void do
modifyState identity
performAction (SelectDatabase selected) _ _ = void do performAction (SelectDatabase selected) _ _ = void do
modifyState \( state) -> state { select_database = selected } modifyState $ _ { select_database = selected }
performAction (UnselectDatabase unselected) _ _ = void do performAction (UnselectDatabase unselected) _ _ = void do
modifyState \( state) -> state { unselect_database = unselected } modifyState $ _ { unselect_database = unselected }
performAction (LoadDatabaseDetails) _ _ = void do performAction (LoadDatabaseDetails) _ _ = do
res <- lift $ getDatabaseDetails $ QueryString { query_query: "string",query_name: ["Pubmed"]} res <- lift $ getDatabaseDetails $ QueryString { query_query: "string",query_name: ["Pubmed"]}
case res of case res of
Left err -> modifyState $ \(state) -> state Left err -> pure unit
Right resData -> do Right resData -> do
modifyState $ \(state) -> state {response = resData} void $ modifyState $ _ {response = resData}
performAction GO _ _ = void do performAction GO _ _ = do
_ <- liftEffect $ setHash "/corpus" liftEffect $ setHash "/corpus"
_ <- liftEffect $ modalHide "addCorpus" liftEffect $ modalHide "addCorpus"
modifyState identity pure unit
newtype QueryString = QueryString newtype QueryString = QueryString
......
module Gargantext.Pages.Layout.Specs.AddCorpus.Specs where module Gargantext.Pages.Layout.Specs.AddCorpus.Specs where
import Gargantext.Pages.Layout.Specs.AddCorpus.Actions
import Gargantext.Pages.Layout.Specs.AddCorpus.States
import Prelude hiding (div) import Prelude hiding (div)
import Affjax (defaultRequest, printResponseFormatError, request)
import Affjax.RequestBody (RequestBody(..))
import Affjax.ResponseFormat as ResponseFormat
import Control.Monad.Cont.Trans (lift) import Control.Monad.Cont.Trans (lift)
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(..))
...@@ -9,19 +14,17 @@ import Data.HTTP.Method (Method(..)) ...@@ -9,19 +14,17 @@ import Data.HTTP.Method (Method(..))
import Data.Lens (over) import Data.Lens (over)
import Data.Maybe (Maybe(Just)) import Data.Maybe (Maybe(Just))
import Data.MediaType.Common (applicationJSON) import Data.MediaType.Common (applicationJSON)
import Effect.Aff (Aff)
import Effect.Class (liftEffect)
import Effect.Console (log)
import Gargantext.Components.Modals.Modal (modalHide) import Gargantext.Components.Modals.Modal (modalHide)
import Gargantext.Pages.Layout.Specs.AddCorpus.States
import Gargantext.Pages.Layout.Specs.AddCorpus.Actions
import React (ReactElement) import React (ReactElement)
import React.DOM (button, div, h3, h5, li, span, text, ul) import React.DOM (button, div, h3, h5, li, span, text, ul)
import React.DOM.Props (_data, _id, _type, aria, className, onClick, role) import React.DOM.Props (_data, _id, _type, aria, className, onClick, role)
import Thermite (PerformAction, Render, Spec, _render, cotransform, modifyState, simpleSpec) import Thermite (PerformAction, Render, Spec, _render, simpleSpec)
modalSpec :: forall props. Boolean -> String -> Spec State props Action -> Spec State props Action modalSpec :: Boolean -> String -> Spec State {} Action -> Spec State {} Action
modalSpec sm t = over _render \render d p s c -> modalSpec sm t = over _render \render d p s c ->
[ div [ _id "addCorpus", className $ "modal myModal" <> if sm then "" else " fade" [ div [ _id "addCorpus", className $ "modal myModal" <> if sm then "" else " fade"
, role "dialog" , role "dialog"
...@@ -43,7 +46,7 @@ modalSpec sm t = over _render \render d p s c -> ...@@ -43,7 +46,7 @@ modalSpec sm t = over _render \render d p s c ->
] ]
spec' :: forall props. Spec State props Action spec' :: Spec State {} Action
spec' = modalSpec true "Search Results" layoutAddcorpus spec' = modalSpec true "Search Results" layoutAddcorpus
...@@ -93,10 +96,10 @@ layoutModal state = ...@@ -93,10 +96,10 @@ layoutModal state =
] ]
layoutAddcorpus :: forall props. Spec State props Action layoutAddcorpus :: Spec State {} Action
layoutAddcorpus = simpleSpec performAction render layoutAddcorpus = simpleSpec performAction render
where where
render :: Render State props Action render :: Render State {} Action
render dispatch _ state _ = render dispatch _ state _ =
[ div [className "container1"] [] [ div [className "container1"] []
, div [className "container1"] , div [className "container1"]
...@@ -119,3 +122,25 @@ layoutAddcorpus = simpleSpec performAction render ...@@ -119,3 +122,25 @@ layoutAddcorpus = simpleSpec performAction render
span [] [text o.name] span [] [text o.name]
, span [className "badge badge-default badge-pill"] [ text $ show o.count] , span [className "badge badge-default badge-pill"] [ text $ show o.count]
] ]
countResults :: Query -> Aff (Either String (Int))
countResults query = do
res <- request $ defaultRequest
{ url = "http://localhost:8008/count"
, responseFormat = ResponseFormat.json
, method = Left POST
, headers = []
, content = Just $ Json $ encodeJson query
}
case res.body of
Left err -> do
_ <- liftEffect $ log $ printResponseFormatError err
pure $ Left $ printResponseFormatError err
Right json -> do
--_ <- liftEffect $ log $ show a.status
--_ <- liftEffect $ log $ show a.headers
--_ <- liftEffect $ log $ show a.body
let obj = decodeJson json
pure obj
...@@ -15,6 +15,22 @@ newtype Response = Response ...@@ -15,6 +15,22 @@ newtype Response = Response
, name :: String , name :: String
} }
newtype Query = Query
{
query_query :: String
, query_name :: Array String
}
instance encodeJsonQuery :: EncodeJson Query where
encodeJson (Query post)
= "query_query" := post.query_query
~> "query_name" := post.query_name
~> jsonEmptyObject
instance decodeJsonresponse :: DecodeJson Response where instance decodeJsonresponse :: DecodeJson Response where
decodeJson json = do decodeJson json = do
obj <- decodeJson json obj <- decodeJson json
...@@ -29,6 +45,3 @@ initialState = ...@@ -29,6 +45,3 @@ initialState =
, unselect_database : true , unselect_database : true
, response : [] , response : []
} }
...@@ -23,32 +23,25 @@ initialState = ...@@ -23,32 +23,25 @@ initialState =
data Action data Action
= NoOp = GO
| GO
| SetQuery String | SetQuery String
performAction :: forall props. PerformAction State props Action performAction :: PerformAction State {} Action
performAction NoOp _ _ = void do
modifyState identity
performAction (SetQuery q) _ _ = void do performAction (SetQuery q) _ _ = void do
modifyState \( state) -> state { query = q } modifyState $ _ { query = q }
performAction GO _ _ = void do performAction GO _ _ = void do
liftEffect $ setHash "/addCorpus" liftEffect $ setHash "/addCorpus"
modifyState identity
unsafeEventValue :: forall event. event -> String unsafeEventValue :: forall event. event -> String
unsafeEventValue e = (unsafeCoerce e).target.value unsafeEventValue e = (unsafeCoerce e).target.value
searchSpec :: forall props. Spec State props Action searchSpec :: Spec State {} Action
searchSpec = simpleSpec performAction render searchSpec = simpleSpec performAction render
where where
render :: Render State props Action render :: Render State {} Action
render dispatch _ state _ = render dispatch _ state _ =
[ div [className "container1"] [] [ div [className "container1"] []
, div [className "container1"] , div [className "container1"]
......
...@@ -4,26 +4,18 @@ import Prelude hiding (div) ...@@ -4,26 +4,18 @@ import Prelude hiding (div)
import Data.Lens (Lens', lens) import Data.Lens (Lens', lens)
import Data.Maybe (Maybe(Just)) import Data.Maybe (Maybe(Just))
import Gargantext.Components.Login as LN
import Gargantext.Components.Login as LN import Gargantext.Components.Tree as Tree
import Gargantext.Components.Tree as Tree import Gargantext.Pages.Corpus.Doc.Annotation as D
import Gargantext.Pages.Layout.Specs.AddCorpus as AC import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV
import Gargantext.Pages.Corpus as CA
import Gargantext.Pages.Corpus.Doc.Annotation as D
import Gargantext.Pages.Corpus.Doc.Facets as TV
import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV
import Gargantext.Pages.Corpus.Doc.Facets.Dashboard as Dsh
import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE
import Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsTable as NG import Gargantext.Pages.Corpus.User.Users as U
import Gargantext.Pages.Corpus.User.Users as U import Gargantext.Pages.Layout.Specs.AddCorpus as AC
import Gargantext.Pages.Home as L import Gargantext.Pages.Layout.Specs.Search as S
import Gargantext.Pages.Layout.Specs.Search as S import Gargantext.Router (Routes(..))
import Gargantext.Router (Routes(..))
type AppState = type AppState =
{ currentRoute :: Maybe Routes { currentRoute :: Maybe Routes
, landingState :: L.State
, loginState :: LN.State , loginState :: LN.State
, addCorpusState :: AC.State , addCorpusState :: AC.State
, docViewState :: DV.State , docViewState :: DV.State
...@@ -31,21 +23,16 @@ type AppState = ...@@ -31,21 +23,16 @@ type AppState =
, userPageState :: U.State , userPageState :: U.State
, docAnnotationState :: D.State , docAnnotationState :: D.State
, ntreeState :: Tree.State , ntreeState :: Tree.State
, tabviewState :: TV.State
, search :: String , search :: String
, corpusState :: CA.State
, showLogin :: Boolean , showLogin :: Boolean
, showCorpus :: Boolean , showCorpus :: Boolean
, graphExplorerState :: GE.State , graphExplorerState :: GE.State
, initialized :: Boolean , initialized :: Boolean
, ngramState :: NG.State
, dashboardState :: Dsh.State
} }
initAppState :: AppState initAppState :: AppState
initAppState = initAppState =
{ currentRoute : Just Home { currentRoute : Just Home
, landingState : L.initialState
, loginState : LN.initialState , loginState : LN.initialState
, addCorpusState : AC.initialState , addCorpusState : AC.initialState
, docViewState : DV.tdata , docViewState : DV.tdata
...@@ -53,21 +40,14 @@ initAppState = ...@@ -53,21 +40,14 @@ initAppState =
, userPageState : U.initialState , userPageState : U.initialState
, docAnnotationState : D.initialState , docAnnotationState : D.initialState
, ntreeState : Tree.exampleTree , ntreeState : Tree.exampleTree
, tabviewState : TV.initialState
, search : "" , search : ""
, corpusState : CA.initialState
, showLogin : false , showLogin : false
, showCorpus : false , showCorpus : false
, graphExplorerState : GE.initialState , graphExplorerState : GE.initialState
, initialized : false , initialized : false
, ngramState : NG.initialState
, dashboardState : Dsh.initialState
} }
--------------------------------------------------------- ---------------------------------------------------------
_landingState :: Lens' AppState L.State
_landingState = lens (\s -> s.landingState) (\s ss -> s{landingState = ss})
_loginState :: Lens' AppState LN.State _loginState :: Lens' AppState LN.State
_loginState = lens (\s -> s.loginState) (\s ss -> s{loginState = ss}) _loginState = lens (\s -> s.loginState) (\s ss -> s{loginState = ss})
...@@ -89,17 +69,5 @@ _docAnnotationViewState = lens (\s -> s.docAnnotationState) (\s ss -> s{docAnnot ...@@ -89,17 +69,5 @@ _docAnnotationViewState = lens (\s -> s.docAnnotationState) (\s ss -> s{docAnnot
_treeState :: Lens' AppState Tree.State _treeState :: Lens' AppState Tree.State
_treeState = lens (\s -> s.ntreeState) (\s ss -> s {ntreeState = ss}) _treeState = lens (\s -> s.ntreeState) (\s ss -> s {ntreeState = ss})
_tabviewState :: Lens' AppState TV.State
_tabviewState = lens (\s -> s.tabviewState) (\s ss -> s {tabviewState = ss})
_corpusState :: Lens' AppState CA.State
_corpusState = lens (\s -> s.corpusState) (\s ss -> s {corpusState = ss})
_dashBoardSate :: Lens' AppState Dsh.State
_dashBoardSate = lens (\s -> s.dashboardState) (\s ss -> s {dashboardState = ss})
_graphExplorerState :: Lens' AppState GE.State _graphExplorerState :: Lens' AppState GE.State
_graphExplorerState = lens (\s -> s.graphExplorerState) (\s ss -> s{graphExplorerState = ss}) _graphExplorerState = lens (\s -> s.graphExplorerState) (\s ss -> s{graphExplorerState = ss})
_ngramState :: Lens' AppState NG.State
_ngramState = lens (\s -> s.ngramState) (\s ss -> s{ngramState = ss})
...@@ -32,11 +32,11 @@ instance showRoutes :: Show Routes where ...@@ -32,11 +32,11 @@ instance showRoutes :: Show Routes where
show Login = "Login" show Login = "Login"
show AddCorpus = "AddCorpus" show AddCorpus = "AddCorpus"
show DocView = "DocView" show DocView = "DocView"
show SearchView = "SearchView" show SearchView = "Search"
show (UserPage i) = "UserPage" show (UserPage i) = "User"
show (DocAnnotation i)= "DocumentView" show (DocAnnotation i)= "Document"
show Tabview = "Tabview" show Tabview = "Tabview"
show CorpusAnalysis = "corpus" show CorpusAnalysis = "Corpus"
show PGraphExplorer = "graphExplorer" show PGraphExplorer = "graphExplorer"
show NGramsTable = "NGramsTable" show NGramsTable = "NGramsTable"
show Dashboard = "Dashboard" show Dashboard = "Dashboard"
...@@ -49,7 +49,7 @@ routing :: Match Routes ...@@ -49,7 +49,7 @@ routing :: Match Routes
routing = routing =
Login <$ route "login" Login <$ route "login"
<|> Tabview <$ route "tabview" <|> Tabview <$ route "tabview"
<|> DocAnnotation <$> (route "documentView" *> int) <|> DocAnnotation <$> (route "document" *> int)
<|> UserPage <$> (route "user" *> int) <|> UserPage <$> (route "user" *> int)
<|> SearchView <$ route "search" <|> SearchView <$ route "search"
<|> DocView <$ route "docView" <|> DocView <$ route "docView"
......
...@@ -4,15 +4,20 @@ import Prelude ...@@ -4,15 +4,20 @@ import Prelude
import Data.Argonaut (class DecodeJson, Json, getFieldOptional) import Data.Argonaut (class DecodeJson, Json, getFieldOptional)
import Data.Either (Either) import Data.Either (Either)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..), fromMaybe)
import Foreign.Object (Object) import Foreign.Object (Object)
foreign import isNull :: forall a. a -> Boolean foreign import isNull :: forall a. a -> Boolean
getFieldOptional' :: forall t9. DecodeJson t9 => Object Json -> String -> Either String (Maybe t9) getFieldOptional' :: forall a. DecodeJson a => Object Json -> String -> Either String (Maybe a)
getFieldOptional' o s = (case _ of getFieldOptional' o s = (case _ of
Just v -> if isNull v then Nothing else v Just v -> if isNull v then Nothing else v
Nothing -> Nothing Nothing -> Nothing
) <$> (getFieldOptional o s) ) <$> (getFieldOptional o s)
infix 7 getFieldOptional' as .?| infix 7 getFieldOptional' as .?|
getFieldOptionalAsMempty :: forall a. DecodeJson a => Monoid a => Object Json -> String -> Either String a
getFieldOptionalAsMempty o s = fromMaybe mempty <$> (getFieldOptional' o s)
infix 7 getFieldOptionalAsMempty as .|
module Test.Main where module Test.Main where
--import Prelude import Prelude
--import Control.Monad.Eff (Eff) --import Control.Monad.Eff (Eff)
--import Control.Monad.Eff.Console (CONSOLE, log) --import Control.Monad.Eff.Console (CONSOLE, log)
--
--main :: forall e. Eff (console :: CONSOLE | e) Unit --main :: forall e. Eff (console :: CONSOLE | e) Unit
--main = do --main = do
-- log "You should add some tests." -- log "You should add some tests."
...@@ -1218,6 +1218,10 @@ color-name@1.1.3: ...@@ -1218,6 +1218,10 @@ color-name@1.1.3:
version "1.1.3" version "1.1.3"
resolved "https://registry.yarnpkg.com/color-name/-/color-name-1.1.3.tgz#a7d0558bd89c42f795dd42328f740831ca53bc25" resolved "https://registry.yarnpkg.com/color-name/-/color-name-1.1.3.tgz#a7d0558bd89c42f795dd42328f740831ca53bc25"
colors@1.0.3:
version "1.0.3"
resolved "https://registry.yarnpkg.com/colors/-/colors-1.0.3.tgz#0433f44d809680fdeb60ed260f1b0c262e82a40b"
colors@>=0.6.0: colors@>=0.6.0:
version "1.3.2" version "1.3.2"
resolved "https://registry.yarnpkg.com/colors/-/colors-1.3.2.tgz#2df8ff573dfbf255af562f8ce7181d6b971a359b" resolved "https://registry.yarnpkg.com/colors/-/colors-1.3.2.tgz#2df8ff573dfbf255af562f8ce7181d6b971a359b"
...@@ -1294,6 +1298,10 @@ core-util-is@~1.0.0: ...@@ -1294,6 +1298,10 @@ core-util-is@~1.0.0:
version "1.0.2" version "1.0.2"
resolved "https://registry.yarnpkg.com/core-util-is/-/core-util-is-1.0.2.tgz#b5fd54220aa2bc5ab57aab7140c940754503c1a7" resolved "https://registry.yarnpkg.com/core-util-is/-/core-util-is-1.0.2.tgz#b5fd54220aa2bc5ab57aab7140c940754503c1a7"
corser@~2.0.0:
version "2.0.1"
resolved "https://registry.yarnpkg.com/corser/-/corser-2.0.1.tgz#8eda252ecaab5840dcd975ceb90d9370c819ff87"
create-ecdh@^4.0.0: create-ecdh@^4.0.0:
version "4.0.3" version "4.0.3"
resolved "https://registry.yarnpkg.com/create-ecdh/-/create-ecdh-4.0.3.tgz#c9111b6f33045c4697f144787f9254cdc77c45ff" resolved "https://registry.yarnpkg.com/create-ecdh/-/create-ecdh-4.0.3.tgz#c9111b6f33045c4697f144787f9254cdc77c45ff"
...@@ -1374,6 +1382,12 @@ debug@^2.1.2, debug@^2.2.0, debug@^2.3.3, debug@^2.6.8: ...@@ -1374,6 +1382,12 @@ debug@^2.1.2, debug@^2.2.0, debug@^2.3.3, debug@^2.6.8:
dependencies: dependencies:
ms "2.0.0" ms "2.0.0"
debug@^3.1.0:
version "3.1.0"
resolved "https://registry.yarnpkg.com/debug/-/debug-3.1.0.tgz#5bb5a0672628b64149566ba16819e61518c67261"
dependencies:
ms "2.0.0"
decode-uri-component@^0.2.0: decode-uri-component@^0.2.0:
version "0.2.0" version "0.2.0"
resolved "https://registry.yarnpkg.com/decode-uri-component/-/decode-uri-component-0.2.0.tgz#eb3913333458775cb84cd1a1fae062106bb87545" resolved "https://registry.yarnpkg.com/decode-uri-component/-/decode-uri-component-0.2.0.tgz#eb3913333458775cb84cd1a1fae062106bb87545"
...@@ -1530,6 +1544,15 @@ echarts@^3.8.5: ...@@ -1530,6 +1544,15 @@ echarts@^3.8.5:
dependencies: dependencies:
zrender "3.7.4" zrender "3.7.4"
ecstatic@^3.0.0:
version "3.3.0"
resolved "https://registry.yarnpkg.com/ecstatic/-/ecstatic-3.3.0.tgz#91cd417d152abf85b37b1ab3ebf3bd25cdc64e80"
dependencies:
he "^1.1.1"
mime "^1.6.0"
minimist "^1.1.0"
url-join "^2.0.5"
element-resize-detector@latest: element-resize-detector@latest:
version "1.1.14" version "1.1.14"
resolved "https://registry.yarnpkg.com/element-resize-detector/-/element-resize-detector-1.1.14.tgz#af064a0a618a820ad570a95c5eec5b77be0128c1" resolved "https://registry.yarnpkg.com/element-resize-detector/-/element-resize-detector-1.1.14.tgz#af064a0a618a820ad570a95c5eec5b77be0128c1"
...@@ -1576,6 +1599,10 @@ esutils@^2.0.2: ...@@ -1576,6 +1599,10 @@ esutils@^2.0.2:
version "2.0.2" version "2.0.2"
resolved "https://registry.yarnpkg.com/esutils/-/esutils-2.0.2.tgz#0abf4f1caa5bcb1f7a9d8acc6dea4faaa04bac9b" resolved "https://registry.yarnpkg.com/esutils/-/esutils-2.0.2.tgz#0abf4f1caa5bcb1f7a9d8acc6dea4faaa04bac9b"
eventemitter3@^3.0.0:
version "3.1.0"
resolved "https://registry.yarnpkg.com/eventemitter3/-/eventemitter3-3.1.0.tgz#090b4d6cdbd645ed10bf750d4b5407942d7ba163"
events@~1.1.0: events@~1.1.0:
version "1.1.1" version "1.1.1"
resolved "https://registry.yarnpkg.com/events/-/events-1.1.1.tgz#9ebdb7635ad099c70dcc4c2a1f5004288e8bd924" resolved "https://registry.yarnpkg.com/events/-/events-1.1.1.tgz#9ebdb7635ad099c70dcc4c2a1f5004288e8bd924"
...@@ -1713,6 +1740,12 @@ fill-range@^4.0.0: ...@@ -1713,6 +1740,12 @@ fill-range@^4.0.0:
repeat-string "^1.6.1" repeat-string "^1.6.1"
to-regex-range "^2.1.0" to-regex-range "^2.1.0"
follow-redirects@^1.0.0:
version "1.5.7"
resolved "https://registry.yarnpkg.com/follow-redirects/-/follow-redirects-1.5.7.tgz#a39e4804dacb90202bca76a9e2ac10433ca6a69a"
dependencies:
debug "^3.1.0"
for-in@^1.0.2: for-in@^1.0.2:
version "1.0.2" version "1.0.2"
resolved "https://registry.yarnpkg.com/for-in/-/for-in-1.0.2.tgz#81068d295a8142ec0ac726c6e2200c30fb6d5e80" resolved "https://registry.yarnpkg.com/for-in/-/for-in-1.0.2.tgz#81068d295a8142ec0ac726c6e2200c30fb6d5e80"
...@@ -1860,6 +1893,10 @@ hash.js@^1.0.0, hash.js@^1.0.3: ...@@ -1860,6 +1893,10 @@ hash.js@^1.0.0, hash.js@^1.0.3:
inherits "^2.0.3" inherits "^2.0.3"
minimalistic-assert "^1.0.1" minimalistic-assert "^1.0.1"
he@^1.1.1:
version "1.1.1"
resolved "https://registry.yarnpkg.com/he/-/he-1.1.1.tgz#93410fd21b009735151f8868c2f271f3427e23fd"
hmac-drbg@^1.0.0: hmac-drbg@^1.0.0:
version "1.0.1" version "1.0.1"
resolved "https://registry.yarnpkg.com/hmac-drbg/-/hmac-drbg-1.0.1.tgz#d2745701025a6c775a6c545793ed502fc0c649a1" resolved "https://registry.yarnpkg.com/hmac-drbg/-/hmac-drbg-1.0.1.tgz#d2745701025a6c775a6c545793ed502fc0c649a1"
...@@ -1879,6 +1916,27 @@ htmlescape@^1.1.0: ...@@ -1879,6 +1916,27 @@ htmlescape@^1.1.0:
version "1.1.1" version "1.1.1"
resolved "https://registry.yarnpkg.com/htmlescape/-/htmlescape-1.1.1.tgz#3a03edc2214bca3b66424a3e7959349509cb0351" resolved "https://registry.yarnpkg.com/htmlescape/-/htmlescape-1.1.1.tgz#3a03edc2214bca3b66424a3e7959349509cb0351"
http-proxy@^1.8.1:
version "1.17.0"
resolved "https://registry.yarnpkg.com/http-proxy/-/http-proxy-1.17.0.tgz#7ad38494658f84605e2f6db4436df410f4e5be9a"
dependencies:
eventemitter3 "^3.0.0"
follow-redirects "^1.0.0"
requires-port "^1.0.0"
http-server@^0.11.1:
version "0.11.1"
resolved "https://registry.yarnpkg.com/http-server/-/http-server-0.11.1.tgz#2302a56a6ffef7f9abea0147d838a5e9b6b6a79b"
dependencies:
colors "1.0.3"
corser "~2.0.0"
ecstatic "^3.0.0"
http-proxy "^1.8.1"
opener "~1.4.0"
optimist "0.6.x"
portfinder "^1.0.13"
union "~0.4.3"
https-browserify@~0.0.0: https-browserify@~0.0.0:
version "0.0.1" version "0.0.1"
resolved "https://registry.yarnpkg.com/https-browserify/-/https-browserify-0.0.1.tgz#3f91365cabe60b77ed0ebba24b454e3e09d95a82" resolved "https://registry.yarnpkg.com/https-browserify/-/https-browserify-0.0.1.tgz#3f91365cabe60b77ed0ebba24b454e3e09d95a82"
...@@ -2326,7 +2384,7 @@ miller-rabin@^4.0.0: ...@@ -2326,7 +2384,7 @@ miller-rabin@^4.0.0:
bn.js "^4.0.0" bn.js "^4.0.0"
brorand "^1.0.1" brorand "^1.0.1"
mime@^1.2.9: mime@^1.2.9, mime@^1.6.0:
version "1.6.0" version "1.6.0"
resolved "https://registry.yarnpkg.com/mime/-/mime-1.6.0.tgz#32cd9e5c64553bd58d19a568af452acff04981b1" resolved "https://registry.yarnpkg.com/mime/-/mime-1.6.0.tgz#32cd9e5c64553bd58d19a568af452acff04981b1"
...@@ -2380,7 +2438,7 @@ mixin-deep@^1.2.0: ...@@ -2380,7 +2438,7 @@ mixin-deep@^1.2.0:
for-in "^1.0.2" for-in "^1.0.2"
is-extendable "^1.0.1" is-extendable "^1.0.1"
mkdirp@^0.5.0, mkdirp@^0.5.1: mkdirp@0.5.x, mkdirp@^0.5.0, mkdirp@^0.5.1:
version "0.5.1" version "0.5.1"
resolved "https://registry.yarnpkg.com/mkdirp/-/mkdirp-0.5.1.tgz#30057438eac6cf7f8c4767f38648d6697d75c903" resolved "https://registry.yarnpkg.com/mkdirp/-/mkdirp-0.5.1.tgz#30057438eac6cf7f8c4767f38648d6697d75c903"
dependencies: dependencies:
...@@ -2600,7 +2658,11 @@ onetime@^2.0.0: ...@@ -2600,7 +2658,11 @@ onetime@^2.0.0:
dependencies: dependencies:
mimic-fn "^1.0.0" mimic-fn "^1.0.0"
optimist@>=0.3.4: opener@~1.4.0:
version "1.4.3"
resolved "https://registry.yarnpkg.com/opener/-/opener-1.4.3.tgz#5c6da2c5d7e5831e8ffa3964950f8d6674ac90b8"
optimist@0.6.x, optimist@>=0.3.4:
version "0.6.1" version "0.6.1"
resolved "https://registry.yarnpkg.com/optimist/-/optimist-0.6.1.tgz#da3ea74686fa21a19a111c326e90eb15a0196686" resolved "https://registry.yarnpkg.com/optimist/-/optimist-0.6.1.tgz#da3ea74686fa21a19a111c326e90eb15a0196686"
dependencies: dependencies:
...@@ -2698,6 +2760,14 @@ platform-name@^1.0.0: ...@@ -2698,6 +2760,14 @@ platform-name@^1.0.0:
dependencies: dependencies:
inspect-with-kind "^1.0.4" inspect-with-kind "^1.0.4"
portfinder@^1.0.13:
version "1.0.17"
resolved "https://registry.yarnpkg.com/portfinder/-/portfinder-1.0.17.tgz#a8a1691143e46c4735edefcf4fbcccedad26456a"
dependencies:
async "^1.5.2"
debug "^2.2.0"
mkdirp "0.5.x"
posix-character-classes@^0.1.0: posix-character-classes@^0.1.0:
version "0.1.1" version "0.1.1"
resolved "https://registry.yarnpkg.com/posix-character-classes/-/posix-character-classes-0.1.1.tgz#01eac0fe3b5af71a2a6c02feabb8c1fef7e00eab" resolved "https://registry.yarnpkg.com/posix-character-classes/-/posix-character-classes-0.1.1.tgz#01eac0fe3b5af71a2a6c02feabb8c1fef7e00eab"
...@@ -2820,6 +2890,10 @@ purescript@^0.12.0: ...@@ -2820,6 +2890,10 @@ purescript@^0.12.0:
dependencies: dependencies:
install-purescript-cli "^0.4.0 || ^0.3.0" install-purescript-cli "^0.4.0 || ^0.3.0"
qs@~2.3.3:
version "2.3.3"
resolved "https://registry.yarnpkg.com/qs/-/qs-2.3.3.tgz#e9e85adbe75da0bbe4c8e0476a086290f863b404"
querystring-es3@~0.2.0: querystring-es3@~0.2.0:
version "0.2.1" version "0.2.1"
resolved "https://registry.yarnpkg.com/querystring-es3/-/querystring-es3-0.2.1.tgz#9ec61f79049875707d69414596fd907a4d711e73" resolved "https://registry.yarnpkg.com/querystring-es3/-/querystring-es3-0.2.1.tgz#9ec61f79049875707d69414596fd907a4d711e73"
...@@ -3009,6 +3083,10 @@ repeating@^2.0.0: ...@@ -3009,6 +3083,10 @@ repeating@^2.0.0:
dependencies: dependencies:
is-finite "^1.0.0" is-finite "^1.0.0"
requires-port@^1.0.0:
version "1.0.0"
resolved "https://registry.yarnpkg.com/requires-port/-/requires-port-1.0.0.tgz#925d2601d39ac485e091cf0da5c6e694dc3dcaff"
resolve-from-npm@^2.0.4: resolve-from-npm@^2.0.4:
version "2.0.4" version "2.0.4"
resolved "https://registry.yarnpkg.com/resolve-from-npm/-/resolve-from-npm-2.0.4.tgz#d331f8b7fc40a710281fdf8ff7daeaf223717495" resolved "https://registry.yarnpkg.com/resolve-from-npm/-/resolve-from-npm-2.0.4.tgz#d331f8b7fc40a710281fdf8ff7daeaf223717495"
...@@ -3553,6 +3631,12 @@ union-value@^1.0.0: ...@@ -3553,6 +3631,12 @@ union-value@^1.0.0:
is-extendable "^0.1.1" is-extendable "^0.1.1"
set-value "^0.4.3" set-value "^0.4.3"
union@~0.4.3:
version "0.4.6"
resolved "https://registry.yarnpkg.com/union/-/union-0.4.6.tgz#198fbdaeba254e788b0efcb630bc11f24a2959e0"
dependencies:
qs "~2.3.3"
unset-value@^1.0.0: unset-value@^1.0.0:
version "1.0.0" version "1.0.0"
resolved "https://registry.yarnpkg.com/unset-value/-/unset-value-1.0.0.tgz#8376873f7d2335179ffb1e6fc3a8ed0dfc8ab559" resolved "https://registry.yarnpkg.com/unset-value/-/unset-value-1.0.0.tgz#8376873f7d2335179ffb1e6fc3a8ed0dfc8ab559"
...@@ -3568,6 +3652,10 @@ urix@^0.1.0: ...@@ -3568,6 +3652,10 @@ urix@^0.1.0:
version "0.1.0" version "0.1.0"
resolved "https://registry.yarnpkg.com/urix/-/urix-0.1.0.tgz#da937f7a62e21fec1fd18d49b35c2935067a6c72" resolved "https://registry.yarnpkg.com/urix/-/urix-0.1.0.tgz#da937f7a62e21fec1fd18d49b35c2935067a6c72"
url-join@^2.0.5:
version "2.0.5"
resolved "https://registry.yarnpkg.com/url-join/-/url-join-2.0.5.tgz#5af22f18c052a000a48d7b82c5e9c2e2feeda728"
url@~0.11.0: url@~0.11.0:
version "0.11.0" version "0.11.0"
resolved "https://registry.yarnpkg.com/url/-/url-0.11.0.tgz#3838e97cfc60521eb73c525a8e55bfdd9e2e28f1" resolved "https://registry.yarnpkg.com/url/-/url-0.11.0.tgz#3838e97cfc60521eb73c525a8e55bfdd9e2e28f1"
......
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