Commit 5ff4dc03 authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

Merge branch 'dev-search-removal' into dev

parents 517f6b28 a00f9694
......@@ -2,16 +2,17 @@ module Gargantext.Components.Login where
import Control.Monad.Cont.Trans (lift)
import Data.Int as Int
import Data.Lens (over, view)
import Data.Lens (over)
import Data.Maybe (Maybe(..))
import Data.Traversable (traverse_)
import Data.Tuple.Nested((/\))
import Effect.Class (liftEffect)
import Effect (Effect)
import Effect.Aff (Aff)
import React.DOM (a, button, div, h2, h4, h5, i, input, label, p, span, text)
import React.DOM.Props (_data, _id, _type, aria, className, href, maxLength, name, onClick, onInput, placeholder, role, target, value)
import Reactix as R
import Reactix.DOM.HTML as H
import React.DOM (button, div, h5, span, text)
import React.DOM.Props (_data, _id, _type, aria, className, role)
import Thermite (PerformAction, Render, Spec, _render, modifyState_, simpleSpec)
import Unsafe.Coerce (unsafeCoerce)
import Web.HTML (window)
import Web.HTML.Window (localStorage)
import Web.Storage.Storage (getItem, setItem, removeItem)
......@@ -47,8 +48,7 @@ initialState = do
data Action
= PostAuth
| SetUserName String
| SetPassword String
| SetCredentials String String
modalSpec :: forall props. Boolean -> String -> Spec State props Action -> Spec State props Action
......@@ -81,110 +81,144 @@ modalSpec sm t = over _render \render d p s c ->
spec' :: Spec State {} Action
spec' = modalSpec true "Login" renderSpec
performAction :: PerformAction State {} Action
performAction (SetCredentials usr pwd) _ _ = do
modifyState_ $ _ { username = usr, password = pwd }
performAction PostAuth _ {username, password} = do
res <- lift $ postAuthRequest $ AuthRequest {username, password}
case res of
AuthResponse {inval: Just (AuthInvalid {message})} ->
modifyState_ $ _ { errorMessage = message }
AuthResponse {valid} -> do
liftEffect $ setAuthData valid
modifyState_ $ _ {authData = valid, errorMessage = ""}
liftEffect $ modalHide "loginModal"
renderSpec :: Spec State {} Action
renderSpec = simpleSpec performAction render
where
performAction :: PerformAction State {} Action
render :: Render State {} Action
render dispatch _ state _ =
[R2.scuff $ renderCpt dispatch state]
performAction (SetUserName usr) _ _ =
modifyState_ $ _ { username = usr }
performAction (SetPassword pwd) _ _ =
modifyState_ $ _ { password = pwd }
renderCpt :: (Action -> Effect Unit) -> State -> R.Element
renderCpt d s = R.createElement el {} []
where
el = R.hooksComponent "RenderComponent" cpt
cpt {} _children = do
(state /\ setState) <- R.useState' s
performAction PostAuth _ {username, password} = do
res <- lift $ postAuthRequest $ AuthRequest {username, password}
case res of
AuthResponse {inval: Just (AuthInvalid {message})} ->
modifyState_ $ _ { errorMessage = message }
AuthResponse {valid} -> do
liftEffect $ setAuthData valid
modifyState_ $ _ {authData = valid, errorMessage = ""}
liftEffect $ modalHide "loginModal"
R.useEffect $
if (state /= s) then do
_ <- d $ SetCredentials state.username state.password
pure $ d $ PostAuth
else
pure $ pure $ unit
render :: Render State {} Action
render dispatch _ state _ =
[ div [className "row"]
[ div [className "col-md-10 col-md-push-1"]
[ h2 [className "text-primary center m-a-2"]
[ i [className "material-icons md-36"] [text "control_point"]
, span [className "icon-text"] [text "Gargantext"]
]
, div [className "card-group"]
[ div [className "card"]
[ div [className "card-block"]
[ div [className "center"]
[ h4 [className "m-b-0"]
[ span [className "icon-text"] [ text "Welcome :)"] ]
, p [className "text-muted"]
[ text $ "Login to your account or",
a [ target "blank",href "https://iscpif.fr/services/applyforourservices/"] [text " ask to get an access"]
]
pure $ renderLogin (state /\ setState)
renderLogin :: R.State State -> R.Element
renderLogin (state /\ setState) = R.createElement el {} []
where
el = R.hooksComponent "RenderLogin" cpt
cpt {} _children = do
username <- R.useState' state.username
password <- R.useState' state.password
pure $ H.div {className: "row"}
[ gargLogo
, H.div {className: "card-group"}
[ H.div {className: "card"}
[ H.div {className: "card-block"}
[ H.div {className: "center"}
[ H.h4 {className: "m-b-0"}
[ H.span {className: "icon-text"}
[ H.text "Welcome :)"]
]
, div []
[ input [_type "hidden",
name "csrfmiddlewaretoken",
-- TODO hard-coded CSRF token
value "Wy52D2nor8kC1r1Y4GrsrSIxQ2eqW8UwkdiQQshMoRwobzU4uldknRUhP0j4WcEM" ]
, div [className "form-group"]
[ p [] [text state.errorMessage]
, input [className "form-control", _id "id_username",maxLength "254", name "username", placeholder "username", _type "text",value state.username, onInput \e -> dispatch (SetUserName $ R2.unsafeEventValue e)]
]
, div [className "form-group"]
[ input [className "form-control", _id "id_password", name "password", placeholder "password", _type "password",value state.password,onInput \e -> dispatch (SetPassword $ R2.unsafeEventValue e)]
, div [className "clearfix"] []
]
, div [className "center"]
[ label []
[ div [className "checkbox"]
[ input [_id "terms-accept", _type "checkbox", value "", className "checkbox"]
, text "I accept the terms of uses ",
a [href "http://gitlab.iscpif.fr/humanities/tofu/tree/master"] [text " [ Read the terms of use ] "]
]
, button [_id "login-button",className "btn btn-primary btn-rounded", _type "submit", onClick \_ -> dispatch $ PostAuth] [text "Login"]
, H.p {className: "text-muted"}
[ H.text $ "Login to your account or",
H.a { target: "blank"
, href: "https://iscpif.fr/services/applyforourservices/"
}
[H.text " ask to get an access"]
]
]
, H.div {}
[ H.input { type: "hidden"
, name: "csrfmiddlewaretoken"
-- TODO hard-coded CSRF token
, value: "Wy52D2nor8kC1r1Y4GrsrSIxQ2eqW8UwkdiQQshMoRwobzU4uldknRUhP0j4WcEM"
}
, H.div {className: "form-group"}
[ H.p {} [H.text state.errorMessage]
, usernameInput username
]
, H.div {className: "form-group"}
[ passwordInput password
, H.div {className: "clearfix"} []
]
, H.div {className: "center"}
[ H.label {}
[ H.div {className: "checkbox"}
[ H.input { id: "terms-accept"
, type: "checkbox"
, value: ""
, className: "checkbox"
}
, H.text "I accept the terms of uses "
, H.a {href: "http://gitlab.iscpif.fr/humanities/tofu/tree/master"}
[ H.text " [ Read the terms of use ] "]
]
]
, H.button { id: "login-button"
, className: "btn btn-primary btn-rounded"
, type: "submit"
-- TODO
--, on: {click: \_ -> dispatch $ PostAuth}
, on: {click: onClick username password}
}
[H.text "Login"]
]
]
]
]
]
]
]
-- div [ className "modal fade myModal"
-- , role "dialog"
-- , _data {show : true}
-- ][ div [ className "modal-dialog"
-- , role "document"
-- ] [ div [ className "modal-content"]
-- [ div [ className "modal-header"]
-- [ h5 [ className "modal-title"
-- ]
-- [ text "CorpusView"
-- ]
-- , button [ _type "button"
-- , className "close"
-- , _data { dismiss : "modal"}
-- ] [ span [ aria {hidden : true}]
-- [ text "X"]
-- ]
-- ]
-- , div [ className "modal-body"]
-- [ ul [ className "list-group"] ( map fn1 state.authData ) ]
-- , div [className "modal-footer"]
-- [ button [ _type "button"
-- , className "btn btn-secondary"
-- , _data {dismiss : "modal"}
-- ] [ text "GO"]
-- ]
-- ]
-- ]
-- ]
-- ]
gargLogo =
H.div {className: "col-md-10 col-md-push-1"}
[ H.h2 {className: "text-primary center m-a-2"}
[ H.i {className: "material-icons md-36"}
[H.text "control_point"]
, H.span {className: "icon-text"}
[H.text "Gargantext"]
]
]
usernameInput (username /\ setUsername) =
H.input { className: "form-control"
, id: "id_username"
, maxLength: "254"
, name: "username"
, placeholder: "username"
, type: "text"
, defaultValue: username
--, on: {input: \e -> dispatch (SetUserName $ R2.unsafeEventValue e)}
, on: {change: \e -> setUsername $ const $ R2.unsafeEventValue e}
}
passwordInput (password /\ setPassword) =
H.input { className: "form-control"
, id: "id_password"
, name: "password"
, placeholder: "password"
, type: "password"
, defaultValue: password
--, on: {input: \e -> dispatch (SetPassword $ R2.unsafeEventValue e)}
, on: {change: \e -> setPassword $ const $ R2.unsafeEventValue e}
}
onClick (username /\ _) (password /\ _) = \e -> do
setState $ \st -> st {username = username, password = password}
getAuthData :: Effect (Maybe AuthData)
......
module Gargantext.Components.Login.Types where
import Prelude
import Data.Lens (Iso', iso)
import Data.Argonaut ( class DecodeJson, class EncodeJson, decodeJson, jsonEmptyObject
, (.?), (.??), (:=), (~>)
)
, (.?), (.??), (:=), (~>)
)
import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Eq (genericEq)
import Data.Lens (Iso', iso)
import Data.Maybe (Maybe)
type Username = String
......@@ -30,6 +32,12 @@ newtype AuthData = AuthData
, tree_id :: TreeId
}
derive instance genericAuthData :: Generic AuthData _
instance eqAuthData :: Eq AuthData where
eq = genericEq
_AuthData :: Iso' AuthData { token :: Token, tree_id :: TreeId }
_AuthData = iso (\(AuthData v) -> v) AuthData
......
......@@ -20,7 +20,6 @@ import Gargantext.Types (class ToQuery)
import Gargantext.Config (End(..), NodeType(..), Path(..), toUrl)
import Gargantext.Config.REST (post, put)
import Gargantext.Components.Modals.Modal (modalHide)
import Gargantext.Pages.Layout.Specs.AddCorpus.States (Response, State)
import Gargantext.Utils (id)
import URI.Extra.QueryPairs as QP
......
......@@ -221,10 +221,8 @@ pathUrl c (Chart {chartType, tabType}) i =
routesPath :: R.Routes -> String
routesPath R.Home = ""
routesPath R.Login = "login"
routesPath R.SearchView = "search"
routesPath (R.Folder i) = "folder/" <> show i
routesPath (R.Corpus i) = "corpus/" <> show i
routesPath R.AddCorpus = "addCorpus"
routesPath (R.CorpusDocument c l i) = "corpus/" <> show c <> "/list/" <> show l <> "/document/" <> show i
routesPath (R.Document l i) = "list/" <> show l <> "/document/" <> show i
routesPath (R.PGraphExplorer i) = "#/"
......
......@@ -10,14 +10,15 @@ import Gargantext.Components.Lang.Landing.EnUS as En
import Gargantext.Components.Lang.Landing.FrFR as Fr
import Gargantext.Components.Data.Landing (BlockText(..), BlockTexts(..), Button(..), LandingData(..))
import Gargantext.Components.Data.Lang (Lang(..))
import Gargantext.Pages.Home.States (State, initialState)
import Gargantext.Pages.Home.Actions (Action, performAction)
import Reactix as R
import Reactix.DOM.HTML as H
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, height, width)
import Thermite (Render, Spec, simpleSpec, hideState, focusState)
import React.DOM.Props (Props)
import Thermite (Spec, hideState, focusState, Render, simpleSpec)
import Gargantext.Utils.Reactix as R2
-- Layout |
......@@ -26,80 +27,82 @@ landingData FR = Fr.landingData
landingData EN = En.landingData
layoutLanding :: Lang -> Spec {} {} Void
layoutLanding = hideState (const $ unwrap initialState)
<<< focusState (re _Newtype)
<<< layoutLanding' <<< landingData
layoutLanding = layoutLanding' <<< landingData
------------------------------------------------------------------------
layoutLanding' :: LandingData -> Spec State {} Action
layoutLanding' hd = simpleSpec performAction render
layoutLanding' :: LandingData -> Spec {} {} Void
layoutLanding' hd = R2.elSpec $ R.hooksComponent "LayoutLanding" cpt
where
render :: Render State {} Action
render dispatch _ state _ =
[ div [ className "container1" ] [ jumboTitle hd false ]
, div [ className "container1" ] [] -- TODO put research form
, div [ className "container1" ] [ blocksRandomText' hd ]
]
cpt {} _children = do
pure $ H.span {} [
H.div { className: "container1" }
[ jumboTitle hd false ]
, H.div { className: "container1" } [] -- TODO put research form
, H.div { className: "container1" } [ blocksRandomText' hd ]
]
------------------------------------------------------------------------
blocksRandomText' :: LandingData -> ReactElement
blocksRandomText' :: LandingData -> R.Element
blocksRandomText' (LandingData hd) = blocksRandomText hd.blockTexts
blocksRandomText :: BlockTexts -> ReactElement
blocksRandomText :: BlockTexts -> R.Element
blocksRandomText (BlockTexts bt) =
div [ className "row" ] ( map showBlock bt.blocks )
H.div { className: "row" } ( map showBlock bt.blocks )
where
showBlock :: BlockText -> ReactElement
showBlock :: BlockText -> R.Element
showBlock (BlockText b) =
div [ className "col-md-4 content" ]
[ h3 [] [ a [ href b.href, title b.title]
[ i [className b.icon] []
, text (" " <> b.titleText)
]
]
, p [] [ text b.text ]
, p [] [ docButton b.docButton ]
]
docButton :: Button -> ReactElement
docButton (Button b) = a [ className "btn btn-outline-primary btn-sm spacing-class"
, href b.href
, target "blank"
, title b.title
] [ span [ aria {hidden : true}
, className "glyphicon glyphicon-hand-right"
] []
, text b.text
]
jumboTitle :: LandingData -> Boolean -> ReactElement
jumboTitle (LandingData hd) b = div jumbo
[ div [className "row" ]
[ div [ className "col-md-12 content"]
[ div [ className "center" ]
[ div [_id "logo-designed" ]
[ img [ src "images/logo.png"
, title hd.logoTitle
]
]
]
]
]
]
where
jumbo = case b of
true -> [className "jumbotron"]
false -> []
imageEnter :: LandingData -> Props -> ReactElement
imageEnter (LandingData hd) action = div [className "row"]
[ div [className "col-md-offset-5 col-md-6 content"]
[ img [ src "images/Gargantextuel-212x300.jpg"
, _id "funnyimg"
, title hd.imageTitle
, action
]
]
]
H.div { className: "col-md-4 content" }
[ H.h3 {} [ H.a { href: b.href, title: b.title}
[ H.i {className: b.icon} []
, H.text (" " <> b.titleText)
]
]
, H.p {} [ H.text b.text ]
, H.p {} [ docButton b.docButton ]
]
docButton :: Button -> R.Element
docButton (Button b) =
H.a { className: "btn btn-outline-primary btn-sm spacing-class"
, href: b.href
, target: "blank"
, title: b.title
} [ H.span { aria: {hidden : true}
, className: "glyphicon glyphicon-hand-right"
} []
, H.text b.text
]
jumboTitle :: LandingData -> Boolean -> R.Element
jumboTitle (LandingData hd) b =
H.div {className: jumbo}
[ H.div { className: "row" }
[ H.div { className: "col-md-12 content" }
[ H.div { className: "center" }
[ H.div { id: "logo-designed" }
[ H.img { src: "images/logo.png"
, title: hd.logoTitle
}
]
]
]
]
]
where
jumbo = case b of
true -> "jumbotron"
false -> ""
imageEnter :: LandingData -> Props -> R.Element
imageEnter (LandingData hd) action =
H.div {className: "row"}
[ H.div {className: "col-md-offset-5 col-md-6 content"}
[ H.img { src: "images/Gargantextuel-212x300.jpg"
, id: "funnyimg"
, title: hd.imageTitle
, action
}
]
]
......@@ -3,7 +3,6 @@ module Gargantext.Pages.Layout where
import Prelude hiding (div)
-- import Gargantext.Components.Login as LN
import Gargantext.Pages.Layout.Actions (Action(..))
import Gargantext.Pages.Layout.Specs.AddCorpus as AC
-- import Gargantext.Pages.Corpus.Tabs as TV
import Gargantext.Pages.Corpus.Graph as GE
......@@ -24,17 +23,9 @@ dispatchAction dispatcher _ Login = do
dispatcher $ SetRoute Login
-- dispatcher $ LoginA TODO
dispatchAction dispatcher _ AddCorpus = do
dispatcher $ SetRoute AddCorpus
dispatcher $ AddCorpusA AC.LoadDatabaseDetails
dispatchAction dispatcher _ (Corpus n) = do
dispatcher $ SetRoute $ Corpus n
dispatchAction dispatcher _ SearchView = do
dispatcher $ SetRoute SearchView
-- dispatcher $ SearchA TODO
dispatchAction dispatcher _ (UserPage id) = do
dispatcher $ SetRoute $ UserPage id
......
......@@ -13,8 +13,6 @@ import Gargantext.Components.Login as LN
import Gargantext.Components.Modals.Modal (modalShow)
import Gargantext.Pages.Annuaire as Annuaire
import Gargantext.Pages.Corpus.Graph as GE
import Gargantext.Pages.Layout.Specs.AddCorpus as AC
import Gargantext.Pages.Layout.Specs.Search as S
import Gargantext.Pages.Layout.States (AppState)
import Gargantext.Prelude
import Gargantext.Router (Routes)
......@@ -24,8 +22,6 @@ import Gargantext.Router (Routes)
data Action
= LoginA LN.Action
| SetRoute Routes
| SearchA S.Action
| AddCorpusA AC.Action
| GraphExplorerA GE.Action
| AnnuaireAction Annuaire.Action
| ShowLogin
......@@ -61,8 +57,6 @@ performAction ShowAddCorpus _ _ = void do
---------------------------------------------------------
performAction (LoginA _) _ _ = pure unit
performAction (AddCorpusA _) _ _ = pure unit
performAction (SearchA _) _ _ = pure unit
performAction (GraphExplorerA _) _ _ = pure unit
performAction (AnnuaireAction _) _ _ = pure unit
-- liftEffect $ modalShow "addCorpus"
......@@ -76,18 +70,6 @@ _loginAction = prism LoginA \action ->
LoginA caction -> Right caction
_-> Left action
_addCorpusAction :: Prism' Action AC.Action
_addCorpusAction = prism AddCorpusA \action ->
case action of
AddCorpusA caction -> Right caction
_-> Left action
_searchAction :: Prism' Action S.Action
_searchAction = prism SearchA \action ->
case action of
SearchA caction -> Right caction
_-> Left action
_annuaireAction :: Prism' Action Annuaire.Action
_annuaireAction = prism AnnuaireAction \action ->
case action of
......
......@@ -4,12 +4,11 @@ import Data.Foldable (fold, intercalate)
import Data.Lens (over)
import Data.Maybe (Maybe(Nothing, Just))
import Effect (Effect)
import React (ReactElement)
import React.DOM (button, div, text)
import React.DOM.Props (_id, className, onClick, role, style)
import Reactix as R
import Reactix.DOM.HTML as H
import Thermite (Render, Spec, _render, defaultPerformAction, defaultRender, focus, simpleSpec, withState, noState, cmapProps)
import Thermite (Spec, _render, defaultPerformAction, defaultRender, focus, simpleSpec, withState, noState, cmapProps)
-- import Unsafe.Coerce (unsafeCoerce)
import Gargantext.Prelude
......@@ -27,11 +26,9 @@ import Gargantext.Pages.Corpus.Graph as GE
import Gargantext.Pages.Lists as Lists
import Gargantext.Pages.Texts as Texts
import Gargantext.Pages.Home as L
import Gargantext.Pages.Layout.Actions (Action(..), _addCorpusAction, _graphExplorerAction, _loginAction, _searchAction, performAction)
import Gargantext.Pages.Layout.Specs.AddCorpus as AC
import Gargantext.Pages.Layout.Specs.Search as S
import Gargantext.Pages.Layout.Actions (Action(..), _graphExplorerAction, _loginAction, performAction)
import Gargantext.Pages.Layout.Specs.SearchBar as SB
import Gargantext.Pages.Layout.States (AppState, _addCorpusState, _graphExplorerState, _loginState, _searchState)
import Gargantext.Pages.Layout.States (AppState, _graphExplorerState, _loginState)
import Gargantext.Router (Routes(..))
import Gargantext.Utils.Reactix as R2
......@@ -42,7 +39,6 @@ layoutSpec =
, container $ withState pagesComponent
, withState \st ->
fold [ focus _loginState _loginAction (LN.modalSpec st.showLogin "Login" LN.renderSpec)
, focus _addCorpusState _addCorpusAction (AC.modalSpec st.showCorpus "Search Results" AC.layoutAddcorpus)
]
]
where
......@@ -57,13 +53,11 @@ pagesComponent s = case s.currentRoute of
Nothing -> selectSpec Home -- TODO add Error page here: url requested does not exist (with funny Garg image)
where
selectSpec :: Routes -> Spec AppState {} Action
selectSpec Home = layout0 $ noState (L.layoutLanding EN)
selectSpec Home = layout0 $ noState $ L.layoutLanding EN
selectSpec Login = focus _loginState _loginAction LN.renderSpec
selectSpec (Folder i) = layout0 $ noState F.layoutFolder
selectSpec (Corpus i) = layout0 $ cmapProps (const {nodeId: i}) $ noState Corpus.layout
selectSpec AddCorpus = layout0 $ focus _addCorpusState _addCorpusAction AC.layoutAddcorpus
selectSpec SearchView = layout0 $ focus _searchState _searchAction S.searchSpec
selectSpec (CorpusDocument c l i) = layout0 $ cmapProps (const {nodeId: i, listId: l, corpusId: Just c}) $ noState Annotation.layout
selectSpec (Document l i) = layout0 $ cmapProps (const {nodeId: i, listId: l, corpusId: Nothing}) $ noState Annotation.layout
selectSpec (PGraphExplorer i)= layout1 $ focus _graphExplorerState _graphExplorerAction GE.specOld
......
module Gargantext.Pages.Layout.Specs.AddCorpus
( module Gargantext.Pages.Layout.Specs.AddCorpus.States
, module Gargantext.Pages.Layout.Specs.AddCorpus.Actions
, module Gargantext.Pages.Layout.Specs.AddCorpus.Specs
) where
import Gargantext.Pages.Layout.Specs.AddCorpus.States
import Gargantext.Pages.Layout.Specs.AddCorpus.Actions
import Gargantext.Pages.Layout.Specs.AddCorpus.Specs
module Gargantext.Pages.Layout.Specs.AddCorpus.Actions where
import Control.Monad.Cont.Trans (lift)
import Data.Argonaut (class EncodeJson, jsonEmptyObject, (:=), (~>))
import Effect.Aff (Aff)
import Effect.Class (liftEffect)
import Routing.Hash (setHash)
import Thermite (PerformAction, modifyState)
import Gargantext.Prelude
import Gargantext.Config.REST (post)
import Gargantext.Components.Modals.Modal (modalHide)
import Gargantext.Pages.Layout.Specs.AddCorpus.States (Response, State)
data Action
= SelectDatabase Boolean
| UnselectDatabase Boolean
| LoadDatabaseDetails
| GO
performAction :: PerformAction State {} Action
performAction (SelectDatabase selected) _ _ = void do
modifyState $ _ { select_database = selected }
performAction (UnselectDatabase unselected) _ _ = void do
modifyState $ _ { unselect_database = unselected }
performAction (LoadDatabaseDetails) _ _ = do
res <- lift $ getDatabaseDetails $ QueryString { query_query: "string",query_name: ["Pubmed"]}
void $ modifyState $ _ {response = res}
performAction GO _ _ = do
liftEffect $ setHash "/corpus"
liftEffect $ modalHide "addCorpus"
pure unit
newtype QueryString = QueryString
{
query_query :: String
, query_name :: Array String
}
queryString :: QueryString
queryString = QueryString
{
query_query: "string",
query_name: [
"Pubmed"
]
}
instance encodeJsonQueryString :: EncodeJson QueryString where
encodeJson (QueryString obj) =
"query_query" := obj.query_query
~> "query_name" := obj.query_name
~> jsonEmptyObject
getDatabaseDetails :: QueryString -> Aff (Array Response)
getDatabaseDetails reqBody = do
-- TODO let token = "eyJ0eXAiOiJKV1QiLCJhbGciOiJIUzI1NiJ9.eyJleHAiOjE1MTk5OTg1ODMsInVzZXJfaWQiOjUsImVtYWlsIjoiYWxleGFuZHJlLmRlbGFub2VAaXNjcGlmLmZyIiwidXNlcm5hbWUiOiJkZXZlbG9wZXIifQ.Os-3wuFNSmRIxCZi98oFNBu2zqGc0McO-dgDayozHJg"
post "http://localhost:8009/count" reqBody
module Gargantext.Pages.Layout.Specs.AddCorpus.Specs where
import Data.Lens (over)
import Effect.Aff (Aff)
import React (ReactElement)
import React.DOM (button, div, h3, h5, li, span, text, ul)
import React.DOM.Props (_data, _id, _type, aria, className, onClick, role)
import Thermite (Render, Spec, _render, simpleSpec)
import Gargantext.Prelude
import Gargantext.Config.REST (post)
import Gargantext.Pages.Layout.Specs.AddCorpus.Actions (Action(..), performAction)
import Gargantext.Pages.Layout.Specs.AddCorpus.States (Query, Response(..), State)
modalSpec :: Boolean -> String -> Spec State {} Action -> Spec State {} Action
modalSpec sm t = over _render \render d p s c ->
[ div [ _id "addCorpus", className $ "modal myModal" <> if sm then "" else " fade"
, role "dialog"
, _data {show : true}
][ div [ className "modal-dialog", role "document"]
[ div [ className "modal-content"]
[ div [ className "modal-header"]
[ h5 [ className "modal-title" ] [ text $ t ]
, button [ _type "button"
, className "close"
, _data { dismiss : "modal"}
] [ span [ aria {hidden : true}] [ text "X"] ]
]
, div [ className "modal-body"] (render d p s c)
]
]
]
]
spec' :: Spec State {} Action
spec' = modalSpec true "Search Results" layoutAddcorpus
layoutModal :: forall e. { response :: Array Response | e} -> Array ReactElement
layoutModal state =
[button [ _type "button"
, _data { "toggle" : "modal"
, "target" : ".myModal"
}
][text "Launch modal"]
, div [ className "modal fade myModal"
, role "dialog"
, _data {show : true}
][ div [ className "modal-dialog"
, role "document"
] [ div [ className "modal-content"]
[ div [ className "modal-header"]
[ h5 [className "modal-title"]
[text "CorpusView" ]
, button [ _type "button"
, className "close"
, _data { dismiss : "modal"}
] [ span [ aria {hidden : true}]
[ text "X"]
]
]
, div [ className "modal-body"]
[ ul [ className "list-group"] ( map fn1 state.response ) ]
, div [className "modal-footer"]
[ button [ _type "button"
, className "btn btn-secondary"
, _data {dismiss : "modal"}
] [ text "GO"]
]
]
]
]
]
where
fn1 (Response o) =
li [className "list-group-item justify-content-between"]
[
span [] [text o.name]
, span [className "badge badge-default badge-pill"] [ text $ show o.count]
]
layoutAddcorpus :: Spec State {} Action
layoutAddcorpus = simpleSpec performAction render
where
render :: Render State {} Action
render dispatch _ state _ =
[ div [className "container1"] []
, div [className "container1"]
[ div [className "jumbotron"]
[ div [className "row"]
[ div [className "col-md-6"] (layoutModal state)
, div [className "col-md-6"]
[ h3 [] [text "Corpusview"]
, ul [className "list-group"] $ map fn1 state.response
, button [onClick \_ -> dispatch GO] [text "GO"]
]
]
]
]
]
where
fn1 (Response o) =
li [className "list-group-item justify-content-between"]
[
span [] [text o.name]
, span [className "badge badge-default badge-pill"] [ text $ show o.count]
]
countResults :: Query -> Aff Int
countResults = post "http://localhost:8008/count"
module Gargantext.Pages.Layout.Specs.AddCorpus.States where
import Prelude hiding (div)
import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, encodeJson, jsonEmptyObject, (.?), (:=), (~>))
type State =
{ select_database :: Boolean
, unselect_database :: Boolean -- dummy state
, response :: Array Response
}
newtype Response = Response
{
count :: Int
, 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
decodeJson json = do
obj <- decodeJson json
count <- obj .? "count"
name <- obj .? "name"
pure $ Response {count,name }
initialState :: State
initialState =
{
select_database : true
, unselect_database : true
, response : []
}
module Gargantext.Pages.Layout.Specs.Search where
import Prelude hiding (div)
import Effect.Class (liftEffect)
import React.DOM (br', button, div, input, text)
import React.DOM.Props (_id, _type, className, name, onClick, onInput, placeholder, value)
import Routing.Hash (setHash)
import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec)
import Gargantext.Utils.Reactix as R2
type State =
{
query :: String
}
initialState :: State
initialState =
{
query : "empty query"
}
data Action
= GO
| SetQuery String
performAction :: PerformAction State {} Action
performAction (SetQuery q) _ _ = void do
modifyState $ _ { query = q }
performAction GO _ _ = void do
liftEffect $ setHash "/addCorpus"
searchSpec :: Spec State {} Action
searchSpec = simpleSpec performAction render
where
render :: Render State {} Action
render dispatch _ state _ =
[ div [className "container1"] []
, div [className "container1"]
[ div [className "jumbotron" ]
[ div [className "row" ]
[ div [className "col-md-10" ]
[ br'
, br'
, div [ className "form-group"][]
{-[ input [ className "form-control"
, _id "id_password"
, name "query"
, placeholder "Query, URL or FILE (works best with Firefox or Chromium browsers)"
, _type "text"
, value state.query
, onInput \e -> dispatch (SetQuery (R2.unsafeEventValue e))
]
, br'
]
-}
]
, div [ className "col-md-2"]
[ br'
, br'
, button [onClick \_ -> dispatch GO] [text "GO"]
]
, br'
]
]
]
]
......@@ -8,15 +8,11 @@ import Effect (Effect)
import Gargantext.Components.Login as LN
import Gargantext.Pages.Corpus.Graph as GE
import Gargantext.Pages.Layout.Specs.AddCorpus as AC
import Gargantext.Pages.Layout.Specs.Search as S
import Gargantext.Router (Routes(..))
type AppState =
{ currentRoute :: Maybe Routes
, loginState :: LN.State
, addCorpusState :: AC.State
, searchState :: S.State
, showLogin :: Boolean
, showCorpus :: Boolean
, graphExplorerState :: GE.State
......@@ -29,8 +25,6 @@ initAppState = do
pure
{ currentRoute : Just Home
, loginState
, addCorpusState : AC.initialState
, searchState : S.initialState
, showLogin : false
, showCorpus : false
, graphExplorerState : GE.initialState
......@@ -43,12 +37,6 @@ initAppState = do
_loginState :: Lens' AppState LN.State
_loginState = lens (\s -> s.loginState) (\s ss -> s{loginState = ss})
_addCorpusState :: Lens' AppState AC.State
_addCorpusState = lens (\s -> s.addCorpusState) (\s ss -> s{addCorpusState = ss})
_searchState :: Lens' AppState S.State
_searchState = lens (\s -> s.searchState) (\s ss -> s{searchState = ss})
_graphExplorerState :: Lens' AppState GE.State
_graphExplorerState = lens (\s -> s.graphExplorerState) (\s ss -> s{graphExplorerState = ss})
......@@ -16,10 +16,8 @@ import Web.Storage.Storage (getItem)
data Routes
= Home
| Login
| SearchView
| Folder Int
| Corpus Int
| AddCorpus
| Document Int Int
| CorpusDocument Int Int Int
| PGraphExplorer Int
......@@ -33,8 +31,6 @@ data Routes
routing :: Match Routes
routing = oneOf
[ Login <$ route "login"
, SearchView <$ route "search"
, AddCorpus <$ route "addCorpus"
, Folder <$> (route "folder" *> int)
, CorpusDocument <$> (route "corpus" *> int) <*> (lit "list" *> int) <*> (lit "document" *> int)
, Corpus <$> (route "corpus" *> int)
......@@ -57,8 +53,6 @@ routing = oneOf
instance showRoutes :: Show Routes where
show Login = "Login"
show AddCorpus = "AddCorpus"
show SearchView = "Search"
show (UserPage i) = "User" <> show i
show (ContactPage i) = "Contact" <> show i
show (CorpusDocument _ _ i) = "Document" <> show i
......
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