Commit fafd5a21 authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

Merge branch 'dev-search-removal' into dev-backend-connection

parents d179d061 a00f9694
...@@ -10,7 +10,6 @@ import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, encodeJson ...@@ -10,7 +10,6 @@ import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, encodeJson
import Data.Array (drop, take, (:), filter) import Data.Array (drop, take, (:), 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.Eq (genericEq)
import Data.Generic.Rep.Show (genericShow) import Data.Generic.Rep.Show (genericShow)
import Data.HTTP.Method (Method(..)) import Data.HTTP.Method (Method(..))
import Data.Lens import Data.Lens
...@@ -22,15 +21,17 @@ import Data.Set (Set) ...@@ -22,15 +21,17 @@ import Data.Set (Set)
import Data.Set as Set import Data.Set as Set
import Data.Int (fromString) import Data.Int (fromString)
import Data.Symbol (SProxy(..)) import Data.Symbol (SProxy(..))
import Data.Tuple (Tuple(..)) import Data.Tuple (Tuple(..), fst)
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import DOM.Simple.Event as DE
import Effect (Effect) import Effect (Effect)
import Effect.Aff (Aff, launchAff) import Effect.Aff (Aff, launchAff)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
import Effect.Uncurried (mkEffectFn1) import Effect.Uncurried (EffectFn1, mkEffectFn1)
import React as React import React as React
import React (ReactClass, ReactElement, Children) import React (ReactClass, ReactElement, Children)
import Reactix as R import Reactix as R
import Reactix.SyntheticEvent as RE
import Reactix.DOM.HTML as H import Reactix.DOM.HTML as H
import Unsafe.Coerce (unsafeCoerce) import Unsafe.Coerce (unsafeCoerce)
------------------------------------------------------------------------ ------------------------------------------------------------------------
...@@ -39,6 +40,7 @@ import Gargantext.Config (End(..), NodeType(..), OrderBy(..), Path(..), TabType, ...@@ -39,6 +40,7 @@ import Gargantext.Config (End(..), NodeType(..), OrderBy(..), Path(..), TabType,
import Gargantext.Config.REST (get, put, post, deleteWithBody, delete) import Gargantext.Config.REST (get, put, post, deleteWithBody, delete)
import Gargantext.Components.Loader2 (useLoader) import Gargantext.Components.Loader2 (useLoader)
import Gargantext.Components.Node (NodePoly(..)) import Gargantext.Components.Node (NodePoly(..))
import Gargantext.Components.Search.Types (Category(..), CategoryQuery(..), favCategory, trashCategory, decodeCategory, putCategories)
import Gargantext.Components.Table as T import Gargantext.Components.Table as T
import Gargantext.Utils.DecodeMaybe ((.|)) import Gargantext.Utils.DecodeMaybe ((.|))
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
...@@ -48,26 +50,6 @@ import Thermite (PerformAction, Render, Spec, defaultPerformAction, modifyState_ ...@@ -48,26 +50,6 @@ import Thermite (PerformAction, Render, Spec, defaultPerformAction, modifyState_
type NodeID = Int type NodeID = Int
type TotalRecords = Int type TotalRecords = Int
data Category = Trash | Normal | Favorite
derive instance genericFavorite :: Generic Category _
instance showCategory :: Show Category where
show = genericShow
instance eqCategory :: Eq Category where
eq = genericEq
instance encodeJsonCategory :: EncodeJson Category where
encodeJson Trash = encodeJson 0
encodeJson Normal = encodeJson 1
encodeJson Favorite = encodeJson 2
favCategory :: Category -> Category
favCategory Normal = Favorite
favCategory Trash = Favorite
favCategory Favorite = Normal
trashCategory :: Category -> Category
trashCategory Normal = Trash
trashCategory Trash = Normal
trashCategory Favorite = Trash
type Props = type Props =
{ nodeId :: Int { nodeId :: Int
...@@ -76,6 +58,7 @@ type Props = ...@@ -76,6 +58,7 @@ type Props =
, tabType :: TabType , tabType :: TabType
, listId :: Int , listId :: Int
, corpusId :: Maybe Int , corpusId :: Maybe Int
, showSearch :: Boolean
-- ^ tabType is not ideal here since it is too much entangled with tabs and -- ^ tabType is not ideal here since it is too much entangled with tabs and
-- ngramtable. Let's see how this evolves. -- ngramtable. Let's see how this evolves.
} }
...@@ -89,7 +72,6 @@ type PageLoaderProps = ...@@ -89,7 +72,6 @@ type PageLoaderProps =
, query :: Query , query :: Query
} }
type DocumentIdsDeleted = Set Int
type LocalCategories = Map Int Category type LocalCategories = Map Int Category
type Query = String type Query = String
...@@ -141,12 +123,6 @@ instance decodeHyperdata :: DecodeJson Hyperdata where ...@@ -141,12 +123,6 @@ instance decodeHyperdata :: DecodeJson Hyperdata where
pub_year <- obj .? "publication_year" pub_year <- obj .? "publication_year"
pure $ Hyperdata { title,source, pub_year} pure $ Hyperdata { title,source, pub_year}
decodeCategory :: Int -> Category
decodeCategory 0 = Trash
decodeCategory 1 = Normal
decodeCategory 2 = Favorite
decodeCategory _ = Normal
instance decodeResponse :: DecodeJson Response where instance decodeResponse :: DecodeJson Response where
decodeJson json = do decodeJson json = do
obj <- decodeJson json obj <- decodeJson json
...@@ -162,30 +138,23 @@ docViewSpec p = R.createElement el p [] ...@@ -162,30 +138,23 @@ docViewSpec p = R.createElement el p []
where where
el = R.hooksComponent "DocView" cpt el = R.hooksComponent "DocView" cpt
cpt p _children = do cpt p _children = do
documentIdsDeleted <- R.useState' (mempty :: DocumentIdsDeleted)
localCategories <- R.useState' (mempty :: LocalCategories)
query <- R.useState' ("" :: Query) query <- R.useState' ("" :: Query)
tableParams <- R.useState' T.initialParams tableParams <- R.useState' T.initialParams
pure $ layoutDocview documentIdsDeleted localCategories query tableParams p pure $ layoutDocview query tableParams p
-- | Main layout of the Documents Tab of a Corpus -- | Main layout of the Documents Tab of a Corpus
layoutDocview :: R.State DocumentIdsDeleted -> R.State LocalCategories -> R.State Query -> R.State T.Params -> Props -> R.Element layoutDocview :: R.State Query -> R.State T.Params -> Props -> R.Element
layoutDocview documentIdsDeleted@(_ /\ setDocumentIdsDeleted) localCategories (query /\ setQuery) tableParams@(params /\ _) p = R.createElement el p [] layoutDocview query tableParams@(params /\ _) p = R.createElement el p []
where where
el = R.hooksComponent "LayoutDocView" cpt el = R.hooksComponent "LayoutDocView" cpt
cpt {nodeId, tabType, listId, corpusId, totalRecords, chart} _children = do cpt {nodeId, tabType, listId, corpusId, totalRecords, chart, showSearch} _children = do
pure $ H.div {className: "container1"} pure $ H.div {className: "container1"}
[ H.div {className: "row"} [ H.div {className: "row"}
[ chart [ chart
, H.div {} , if showSearch then searchBar query else H.div {} []
[ H.input { type: "text"
, onChange: onChangeQuery
, placeholder: query}
]
, H.div {className: "col-md-12"} , H.div {className: "col-md-12"}
[ pageLoader localCategories tableParams {nodeId, totalRecords, tabType, listId, corpusId, query} [ pageLoader tableParams {nodeId, totalRecords, tabType, listId, corpusId, query: fst query} ]
]
, H.div {className: "col-md-1 col-md-offset-11"} , H.div {className: "col-md-1 col-md-offset-11"}
[ H.button { className: "btn" [ H.button { className: "btn"
, style: {backgroundColor: "peru", color : "white", border : "white"} , style: {backgroundColor: "peru", color : "white", border : "white"}
...@@ -197,12 +166,52 @@ layoutDocview documentIdsDeleted@(_ /\ setDocumentIdsDeleted) localCategories (q ...@@ -197,12 +166,52 @@ layoutDocview documentIdsDeleted@(_ /\ setDocumentIdsDeleted) localCategories (q
] ]
] ]
] ]
onChangeQuery = mkEffectFn1 $ \e -> do
setQuery $ const $ unsafeEventValue e
onClickTrashAll nodeId = mkEffectFn1 $ \_ -> do onClickTrashAll nodeId = mkEffectFn1 $ \_ -> do
launchAff $ deleteAllDocuments nodeId launchAff $ deleteAllDocuments nodeId
-- TODO
-- setDocumentIdsDeleted $ \dids -> Set.union dids (Set.fromFoldable ids) searchBar :: R.State Query -> R.Element
searchBar (query /\ setQuery) = R.createElement el {} []
where
el = R.hooksComponent "SearchBar" cpt
cpt {} _children = do
queryText <- R.useState' query
pure $ H.div {className: "row"}
[ H.div {className: "col col-md-3 form-group"}
[ H.input { type: "text"
, className: "form-control"
, on: {change: onSearchChange queryText, keyUp: onSearchKeyup queryText}
, placeholder: query
, defaultValue: query}
]
, H.div {className: "col col-md-1"}
[ searchButton queryText
, if query /= "" then clearButton else H.div {} []
]
]
onSearchChange :: forall e. R.State Query -> e -> Effect Unit
onSearchChange (_ /\ setQueryText) = \e ->
setQueryText $ const $ R2.unsafeEventValue e
onSearchKeyup :: R.State Query -> DE.KeyboardEvent -> Effect Unit
onSearchKeyup (queryText /\ _) = \e ->
if DE.key e == "Enter" then
setQuery $ const queryText
else
pure $ unit
searchButton (queryText /\ _) =
H.button { type: "submit"
, className: "btn btn-default"
, on: {click: \e -> setQuery $ const queryText}}
[ H.span {className: "glyphicon glyphicon-search"} [] ]
clearButton =
H.button { className: "btn btn-danger"
, on: {click: \e -> setQuery $ const ""}}
[ H.span {className: "glyphicon glyphicon-remove"} [] ]
mock :: Boolean mock :: Boolean
mock = false mock = false
...@@ -250,8 +259,8 @@ loadPage {nodeId, tabType, query, listId, corpusId, params: {limit, offset, orde ...@@ -250,8 +259,8 @@ loadPage {nodeId, tabType, query, listId, corpusId, params: {limit, offset, orde
convOrderBy _ = DateAsc -- TODO convOrderBy _ = DateAsc -- TODO
renderPage :: R.State LocalCategories -> R.State T.Params -> PageLoaderProps -> Array DocumentsView -> R.Element renderPage :: R.State T.Params -> PageLoaderProps -> Array DocumentsView -> R.Element
renderPage (localCategories /\ setLocalCategories) (_ /\ setTableParams) p res = R.createElement el p [] renderPage (_ /\ setTableParams) p res = R.createElement el p []
where where
el = R.hooksComponent "RenderPage" cpt el = R.hooksComponent "RenderPage" cpt
...@@ -259,13 +268,14 @@ renderPage (localCategories /\ setLocalCategories) (_ /\ setTableParams) p res = ...@@ -259,13 +268,14 @@ renderPage (localCategories /\ setLocalCategories) (_ /\ setTableParams) p res =
gi _ = "glyphicon glyphicon-star-empty" gi _ = "glyphicon glyphicon-star-empty"
trashStyle Trash = {textDecoration: "line-through"} trashStyle Trash = {textDecoration: "line-through"}
trashStyle _ = {textDecoration: "none"} trashStyle _ = {textDecoration: "none"}
getCategory {_id, category} = maybe category identity (localCategories ^. at _id)
corpusDocument (Just corpusId) = Router.CorpusDocument corpusId corpusDocument (Just corpusId) = Router.CorpusDocument corpusId
corpusDocument _ = Router.Document corpusDocument _ = Router.Document
cpt {nodeId, corpusId, listId} _children = do cpt {nodeId, corpusId, listId, totalRecords} _children = do
localCategories <- R.useState' (mempty :: LocalCategories)
pure $ R2.buff $ T.tableElt pure $ R2.buff $ T.tableElt
{ rows { rows: rows localCategories
-- , setParams: \params -> liftEffect $ loaderDispatch (Loader.SetPath {nodeId, tabType, listId, corpusId, params, query}) -- , setParams: \params -> liftEffect $ loaderDispatch (Loader.SetPath {nodeId, tabType, listId, corpusId, params, query})
, setParams: \params -> setTableParams $ const params , setParams: \params -> setTableParams $ const params
, container: T.defaultContainer { title: "Documents" } , container: T.defaultContainer { title: "Documents" }
...@@ -277,23 +287,23 @@ renderPage (localCategories /\ setLocalCategories) (_ /\ setTableParams) p res = ...@@ -277,23 +287,23 @@ renderPage (localCategories /\ setLocalCategories) (_ /\ setTableParams) p res =
, "Title" , "Title"
, "Source" , "Source"
] ]
-- , totalRecords , totalRecords
, totalRecords: 1000 -- TODO
} }
where where
rows = (\(DocumentsView r) -> getCategory (localCategories /\ _) {_id, category} = maybe category identity (localCategories ^. at _id)
let cat = getCategory r rows localCategories = (\(DocumentsView r) ->
let cat = getCategory localCategories r
isDel = Trash == cat in isDel = Trash == cat in
{ row: map R2.scuff $ [ { row: map R2.scuff $ [
H.div {} H.div {}
[ H.a { className: gi cat [ H.a { className: gi cat
, style: trashStyle cat , style: trashStyle cat
, onClick: onClick Favorite r._id cat , on: {click: onClick localCategories Favorite r._id cat}
} [] } []
] ]
, H.input { type: "checkbox" , H.input { type: "checkbox"
, checked: isDel , checked: isDel
, onClick: onClick Trash r._id cat , on: {click: onClick localCategories Trash r._id cat}
} }
-- TODO show date: Year-Month-Day only -- TODO show date: Year-Month-Day only
, H.div { style: trashStyle cat } [ H.text (show r.date) ] , H.div { style: trashStyle cat } [ H.text (show r.date) ]
...@@ -305,18 +315,18 @@ renderPage (localCategories /\ setLocalCategories) (_ /\ setTableParams) p res = ...@@ -305,18 +315,18 @@ renderPage (localCategories /\ setLocalCategories) (_ /\ setTableParams) p res =
] ]
, delete: true , delete: true
}) <$> res }) <$> res
onClick catType nid cat = mkEffectFn1 $ \_-> do onClick (_ /\ setLocalCategories) catType nid cat = \_-> do
let newCat = if (catType == Favorite) then (favCategory cat) else (trashCategory cat) let newCat = if (catType == Favorite) then (favCategory cat) else (trashCategory cat)
setLocalCategories $ insert nid newCat setLocalCategories $ insert nid newCat
void $ launchAff $ putCategories nodeId $ CategoryQuery {nodeIds: [nid], category: newCat} void $ launchAff $ putCategories nodeId $ CategoryQuery {nodeIds: [nid], category: newCat}
pageLoader :: R.State LocalCategories -> R.State T.Params -> PageLoaderProps -> R.Element pageLoader :: R.State T.Params -> PageLoaderProps -> R.Element
pageLoader localCategories tableParams@(pageParams /\ _) p = R.createElement el p [] pageLoader tableParams@(pageParams /\ _) p = R.createElement el p []
where where
el = R.hooksComponent "PageLoader" cpt el = R.hooksComponent "PageLoader" cpt
cpt p@{nodeId, listId, corpusId, tabType, query} _children = do cpt p@{nodeId, listId, corpusId, tabType, query} _children = do
useLoader {nodeId, listId, corpusId, tabType, query, params: pageParams} loadPage $ \{loaded} -> useLoader {nodeId, listId, corpusId, tabType, query, params: pageParams} loadPage $ \{loaded} ->
renderPage localCategories tableParams p loaded renderPage tableParams p loaded
--------------------------------------------------------- ---------------------------------------------------------
sampleData' :: DocumentsView sampleData' :: DocumentsView
...@@ -360,24 +370,6 @@ searchResults :: SearchQuery -> Aff Int ...@@ -360,24 +370,6 @@ searchResults :: SearchQuery -> Aff Int
searchResults squery = post "http://localhost:8008/count" unit searchResults squery = post "http://localhost:8008/count" unit
-- TODO -- TODO
newtype CategoryQuery = CategoryQuery {
nodeIds :: Array Int
, category :: Category
}
instance encodeJsonCategoryQuery :: EncodeJson CategoryQuery where
encodeJson (CategoryQuery post) =
"ntc_nodesId" := post.nodeIds
~> "ntc_category" := encodeJson post.category
~> jsonEmptyObject
categoryUrl :: Int -> String
categoryUrl nodeId = toUrl endConfigStateful Back Node (Just nodeId) <> "/category"
putCategories :: Int -> CategoryQuery -> Aff (Array Int)
putCategories nodeId = put $ categoryUrl nodeId
documentsUrl :: Int -> String documentsUrl :: Int -> String
documentsUrl nodeId = toUrl endConfigStateful Back Node (Just nodeId) <> "/documents" documentsUrl nodeId = toUrl endConfigStateful Back Node (Just nodeId) <> "/documents"
...@@ -389,6 +381,3 @@ toggleSet :: forall a. Ord a => a -> Set a -> Set a ...@@ -389,6 +381,3 @@ toggleSet :: forall a. Ord a => a -> Set a -> Set a
toggleSet a s toggleSet a s
| Set.member a s = Set.delete a s | Set.member a s = Set.delete a s
| otherwise = Set.insert a s | otherwise = Set.insert a s
unsafeEventValue :: forall event. event -> String
unsafeEventValue e = (unsafeCoerce e).target.value
...@@ -26,10 +26,12 @@ import React as React ...@@ -26,10 +26,12 @@ import React as React
import React (ReactClass, ReactElement, Children) import React (ReactClass, ReactElement, Children)
------------------------------------------------------------------------ ------------------------------------------------------------------------
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Config (End(..), NodeType(..), OrderBy(..), Path(..), TabType, toUrl, endConfigStateful) import Gargantext.Config (End(..), NodeType(..), OrderBy(..), Path(..), TabType, toUrl, toLink, endConfigStateful)
import Gargantext.Config.REST (put, post, deleteWithBody) import Gargantext.Config.REST (put, post, deleteWithBody)
import Gargantext.Components.Loader as Loader import Gargantext.Components.Loader as Loader
import Gargantext.Components.Search.Types (Category(..), CategoryQuery(..), favCategory, trashCategory, decodeCategory, putCategories)
import Gargantext.Components.Table as T import Gargantext.Components.Table as T
import Gargantext.Router as Router
import Gargantext.Utils (toggleSet) import Gargantext.Utils (toggleSet)
import Gargantext.Utils.DecodeMaybe ((.|)) import Gargantext.Utils.DecodeMaybe ((.|))
import React.DOM (a, br', button, div, i, input, p, text, span) import React.DOM (a, br', button, div, i, input, p, text, span)
...@@ -83,9 +85,9 @@ initialState = ...@@ -83,9 +85,9 @@ initialState =
} }
data Action data Action
= MarkFavorites (Array Int) = MarkCategory Category (Array Int)
| ToggleDocumentToDelete Int | ToggleDocumentToDelete Int
| Trash | TrashDocuments
newtype Pair = Pair newtype Pair = Pair
{ id :: Int { id :: Int
...@@ -106,9 +108,9 @@ newtype DocumentsView ...@@ -106,9 +108,9 @@ newtype DocumentsView
, score :: Int , score :: Int
, pairs :: Array Pair , pairs :: Array Pair
, delete :: Boolean , delete :: Boolean
, category :: Category
} }
derive instance genericDocumentsView :: Generic DocumentsView _ derive instance genericDocumentsView :: Generic DocumentsView _
instance showDocumentsView :: Show DocumentsView where instance showDocumentsView :: Show DocumentsView where
...@@ -118,7 +120,7 @@ newtype Response = Response ...@@ -118,7 +120,7 @@ newtype Response = Response
{ id :: Int { id :: Int
, created :: String , created :: String
, hyperdata :: Hyperdata , hyperdata :: Hyperdata
, favorite :: Boolean , category :: Category
, ngramCount :: Int , ngramCount :: Int
-- , date :: String -- , date :: String
-- , score :: Int -- , score :: Int
...@@ -174,7 +176,7 @@ instance decodeResponse :: DecodeJson Response where ...@@ -174,7 +176,7 @@ instance decodeResponse :: DecodeJson Response where
hyperdata <- obj .? "hyperdata" hyperdata <- obj .? "hyperdata"
favorite <- obj .? "favorite" favorite <- obj .? "favorite"
ngramCount <- obj .? "ngramCount" ngramCount <- obj .? "ngramCount"
pure $ Response { id, created, hyperdata, favorite, ngramCount } pure $ Response { id, created, hyperdata, category: decodeCategory favorite, ngramCount }
-- | Filter -- | Filter
-- TODO: unused -- TODO: unused
...@@ -194,12 +196,12 @@ layoutDocview :: Spec State Props Action ...@@ -194,12 +196,12 @@ layoutDocview :: Spec State Props Action
layoutDocview = simpleSpec performAction render layoutDocview = simpleSpec performAction render
where where
performAction :: PerformAction State Props Action performAction :: PerformAction State Props Action
performAction (MarkFavorites nids) {nodeId} _ = performAction (MarkCategory category nids) {nodeId} _ =
void $ lift $ putFavorites nodeId (FavoriteQuery {favorites: nids}) void $ lift $ putCategories nodeId $ CategoryQuery {nodeIds: nids, category: favCategory category}
--TODO add array of delete rows here --TODO add array of delete rows here
performAction (ToggleDocumentToDelete nid) _ _ = performAction (ToggleDocumentToDelete nid) _ _ =
modifyState_ \state -> state {documentIdsToDelete = toggleSet nid state.documentIdsToDelete} modifyState_ \state -> state {documentIdsToDelete = toggleSet nid state.documentIdsToDelete}
performAction Trash {nodeId} {documentIdsToDelete} = do performAction TrashDocuments {nodeId} {documentIdsToDelete} = do
void $ lift $ deleteDocuments nodeId (DeleteDocumentQuery {documents: Set.toUnfoldable documentIdsToDelete}) void $ lift $ deleteDocuments nodeId (DeleteDocumentQuery {documents: Set.toUnfoldable documentIdsToDelete})
modifyState_ \{documentIdsToDelete, documentIdsDeleted} -> modifyState_ \{documentIdsToDelete, documentIdsDeleted} ->
{ documentIdsToDelete: mempty { documentIdsToDelete: mempty
...@@ -229,7 +231,7 @@ layoutDocview = simpleSpec performAction render ...@@ -229,7 +231,7 @@ layoutDocview = simpleSpec performAction render
] ]
, div [className "col-md-12"] , div [className "col-md-12"]
[ button [ style {backgroundColor: "peru", padding : "9px", color : "white", border : "white", float: "right"} [ button [ style {backgroundColor: "peru", padding : "9px", color : "white", border : "white", float: "right"}
, onClick $ (\_ -> dispatch Trash) , onClick $ (\_ -> dispatch TrashDocuments)
] ]
[ i [className "glyphitem glyphicon glyphicon-trash", style {marginRight : "9px"}] [] [ i [className "glyphitem glyphicon glyphicon-trash", style {marginRight : "9px"}] []
, text "Trash it !" , text "Trash it !"
...@@ -245,12 +247,12 @@ layoutDocviewGraph :: Spec State Props Action ...@@ -245,12 +247,12 @@ layoutDocviewGraph :: Spec State Props Action
layoutDocviewGraph = simpleSpec performAction render layoutDocviewGraph = simpleSpec performAction render
where where
performAction :: PerformAction State Props Action performAction :: PerformAction State Props Action
performAction (MarkFavorites nids) {nodeId} _ = performAction (MarkCategory category nids) {nodeId} _ =
void $ lift $ putFavorites nodeId (FavoriteQuery {favorites: nids}) void $ lift $ putCategories nodeId $ CategoryQuery {nodeIds: nids, category: favCategory category}
--TODO add array of delete rows here --TODO add array of delete rows here
performAction (ToggleDocumentToDelete nid) _ _ = performAction (ToggleDocumentToDelete nid) _ _ =
modifyState_ \state -> state {documentIdsToDelete = toggleSet nid state.documentIdsToDelete} modifyState_ \state -> state {documentIdsToDelete = toggleSet nid state.documentIdsToDelete}
performAction Trash {nodeId} {documentIdsToDelete} = do performAction TrashDocuments {nodeId} {documentIdsToDelete} = do
void $ lift $ deleteDocuments nodeId (DeleteDocumentQuery {documents: Set.toUnfoldable documentIdsToDelete}) void $ lift $ deleteDocuments nodeId (DeleteDocumentQuery {documents: Set.toUnfoldable documentIdsToDelete})
modifyState_ \{documentIdsToDelete, documentIdsDeleted} -> modifyState_ \{documentIdsToDelete, documentIdsDeleted} ->
{ documentIdsToDelete: mempty { documentIdsToDelete: mempty
...@@ -275,7 +277,7 @@ layoutDocviewGraph = simpleSpec performAction render ...@@ -275,7 +277,7 @@ layoutDocviewGraph = simpleSpec performAction render
, container , container
} }
, button [ style {backgroundColor: "peru", padding : "9px", color : "white", border : "white", float: "right"} , button [ style {backgroundColor: "peru", padding : "9px", color : "white", border : "white", float: "right"}
, onClick $ (\_ -> dispatch Trash) , onClick $ (\_ -> dispatch TrashDocuments)
] ]
[ i [className "glyphitem glyphicon glyphicon-trash", style {marginRight : "9px"}] [] [ i [className "glyphitem glyphicon glyphicon-trash", style {marginRight : "9px"}] []
, text "Trash it !" , text "Trash it !"
...@@ -303,7 +305,7 @@ loadPage {nodeId, listId, query, params: {limit, offset, orderBy}} = do ...@@ -303,7 +305,7 @@ loadPage {nodeId, listId, query, params: {limit, offset, orderBy}} = do
res2corpus :: Response -> DocumentsView res2corpus :: Response -> DocumentsView
res2corpus (Response { id, created: date, ngramCount: score res2corpus (Response { id, created: date, ngramCount: score
, hyperdata: Hyperdata {title, source} , hyperdata: Hyperdata {title, source}
-- favorite TODO , category
}) = }) =
DocumentsView DocumentsView
{ id { id
...@@ -313,6 +315,7 @@ loadPage {nodeId, listId, query, params: {limit, offset, orderBy}} = do ...@@ -313,6 +315,7 @@ loadPage {nodeId, listId, query, params: {limit, offset, orderBy}} = do
, score , score
, pairs: [] , pairs: []
, delete: false , delete: false
, category
} }
convOrderBy (T.ASC (T.ColumnName "Date")) = DateAsc convOrderBy (T.ASC (T.ColumnName "Date")) = DateAsc
convOrderBy (T.DESC (T.ColumnName "Date")) = DateDesc convOrderBy (T.DESC (T.ColumnName "Date")) = DateDesc
...@@ -363,7 +366,7 @@ renderPage loaderDispatch { totalRecords, dispatch, container ...@@ -363,7 +366,7 @@ renderPage loaderDispatch { totalRecords, dispatch, container
] ]
where where
-- TODO: how to interprete other scores? -- TODO: how to interprete other scores?
gi 0 = "glyphicon glyphicon-star-empty" gi Favorite = "glyphicon glyphicon-star-empty"
gi _ = "glyphicon glyphicon-star" gi _ = "glyphicon glyphicon-star"
isChecked id = Set.member id documentIdsToDelete isChecked id = Set.member id documentIdsToDelete
isDeleted (DocumentsView {id}) = Set.member id documentIdsDeleted isDeleted (DocumentsView {id}) = Set.member id documentIdsDeleted
...@@ -371,7 +374,7 @@ renderPage loaderDispatch { totalRecords, dispatch, container ...@@ -371,7 +374,7 @@ renderPage loaderDispatch { totalRecords, dispatch, container
| id > 1 = [a [href (toUrl endConfigStateful Front NodeContact (Just id)), target "blank"] [text label]] | id > 1 = [a [href (toUrl endConfigStateful Front NodeContact (Just id)), target "blank"] [text label]]
| otherwise = [text label] | otherwise = [text label]
comma = span [] [text ", "] comma = span [] [text ", "]
rows = (\(DocumentsView {id,score,title,source,date,pairs,delete}) -> rows = (\(DocumentsView {id,score,title,source,date,pairs,delete,category}) ->
let let
strikeIfDeleted strikeIfDeleted
| delete = [style {textDecoration : "line-through"}] | delete = [style {textDecoration : "line-through"}]
...@@ -379,13 +382,13 @@ renderPage loaderDispatch { totalRecords, dispatch, container ...@@ -379,13 +382,13 @@ renderPage loaderDispatch { totalRecords, dispatch, container
in in
{ row: { row:
[ div [] [ div []
[ a [ className $ gi score [ a [ className $ gi category
, onClick $ const $ dispatch $ MarkFavorites [id] , onClick $ const $ dispatch $ MarkCategory category [id]
] [] ] []
] ]
-- TODO show date: Year-Month-Day only -- TODO show date: Year-Month-Day only
, div strikeIfDeleted [text date] , div strikeIfDeleted [text date]
, a (strikeIfDeleted <> [ href (toUrl endConfigStateful Front (ListDocument (Just listId)) (Just id)) , a (strikeIfDeleted <> [ href $ toLink $ endConfigStateful Router.Document listId id
, target "blank"]) , target "blank"])
[ text title ] [ text title ]
, div strikeIfDeleted [text source] , div strikeIfDeleted [text source]
...@@ -405,15 +408,6 @@ pageLoader props = React.createElement pageLoaderClass props [] ...@@ -405,15 +408,6 @@ pageLoader props = React.createElement pageLoaderClass props []
--------------------------------------------------------- ---------------------------------------------------------
newtype FavoriteQuery = FavoriteQuery
{ favorites :: Array Int
}
instance encodeJsonFQuery :: EncodeJson FavoriteQuery where
encodeJson (FavoriteQuery post)
= "favorites" := post.favorites
~> jsonEmptyObject
newtype DeleteDocumentQuery = DeleteDocumentQuery newtype DeleteDocumentQuery = DeleteDocumentQuery
{ {
documents :: Array Int documents :: Array Int
...@@ -425,11 +419,5 @@ instance encodeJsonDDQuery :: EncodeJson DeleteDocumentQuery where ...@@ -425,11 +419,5 @@ instance encodeJsonDDQuery :: EncodeJson DeleteDocumentQuery where
= "documents" := post.documents = "documents" := post.documents
~> jsonEmptyObject ~> jsonEmptyObject
putFavorites :: Int -> FavoriteQuery -> Aff (Array Int)
putFavorites nodeId = put (toUrl endConfigStateful Back Node (Just nodeId) <> "/favorites")
deleteFavorites :: Int -> FavoriteQuery -> Aff (Array Int)
deleteFavorites nodeId = deleteWithBody (toUrl endConfigStateful Back Node (Just nodeId) <> "/favorites")
deleteDocuments :: Int -> DeleteDocumentQuery -> Aff (Array Int) deleteDocuments :: Int -> DeleteDocumentQuery -> Aff (Array Int)
deleteDocuments nodeId = deleteWithBody (toUrl endConfigStateful Back Node (Just nodeId) <> "/documents") deleteDocuments nodeId = deleteWithBody (toUrl endConfigStateful Back Node (Just nodeId) <> "/documents")
...@@ -2,16 +2,17 @@ module Gargantext.Components.Login where ...@@ -2,16 +2,17 @@ module Gargantext.Components.Login where
import Control.Monad.Cont.Trans (lift) import Control.Monad.Cont.Trans (lift)
import Data.Int as Int import Data.Int as Int
import Data.Lens (over, view) import Data.Lens (over)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Data.Traversable (traverse_) import Data.Tuple.Nested((/\))
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
import Effect (Effect) import Effect (Effect)
import Effect.Aff (Aff) import Effect.Aff (Aff)
import React.DOM (a, button, div, h2, h4, h5, i, input, label, p, span, text) import Reactix as R
import React.DOM.Props (_data, _id, _type, aria, className, href, maxLength, name, onClick, onInput, placeholder, role, target, value) 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 Thermite (PerformAction, Render, Spec, _render, modifyState_, simpleSpec)
import Unsafe.Coerce (unsafeCoerce)
import Web.HTML (window) import Web.HTML (window)
import Web.HTML.Window (localStorage) import Web.HTML.Window (localStorage)
import Web.Storage.Storage (getItem, setItem, removeItem) import Web.Storage.Storage (getItem, setItem, removeItem)
...@@ -22,6 +23,7 @@ import Gargantext.Config (toUrl, endConfigStateful, Path(..), End(..)) ...@@ -22,6 +23,7 @@ import Gargantext.Config (toUrl, endConfigStateful, Path(..), End(..))
import Gargantext.Config.REST (post) import Gargantext.Config.REST (post)
import Gargantext.Components.Modals.Modal (modalHide) import Gargantext.Components.Modals.Modal (modalHide)
import Gargantext.Components.Login.Types import Gargantext.Components.Login.Types
import Gargantext.Utils.Reactix as R2
-- TODO: ask for login (modal) or account creation after 15 mn when user -- TODO: ask for login (modal) or account creation after 15 mn when user
-- is not logged and has made one search at least -- is not logged and has made one search at least
...@@ -46,8 +48,7 @@ initialState = do ...@@ -46,8 +48,7 @@ initialState = do
data Action data Action
= PostAuth = PostAuth
| SetUserName String | SetCredentials String String
| SetPassword String
modalSpec :: forall props. Boolean -> String -> Spec State props Action -> Spec State props Action modalSpec :: forall props. Boolean -> String -> Spec State props Action -> Spec State props Action
...@@ -80,115 +81,145 @@ modalSpec sm t = over _render \render d p s c -> ...@@ -80,115 +81,145 @@ modalSpec sm t = over _render \render d p s c ->
spec' :: Spec State {} Action spec' :: Spec State {} Action
spec' = modalSpec true "Login" renderSpec 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 :: Spec State {} Action
renderSpec = simpleSpec performAction render renderSpec = simpleSpec performAction render
where 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) _ _ = renderCpt :: (Action -> Effect Unit) -> State -> R.Element
modifyState_ $ _ { password = pwd } 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 R.useEffect $
res <- lift $ postAuthRequest $ AuthRequest {username, password} if (state /= s) then do
case res of _ <- d $ SetCredentials state.username state.password
AuthResponse {inval: Just (AuthInvalid {message})} -> pure $ d $ PostAuth
modifyState_ $ _ { errorMessage = message } else
AuthResponse {valid} -> do pure $ pure $ unit
liftEffect $ setAuthData valid
modifyState_ $ _ {authData = valid, errorMessage = ""}
liftEffect $ modalHide "loginModal"
render :: Render State {} Action pure $ renderLogin (state /\ setState)
render dispatch _ state _ =
[ div [className "row"] renderLogin :: R.State State -> R.Element
[ div [className "col-md-10 col-md-push-1"] renderLogin (state /\ setState) = R.createElement el {} []
[ h2 [className "text-primary center m-a-2"] where
[ i [className "material-icons md-36"] [text "control_point"] el = R.hooksComponent "RenderLogin" cpt
, span [className "icon-text"] [text "Gargantext"] cpt {} _children = do
] username <- R.useState' state.username
, div [className "card-group"] password <- R.useState' state.password
[ div [className "card"]
[ div [className "card-block"] pure $ H.div {className: "row"}
[ div [className "center"] [ gargLogo
[ h4 [className "m-b-0"] , H.div {className: "card-group"}
[ span [className "icon-text"] [ text "Welcome :)"] ] [ H.div {className: "card"}
, p [className "text-muted"] [ H.div {className: "card-block"}
[ text $ "Login to your account or", [ H.div {className: "center"}
a [ target "blank",href "https://iscpif.fr/services/applyforourservices/"] [text " ask to get an access"] [ H.h4 {className: "m-b-0"}
] [ H.span {className: "icon-text"}
[ H.text "Welcome :)"]
] ]
, div [] , H.p {className: "text-muted"}
[ input [_type "hidden", [ H.text $ "Login to your account or",
name "csrfmiddlewaretoken", H.a { target: "blank"
-- TODO hard-coded CSRF token , href: "https://iscpif.fr/services/applyforourservices/"
value "Wy52D2nor8kC1r1Y4GrsrSIxQ2eqW8UwkdiQQshMoRwobzU4uldknRUhP0j4WcEM" ] }
[H.text " ask to get an access"]
, 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 (unsafeEventValue e))] , H.div {}
] [ H.input { type: "hidden"
, div [className "form-group"] , name: "csrfmiddlewaretoken"
[ input [className "form-control", _id "id_password", name "password", placeholder "password", _type "password",value state.password,onInput \e -> dispatch (SetPassword (unsafeEventValue e))] -- TODO hard-coded CSRF token
, div [className "clearfix"] [] , value: "Wy52D2nor8kC1r1Y4GrsrSIxQ2eqW8UwkdiQQshMoRwobzU4uldknRUhP0j4WcEM"
] }
, div [className "center"]
[ label [] , H.div {className: "form-group"}
[ div [className "checkbox"] [ H.p {} [H.text state.errorMessage]
[ input [_id "terms-accept", _type "checkbox", value "", className "checkbox"] , usernameInput username
, text "I accept the terms of uses ", ]
a [href "http://gitlab.iscpif.fr/humanities/tofu/tree/master"] [text " [ Read the terms of use ] "] , H.div {className: "form-group"}
] [ passwordInput password
, button [_id "login-button",className "btn btn-primary btn-rounded", _type "submit", onClick \_ -> dispatch $ PostAuth] [text "Login"] , 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"]
] ]
] ]
] ]
] ]
] ]
] ]
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}
-- 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"]
-- ]
-- ]
-- ]
-- ]
-- ]
unsafeEventValue :: forall event. event -> String
unsafeEventValue e = (unsafeCoerce e).target.value
getAuthData :: Effect (Maybe AuthData) getAuthData :: Effect (Maybe AuthData)
getAuthData = do getAuthData = do
......
module Gargantext.Components.Login.Types where module Gargantext.Components.Login.Types where
import Prelude import Prelude
import Data.Lens (Iso', iso)
import Data.Argonaut ( class DecodeJson, class EncodeJson, decodeJson, jsonEmptyObject 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) import Data.Maybe (Maybe)
type Username = String type Username = String
...@@ -30,6 +32,12 @@ newtype AuthData = AuthData ...@@ -30,6 +32,12 @@ newtype AuthData = AuthData
, tree_id :: TreeId , 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 { token :: Token, tree_id :: TreeId }
_AuthData = iso (\(AuthData v) -> v) AuthData _AuthData = iso (\(AuthData v) -> v) AuthData
......
...@@ -40,6 +40,7 @@ import Gargantext.Components.Table as T ...@@ -40,6 +40,7 @@ import Gargantext.Components.Table as T
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Components.Loader as Loader import Gargantext.Components.Loader as Loader
import Gargantext.Components.NgramsTable.Core import Gargantext.Components.NgramsTable.Core
import Gargantext.Utils.Reactix as R2
type State = type State =
CoreState CoreState
...@@ -119,7 +120,7 @@ tableContainer { pageParams ...@@ -119,7 +120,7 @@ tableContainer { pageParams
, name "search", placeholder "Search" , name "search", placeholder "Search"
, _type "value" , _type "value"
, value pageParams.searchQuery , value pageParams.searchQuery
, onInput \e -> setSearchQuery (unsafeEventValue e) , onInput \e -> setSearchQuery (R2.unsafeEventValue e)
] ]
, div [] ( , div [] (
if A.null props.tableBody && pageParams.searchQuery /= "" then [ if A.null props.tableBody && pageParams.searchQuery /= "" then [
...@@ -134,7 +135,7 @@ tableContainer { pageParams ...@@ -134,7 +135,7 @@ tableContainer { pageParams
[ select [ _id "picklistmenu" [ select [ _id "picklistmenu"
, className "form-control custom-select" , className "form-control custom-select"
, value (maybe "" show pageParams.termListFilter) , value (maybe "" show pageParams.termListFilter)
, onChange (\e -> setTermListFilter $ readTermList $ unsafeEventValue e) , onChange (\e -> setTermListFilter $ readTermList $ R2.unsafeEventValue e)
] $ map optps1 termLists ] $ map optps1 termLists
] ]
] ]
...@@ -143,7 +144,7 @@ tableContainer { pageParams ...@@ -143,7 +144,7 @@ tableContainer { pageParams
[ select [ _id "picktermtype" [ select [ _id "picktermtype"
, className "form-control custom-select" , className "form-control custom-select"
, value (maybe "" show pageParams.termSizeFilter) , value (maybe "" show pageParams.termSizeFilter)
, onChange (\e -> setTermSizeFilter $ readTermSize $ unsafeEventValue e) , onChange (\e -> setTermSizeFilter $ readTermSize $ R2.unsafeEventValue e)
] $ map optps1 termSizes ] $ map optps1 termSizes
] ]
] ]
...@@ -420,6 +421,3 @@ optps1 :: forall a. Show a => { desc :: String, mval :: Maybe a } -> ReactElemen ...@@ -420,6 +421,3 @@ optps1 :: forall a. Show a => { desc :: String, mval :: Maybe a } -> ReactElemen
optps1 { desc, mval } = option [value val] [text desc] optps1 { desc, mval } = option [value val] [text desc]
where where
val = maybe "" show mval val = maybe "" show mval
unsafeEventValue :: forall event. event -> String
unsafeEventValue e = (unsafeCoerce e).target.value
...@@ -2,8 +2,11 @@ module Gargantext.Components.Search.Types where ...@@ -2,8 +2,11 @@ module Gargantext.Components.Search.Types where
import Control.Monad.Cont.Trans (lift) import Control.Monad.Cont.Trans (lift)
import Data.Argonaut (class EncodeJson, jsonEmptyObject, (:=), (~>), encodeJson) import Data.Argonaut (class EncodeJson, jsonEmptyObject, (:=), (~>), encodeJson)
import Data.Maybe (Maybe(..), fromMaybe, maybe)
import Data.Array (head) import Data.Array (head)
import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Eq (genericEq)
import Data.Generic.Rep.Show (genericShow)
import Data.Maybe (Maybe(..), fromMaybe, maybe)
import Data.Newtype (class Newtype) import Data.Newtype (class Newtype)
import Data.Tuple (Tuple) import Data.Tuple (Tuple)
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
...@@ -14,9 +17,9 @@ import Thermite (PerformAction, modifyState) ...@@ -14,9 +17,9 @@ import Thermite (PerformAction, modifyState)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Types (class ToQuery) import Gargantext.Types (class ToQuery)
import Gargantext.Config.REST (post) import Gargantext.Config (End(..), NodeType(..), Path(..), toUrl)
import Gargantext.Config.REST (post, put)
import Gargantext.Components.Modals.Modal (modalHide) import Gargantext.Components.Modals.Modal (modalHide)
import Gargantext.Pages.Layout.Specs.AddCorpus.States (Response, State)
import Gargantext.Utils (id) import Gargantext.Utils (id)
import URI.Extra.QueryPairs as QP import URI.Extra.QueryPairs as QP
...@@ -96,3 +99,51 @@ instance encodeJsonSearchQuery :: EncodeJson SearchQuery where ...@@ -96,3 +99,51 @@ instance encodeJsonSearchQuery :: EncodeJson SearchQuery where
~> "corpus_id" := fromMaybe 0 corpus_id ~> "corpus_id" := fromMaybe 0 corpus_id
~> "files_id" := files_id ~> "files_id" := files_id
~> jsonEmptyObject ~> jsonEmptyObject
data Category = Trash | Normal | Favorite
derive instance genericFavorite :: Generic Category _
instance showCategory :: Show Category where
show = genericShow
instance eqCategory :: Eq Category where
eq = genericEq
instance encodeJsonCategory :: EncodeJson Category where
encodeJson Trash = encodeJson 0
encodeJson Normal = encodeJson 1
encodeJson Favorite = encodeJson 2
favCategory :: Category -> Category
favCategory Normal = Favorite
favCategory Trash = Favorite
favCategory Favorite = Normal
trashCategory :: Category -> Category
trashCategory Normal = Trash
trashCategory Trash = Normal
trashCategory Favorite = Trash
decodeCategory :: Int -> Category
decodeCategory 0 = Trash
decodeCategory 1 = Normal
decodeCategory 2 = Favorite
decodeCategory _ = Normal
newtype CategoryQuery = CategoryQuery {
nodeIds :: Array Int
, category :: Category
}
instance encodeJsonCategoryQuery :: EncodeJson CategoryQuery where
encodeJson (CategoryQuery post) =
"ntc_nodesId" := post.nodeIds
~> "ntc_category" := encodeJson post.category
~> jsonEmptyObject
categoryUrl :: Int -> String
categoryUrl nodeId = toUrl Back Node (Just nodeId) <> "/category"
putCategories :: Int -> CategoryQuery -> Aff (Array Int)
putCategories nodeId = put $ categoryUrl nodeId
...@@ -14,6 +14,7 @@ import Thermite (PerformAction, Render, Spec, modifyState_, simpleSpec, StateCoT ...@@ -14,6 +14,7 @@ import Thermite (PerformAction, Render, Spec, modifyState_, simpleSpec, StateCoT
import Unsafe.Coerce (unsafeCoerce) import Unsafe.Coerce (unsafeCoerce)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Utils.Reactix as R2
type TableContainerProps = type TableContainerProps =
{ pageSizeControl :: ReactElement { pageSizeControl :: ReactElement
...@@ -218,7 +219,7 @@ sizeDD :: PageSizes -> (Action -> Effect Unit) -> ReactElement ...@@ -218,7 +219,7 @@ sizeDD :: PageSizes -> (Action -> Effect Unit) -> ReactElement
sizeDD ps d sizeDD ps d
= span [] = span []
[ select [ className "form-control" [ select [ className "form-control"
, onChange (\e -> d (ChangePageSize $ string2PageSize $ (unsafeCoerce e).target.value)) , onChange (\e -> d (ChangePageSize $ string2PageSize $ R2.unsafeEventValue e))
] $ map (optps ps) aryPS ] $ map (optps ps) aryPS
] ]
......
...@@ -699,6 +699,3 @@ uploadFile id fileType (UploadFileContents fileContents) = postWwwUrlencoded url ...@@ -699,6 +699,3 @@ uploadFile id fileType (UploadFileContents fileContents) = postWwwUrlencoded url
fnTransform :: LNode -> FTree fnTransform :: LNode -> FTree
fnTransform n = NTree n [] fnTransform n = NTree n []
unsafeEventValue :: forall event. event -> String
unsafeEventValue e = (unsafeCoerce e).target.value
...@@ -146,7 +146,7 @@ showTabType' (TabPairing t) = show t ...@@ -146,7 +146,7 @@ showTabType' (TabPairing t) = show t
data TabPostQuery = TabPostQuery { data TabPostQuery = TabPostQuery {
offset :: Int offset :: Int
, limit :: Int , limit :: Int
, orderBy :: Maybe OrderBy , orderBy :: OrderBy
, tabType :: TabType , tabType :: TabType
, query :: String , query :: String
} }
...@@ -225,10 +225,8 @@ pathUrl c (Chart {chartType, tabType}) i = ...@@ -225,10 +225,8 @@ pathUrl c (Chart {chartType, tabType}) i =
routesPath :: R.Routes -> String routesPath :: R.Routes -> String
routesPath R.Home = "" routesPath R.Home = ""
routesPath R.Login = "login" routesPath R.Login = "login"
routesPath R.SearchView = "search"
routesPath (R.Folder i) = "folder/" <> show i routesPath (R.Folder i) = "folder/" <> show i
routesPath (R.Corpus i) = "corpus/" <> 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.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.Document l i) = "list/" <> show l <> "/document/" <> show i
routesPath (R.PGraphExplorer i) = "#/" routesPath (R.PGraphExplorer i) = "#/"
......
...@@ -78,7 +78,9 @@ statefulTabs = ...@@ -78,7 +78,9 @@ statefulTabs =
, tabType: TabPairing TabDocs , tabType: TabPairing TabDocs
, totalRecords: 4736 , totalRecords: 4736
, listId: defaultListId , listId: defaultListId
, corpusId: Nothing} , corpusId: Nothing
, showSearch: true
}
ngramsViewSpec :: {mode :: Mode} -> Spec Tab.State Props Tab.Action ngramsViewSpec :: {mode :: Mode} -> Spec Tab.State Props Tab.Action
ngramsViewSpec {mode} = ngramsViewSpec {mode} =
......
...@@ -419,8 +419,9 @@ specOld = fold [treespec treeSpec, graphspec $ simpleSpec performAction render'] ...@@ -419,8 +419,9 @@ specOld = fold [treespec treeSpec, graphspec $ simpleSpec performAction render']
Nothing -> Nothing ->
simpleSpec defaultPerformAction defaultRender simpleSpec defaultPerformAction defaultRender
Just treeId -> Just treeId ->
--cmapProps (const {root: treeId, mCurrentRoute: Nothing}) $ noState $ Tree.treeview
-- TODO
simpleSpec defaultPerformAction defaultRender simpleSpec defaultPerformAction defaultRender
--cmapProps (const {root: treeId, mCurrentRoute: Nothing}) (noState $ Tree.treeview Config.endConfigStateful)
render' :: Render State {} Action render' :: Render State {} Action
......
...@@ -4,7 +4,6 @@ import Prelude hiding (div) ...@@ -4,7 +4,6 @@ import Prelude hiding (div)
import Data.Lens (view) import Data.Lens (view)
import Data.List (fromFoldable) import Data.List (fromFoldable)
import Data.Tuple (Tuple(..)) import Data.Tuple (Tuple(..))
import Gargantext.Config (TabType(..), TabSubType(..))
import Gargantext.Components.GraphExplorer.Types (GraphSideCorpus(..)) import Gargantext.Components.GraphExplorer.Types (GraphSideCorpus(..))
import Gargantext.Components.FacetsTable (TextQuery, docViewSpec) import Gargantext.Components.FacetsTable (TextQuery, docViewSpec)
import Gargantext.Components.Table as T import Gargantext.Components.Table as T
......
...@@ -10,14 +10,15 @@ import Gargantext.Components.Lang.Landing.EnUS as En ...@@ -10,14 +10,15 @@ 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, initialState)
import Gargantext.Pages.Home.Actions (Action, performAction) import Gargantext.Pages.Home.Actions (Action, performAction)
import Reactix as R
import Reactix.DOM.HTML as H
import React (ReactElement) import React (ReactElement)
import React.DOM (a, div, h3, i, img, p, span, text) import React.DOM.Props (Props)
import React.DOM.Props (Props, _id, aria, className, href, src, target, title, height, width) import Thermite (Spec, hideState, focusState, Render, simpleSpec)
import Thermite (Render, Spec, simpleSpec, hideState, focusState)
import Gargantext.Utils.Reactix as R2
-- Layout | -- Layout |
...@@ -26,80 +27,82 @@ landingData FR = Fr.landingData ...@@ -26,80 +27,82 @@ landingData FR = Fr.landingData
landingData EN = En.landingData landingData EN = En.landingData
layoutLanding :: Lang -> Spec {} {} Void layoutLanding :: Lang -> Spec {} {} Void
layoutLanding = hideState (const $ unwrap initialState) layoutLanding = layoutLanding' <<< landingData
<<< focusState (re _Newtype)
<<< layoutLanding' <<< landingData
------------------------------------------------------------------------ ------------------------------------------------------------------------
layoutLanding' :: LandingData -> Spec State {} Action layoutLanding' :: LandingData -> Spec {} {} Void
layoutLanding' hd = simpleSpec performAction render layoutLanding' hd = R2.elSpec $ R.hooksComponent "LayoutLanding" cpt
where where
render :: Render State {} Action cpt {} _children = do
render dispatch _ state _ = pure $ H.span {} [
[ div [ className "container1" ] [ jumboTitle hd false ] H.div { className: "container1" }
, div [ className "container1" ] [] -- TODO put research form [ jumboTitle hd false ]
, div [ className "container1" ] [ blocksRandomText' hd ] , 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' (LandingData hd) = blocksRandomText hd.blockTexts
blocksRandomText :: BlockTexts -> ReactElement blocksRandomText :: BlockTexts -> R.Element
blocksRandomText (BlockTexts bt) = blocksRandomText (BlockTexts bt) =
div [ className "row" ] ( map showBlock bt.blocks ) H.div { className: "row" } ( map showBlock bt.blocks )
where where
showBlock :: BlockText -> ReactElement showBlock :: BlockText -> R.Element
showBlock (BlockText b) = showBlock (BlockText b) =
div [ className "col-md-4 content" ] H.div { className: "col-md-4 content" }
[ h3 [] [ a [ href b.href, title b.title] [ H.h3 {} [ H.a { href: b.href, title: b.title}
[ i [className b.icon] [] [ H.i {className: b.icon} []
, text (" " <> b.titleText) , H.text (" " <> b.titleText)
] ]
] ]
, p [] [ text b.text ] , H.p {} [ H.text b.text ]
, p [] [ docButton b.docButton ] , H.p {} [ docButton b.docButton ]
] ]
docButton :: Button -> ReactElement docButton :: Button -> R.Element
docButton (Button b) = a [ className "btn btn-outline-primary btn-sm spacing-class" docButton (Button b) =
, href b.href H.a { className: "btn btn-outline-primary btn-sm spacing-class"
, target "blank" , href: b.href
, title b.title , target: "blank"
] [ span [ aria {hidden : true} , title: b.title
, className "glyphicon glyphicon-hand-right" } [ H.span { aria: {hidden : true}
] [] , className: "glyphicon glyphicon-hand-right"
, text b.text } []
] , H.text b.text
]
jumboTitle :: LandingData -> Boolean -> ReactElement
jumboTitle (LandingData hd) b = div jumbo jumboTitle :: LandingData -> Boolean -> R.Element
[ div [className "row" ] jumboTitle (LandingData hd) b =
[ div [ className "col-md-12 content"] H.div {className: jumbo}
[ div [ className "center" ] [ H.div { className: "row" }
[ div [_id "logo-designed" ] [ H.div { className: "col-md-12 content" }
[ img [ src "images/logo.png" [ H.div { className: "center" }
, title hd.logoTitle [ H.div { id: "logo-designed" }
] [ H.img { src: "images/logo.png"
] , title: hd.logoTitle
] }
] ]
] ]
] ]
where ]
jumbo = case b of ]
true -> [className "jumbotron"] where
false -> [] jumbo = case b of
true -> "jumbotron"
imageEnter :: LandingData -> Props -> ReactElement false -> ""
imageEnter (LandingData hd) action = div [className "row"]
[ div [className "col-md-offset-5 col-md-6 content"] imageEnter :: LandingData -> Props -> R.Element
[ img [ src "images/Gargantextuel-212x300.jpg" imageEnter (LandingData hd) action =
, _id "funnyimg" H.div {className: "row"}
, title hd.imageTitle [ H.div {className: "col-md-offset-5 col-md-6 content"}
, action [ H.img { src: "images/Gargantextuel-212x300.jpg"
] , id: "funnyimg"
] , title: hd.imageTitle
] , action
}
]
]
...@@ -3,14 +3,12 @@ module Gargantext.Pages.Layout where ...@@ -3,14 +3,12 @@ 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.Corpus.Tabs as TV -- import Gargantext.Pages.Corpus.Tabs as TV
import Gargantext.Pages.Corpus.Graph as GE import Gargantext.Pages.Corpus.Graph as GE
-- import Gargantext.Pages.Corpus.Tabs.Terms.NgramsTable as NG -- import Gargantext.Pages.Corpus.Tabs.Terms.NgramsTable as NG
-- import Gargantext.Pages.Home as L -- import Gargantext.Pages.Home as L
-- import Gargantext.Pages.Layout.Specs.Search as S
import Gargantext.Router (Routes(..)) import Gargantext.Router (Routes(..))
dispatchAction :: forall ignored m. dispatchAction :: forall ignored m.
...@@ -25,17 +23,9 @@ dispatchAction dispatcher _ Login = do ...@@ -25,17 +23,9 @@ dispatchAction dispatcher _ Login = do
dispatcher $ SetRoute Login dispatcher $ SetRoute Login
-- dispatcher $ LoginA TODO -- dispatcher $ LoginA TODO
dispatchAction dispatcher _ AddCorpus = do
dispatcher $ SetRoute AddCorpus
dispatcher $ AddCorpusA AC.LoadDatabaseDetails
dispatchAction dispatcher _ (Corpus n) = do dispatchAction dispatcher _ (Corpus n) = do
dispatcher $ SetRoute $ Corpus n dispatcher $ SetRoute $ Corpus n
dispatchAction dispatcher _ SearchView = do
dispatcher $ SetRoute SearchView
-- dispatcher $ SearchA TODO
dispatchAction dispatcher _ (UserPage id) = do dispatchAction dispatcher _ (UserPage id) = do
dispatcher $ SetRoute $ UserPage id dispatcher $ SetRoute $ UserPage id
......
...@@ -13,8 +13,6 @@ import Gargantext.Components.Login as LN ...@@ -13,8 +13,6 @@ import Gargantext.Components.Login as LN
import Gargantext.Components.Modals.Modal (modalShow) import Gargantext.Components.Modals.Modal (modalShow)
import Gargantext.Pages.Annuaire as Annuaire import Gargantext.Pages.Annuaire as Annuaire
import Gargantext.Pages.Corpus.Graph as GE 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.Pages.Layout.States (AppState)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Router (Routes) import Gargantext.Router (Routes)
...@@ -24,8 +22,6 @@ import Gargantext.Router (Routes) ...@@ -24,8 +22,6 @@ import Gargantext.Router (Routes)
data Action data Action
= LoginA LN.Action = LoginA LN.Action
| SetRoute Routes | SetRoute Routes
| SearchA S.Action
| AddCorpusA AC.Action
| GraphExplorerA GE.Action | GraphExplorerA GE.Action
| AnnuaireAction Annuaire.Action | AnnuaireAction Annuaire.Action
| ShowLogin | ShowLogin
...@@ -61,8 +57,6 @@ performAction ShowAddCorpus _ _ = void do ...@@ -61,8 +57,6 @@ performAction ShowAddCorpus _ _ = void do
--------------------------------------------------------- ---------------------------------------------------------
performAction (LoginA _) _ _ = pure unit performAction (LoginA _) _ _ = pure unit
performAction (AddCorpusA _) _ _ = pure unit
performAction (SearchA _) _ _ = pure unit
performAction (GraphExplorerA _) _ _ = pure unit performAction (GraphExplorerA _) _ _ = pure unit
performAction (AnnuaireAction _) _ _ = pure unit performAction (AnnuaireAction _) _ _ = pure unit
-- liftEffect $ modalShow "addCorpus" -- liftEffect $ modalShow "addCorpus"
...@@ -76,18 +70,6 @@ _loginAction = prism LoginA \action -> ...@@ -76,18 +70,6 @@ _loginAction = prism LoginA \action ->
LoginA caction -> Right caction LoginA caction -> Right caction
_-> Left action _-> 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' Action Annuaire.Action
_annuaireAction = prism AnnuaireAction \action -> _annuaireAction = prism AnnuaireAction \action ->
case action of case action of
......
...@@ -4,10 +4,11 @@ import Data.Foldable (fold, intercalate) ...@@ -4,10 +4,11 @@ import Data.Foldable (fold, intercalate)
import Data.Lens (over) import Data.Lens (over)
import Data.Maybe (Maybe(Nothing, Just)) import Data.Maybe (Maybe(Nothing, Just))
import Effect (Effect) import Effect (Effect)
import React (ReactElement) import React.DOM (button, div, text)
import React.DOM (a, button, div, footer, hr', img, li, p, span, text, ul) import React.DOM.Props (_id, className, onClick, role, style)
import React.DOM.Props (_data, _id, aria, className, href, onClick, role, src, style, tabIndex, target, title, height, width) import Reactix as R
import Thermite (Render, Spec, _render, defaultPerformAction, defaultRender, focus, simpleSpec, withState, noState, cmapProps) import Reactix.DOM.HTML as H
import Thermite (Spec, _render, defaultPerformAction, defaultRender, focus, simpleSpec, withState, noState, cmapProps)
-- import Unsafe.Coerce (unsafeCoerce) -- import Unsafe.Coerce (unsafeCoerce)
import Gargantext.Prelude import Gargantext.Prelude
...@@ -25,13 +26,11 @@ import Gargantext.Pages.Corpus.Graph as GE ...@@ -25,13 +26,11 @@ import Gargantext.Pages.Corpus.Graph as GE
import Gargantext.Pages.Lists as Lists import Gargantext.Pages.Lists as Lists
import Gargantext.Pages.Texts as Texts import Gargantext.Pages.Texts as Texts
import Gargantext.Pages.Home as L import Gargantext.Pages.Home as L
import Gargantext.Pages.Layout.Actions (Action(..), _addCorpusAction, _graphExplorerAction, _loginAction, _searchAction, performAction) import Gargantext.Pages.Layout.Actions (Action(..), _graphExplorerAction, _loginAction, performAction)
import Gargantext.Pages.Layout.Specs.AddCorpus as AC
import Gargantext.Pages.Layout.Specs.Search as S
import Gargantext.Pages.Layout.Specs.SearchBar as SB import Gargantext.Pages.Layout.Specs.SearchBar as SB
import Gargantext.Pages.Layout.States (AppState, _graphExplorerState, _searchState, _loginState, _addCorpusState) import Gargantext.Pages.Layout.States (AppState, _graphExplorerState, _loginState)
import Gargantext.Router (Routes(..)) import Gargantext.Router (Routes(..))
import Gargantext.Utils.Reactix (scuff) import Gargantext.Utils.Reactix as R2
-- TODO -- TODO
-- rewrite layoutSpec to use state (with EndConfig) -- rewrite layoutSpec to use state (with EndConfig)
...@@ -44,7 +43,6 @@ layoutSpec = ...@@ -44,7 +43,6 @@ layoutSpec =
, container $ withState pagesComponent , container $ withState pagesComponent
, withState \st -> , withState \st ->
fold [ focus _loginState _loginAction (LN.modalSpec st.showLogin "Login" LN.renderSpec) fold [ focus _loginState _loginAction (LN.modalSpec st.showLogin "Login" LN.renderSpec)
, focus _addCorpusState _addCorpusAction (AC.modalSpec st.showCorpus "Search Results" AC.layoutAddcorpus)
] ]
] ]
where where
...@@ -59,13 +57,11 @@ pagesComponent s = case s.currentRoute of ...@@ -59,13 +57,11 @@ pagesComponent s = case s.currentRoute of
Nothing -> selectSpec Home -- TODO add Error page here: url requested does not exist (with funny Garg image) Nothing -> selectSpec Home -- TODO add Error page here: url requested does not exist (with funny Garg image)
where where
selectSpec :: Routes -> Spec AppState {} Action 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 Login = focus _loginState _loginAction LN.renderSpec
selectSpec (Folder i) = layout0 $ noState F.layoutFolder selectSpec (Folder i) = layout0 $ noState F.layoutFolder
selectSpec (Corpus i) = layout0 $ cmapProps (const {nodeId: i}) $ noState Corpus.layout 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 (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 (Document l i) = layout0 $ cmapProps (const {nodeId: i, listId: l, corpusId: Nothing}) $ noState Annotation.layout
selectSpec (PGraphExplorer i)= layout1 $ focus _graphExplorerState _graphExplorerAction GE.specOld selectSpec (PGraphExplorer i)= layout1 $ focus _graphExplorerState _graphExplorerAction GE.specOld
...@@ -87,7 +83,7 @@ layout0 layout = ...@@ -87,7 +83,7 @@ layout0 layout =
fold fold
[ searchBar [ searchBar
, outerLayout , outerLayout
, layoutFooter , noState layoutFooter
] ]
where where
outerLayout1 = simpleSpec defaultPerformAction defaultRender outerLayout1 = simpleSpec defaultPerformAction defaultRender
...@@ -115,8 +111,6 @@ layout0 layout = ...@@ -115,8 +111,6 @@ layout0 layout =
] (render d p s c) ] ] (render d p s c) ]
cont = over _render \render d p s c -> [ div [className "row" ] (render d p s c) ] cont = over _render \render d p s c -> [ div [className "row" ] (render d p s c) ]
--as = noState Tree.treeview
bs = innerLayout $ layout bs = innerLayout $ layout
innerLayout :: Spec AppState {} Action innerLayout :: Spec AppState {} Action
...@@ -136,7 +130,7 @@ layout1 layout = ...@@ -136,7 +130,7 @@ layout1 layout =
[ searchBar [ searchBar
, layout , layout
-- , outerLayout -- , outerLayout
, layoutFooter , noState layoutFooter
] ]
where where
outerLayout1 = simpleSpec defaultPerformAction defaultRender outerLayout1 = simpleSpec defaultPerformAction defaultRender
...@@ -182,29 +176,29 @@ searchBar = simpleSpec defaultPerformAction render ...@@ -182,29 +176,29 @@ searchBar = simpleSpec defaultPerformAction render
] [ div [className "container-fluid" ] [ div [className "container-fluid"
] ]
[ div [ className "navbar-inner" ] [ div [ className "navbar-inner" ]
[ divLogo [ R2.scuff divLogo
, div [ className "collapse navbar-collapse" , div [ className "collapse navbar-collapse"
] ]
$ [ divDropdownLeft ] $ [ R2.scuff divDropdownLeft ]
<> [ scuff (SB.searchBar SB.defaultProps) ] <> [ R2.scuff (SB.searchBar SB.defaultProps) ]
<> [ divDropdownRight d s ] <> [ R2.scuff $ divDropdownRight d s ]
] ]
] ]
] ]
] ]
divLogo :: ReactElement divLogo :: R.Element
divLogo = a [ className "navbar-brand logoSmall" divLogo = H.a { className: "navbar-brand logoSmall"
, href "#/" , href: "#/"
] [ img [ src "images/logoSmall.png" } [ H.img { src: "images/logoSmall.png"
, title "Back to home." , title: "Back to home."
, width "30" , width: "30"
, height "28" , height: "28"
] }
] ]
divDropdownLeft :: ReactElement divDropdownLeft :: R.Element
divDropdownLeft = divDropdownLeft' (LiNav { title : "About Gargantext" divDropdownLeft = divDropdownLeft' (LiNav { title : "About Gargantext"
, href : "#" , href : "#"
, icon : "glyphicon glyphicon-info-sign" , icon : "glyphicon glyphicon-info-sign"
...@@ -212,32 +206,33 @@ divDropdownLeft = divDropdownLeft' (LiNav { title : "About Gargantext" ...@@ -212,32 +206,33 @@ divDropdownLeft = divDropdownLeft' (LiNav { title : "About Gargantext"
} }
) )
divDropdownLeft' :: LiNav -> ReactElement divDropdownLeft' :: LiNav -> R.Element
divDropdownLeft' mb = ul [className "nav navbar-nav"] divDropdownLeft' mb = H.ul {className: "nav navbar-nav"}
[ ul [className "nav navbar-nav pull-left"] [ H.ul {className: "nav navbar-nav pull-left"}
[ li [className "dropdown"] [ H.li {className: "dropdown"}
[ menuButton mb [ menuButton mb
, menuElements' , menuElements'
] ]
] ]
] ]
menuButton :: LiNav -> ReactElement menuButton :: LiNav -> R.Element
menuButton (LiNav { title : title' menuButton (LiNav { title : title'
, href : href' , href : href'
, icon : icon' , icon : icon'
, text : text' , text : text'
}) = a [ className "dropdown-toggle navbar-text" }) = H.a { className: "dropdown-toggle navbar-text"
, _data {toggle: "dropdown"} , data: {toggle: "dropdown"}
, href href', role "button" , href: href'
, title title' , role: "button"
][ span [ aria {hidden : true} , title: title'
, className icon' } [ H.span { aria: {hidden : true}
] [] , className: icon'
, text (" " <> text') } []
] , H.text (" " <> text')
]
menuElements' :: ReactElement
menuElements' :: R.Element
menuElements' = menuElements-- title, icon, text menuElements' = menuElements-- title, icon, text
[ -- =========================================================== [ -- ===========================================================
[ LiNav { title : "Quick start, tutorials and methodology" [ LiNav { title : "Quick start, tutorials and methodology"
...@@ -273,14 +268,14 @@ menuElements' = menuElements-- title, icon, text ...@@ -273,14 +268,14 @@ menuElements' = menuElements-- title, icon, text
] -- =========================================================== ] -- ===========================================================
-- | Menu in the sidebar, syntactic sugar -- | Menu in the sidebar, syntactic sugar
menuElements :: Array (Array LiNav) -> ReactElement menuElements :: Array (Array LiNav) -> R.Element
menuElements ns = dropDown $ intercalate divider $ map (map liNav) ns menuElements ns = dropDown $ intercalate divider $ map (map liNav) ns
where where
dropDown :: Array ReactElement -> ReactElement dropDown :: Array R.Element -> R.Element
dropDown = ul [className "dropdown-menu"] dropDown = H.ul {className: "dropdown-menu"}
divider :: Array ReactElement divider :: Array R.Element
divider = [li [className "divider"] []] divider = [H.li {className: "divider"} []]
-- | surgar for target : "blank" -- | surgar for target : "blank"
--data LiNav_ = LiNav_ { title :: String --data LiNav_ = LiNav_ { title :: String
...@@ -296,77 +291,78 @@ data LiNav = LiNav { title :: String ...@@ -296,77 +291,78 @@ data LiNav = LiNav { title :: String
, text :: String , text :: String
} }
liNav :: LiNav -> ReactElement liNav :: LiNav -> R.Element
liNav (LiNav { title : title' liNav (LiNav { title : title'
, href : href' , href : href'
, icon : icon' , icon : icon'
, text : text' , text : text'
} }
) = li [] [ a [ tabIndex (-1) ) = H.li {} [ H.a { tabIndex: (-1)
, target "blank" , target: "blank"
, title title' , title: title'
, href href' , href: href'
] [ span [ className icon' ] [] } [ H.span { className: icon' } []
, text $ " " <> text' , H.text $ " " <> text'
] ]
] ]
logLinks :: (Action -> Effect Unit) -> AppState -> ReactElement logLinks :: (Action -> Effect Unit) -> AppState -> R.Element
logLinks d s = case s.loginState.authData of logLinks d s = case s.loginState.authData of
Nothing -> loginLink Nothing -> loginLink
Just _ -> logoutLink Just _ -> logoutLink
where where
loginLink = loginLink =
a [ aria {hidden : true} H.a { aria: {hidden : true}
, className "glyphicon glyphicon-log-in" , className: "glyphicon glyphicon-log-in"
, onClick $ \e -> d ShowLogin , on: {click: \e -> d ShowLogin}
, style {color:"white"} , style: {color:"white"}
, title "Log in and save your time" , title: "Log in and save your time"
-- TODO hover: bold -- TODO hover: bold
] }
[text " Login / Signup"] [H.text " Login / Signup"]
-- TODO dropdown to logout -- TODO dropdown to logout
logoutLink = logoutLink =
a [ aria {hidden : true} H.a { aria: {hidden : true}
, className "glyphicon glyphicon-log-out" , className: "glyphicon glyphicon-log-out"
, onClick $ \e -> d Logout , on: {click: \e -> d Logout}
, style {color:"white"} , style: {color:"white"}
, title "Log out" -- TODO , title: "Log out" -- TODO
-- TODO hover: bold -- TODO hover: bold
] }
[text " Logout"] [H.text " Logout"]
divDropdownRight :: (Action -> Effect Unit) -> AppState -> ReactElement divDropdownRight :: (Action -> Effect Unit) -> AppState -> R.Element
divDropdownRight d s = divDropdownRight d s =
ul [className "nav navbar-nav pull-right"] H.ul {className: "nav navbar-nav pull-right"}
[ li [className "dropdown"] [ H.li {className: "dropdown"}
[ logLinks d s ] [ logLinks d s ]
] ]
layoutFooter :: Spec AppState {} Action layoutFooter :: Spec {} {} Void
layoutFooter = simpleSpec performAction render layoutFooter = R2.elSpec $ R.hooksComponent "LayoutFooter" cpt
where where
render :: Render AppState {} Action cpt {} _children = do
render dispatch _ state _ = [div [ className "container" ] [ hr', footerLegalInfo']] pure $ H.div { className: "container" } [ H.hr {}, footerLegalInfo']
where
footerLegalInfo' = footer [] [ p [] [ text "Gargantext " footerLegalInfo' = H.footer {}
, span [className "glyphicon glyphicon-registration-mark" ] [] [ H.p {} [ H.text "Gargantext "
, text ", version 4.0" , H.span {className: "glyphicon glyphicon-registration-mark"} []
, a [ href "http://www.cnrs.fr" , H.text ", version 4.0"
, target "blank" , H.a { href: "http://www.cnrs.fr"
, title "Project hosted by CNRS." , target: "blank"
] , title: "Project hosted by CNRS."
[ text ", Copyrights " }
, span [ className "glyphicon glyphicon-copyright-mark" ] [] [ H.text ", Copyrights "
, text " CNRS 2017-Present" , H.span { className: "glyphicon glyphicon-copyright-mark" } []
] , H.text " CNRS 2017-Present"
, a [ href "http://gitlab.iscpif.fr/humanities/gargantext/blob/stable/LICENSE" ]
, target "blank" , H.a { href: "http://gitlab.iscpif.fr/humanities/gargantext/blob/stable/LICENSE"
, title "Legal instructions of the project." , target: "blank"
] , title: "Legal instructions of the project."
[ text ", Licences aGPLV3 and CECILL variant Affero compliant" ] }
, text "." [ H.text ", Licences aGPLV3 and CECILL variant Affero compliant" ]
] , H.text "."
] ]
]
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 Unsafe.Coerce (unsafeCoerce)
type State =
{
query :: String
}
initialState :: State
initialState =
{
query : "empty query"
}
data Action
= GO
| SetQuery String
unsafeEventValue :: forall event. event -> String
unsafeEventValue e = (unsafeCoerce e).target.value
searchSpec :: Spec State {} Action
searchSpec = simpleSpec performAction render
where
performAction :: PerformAction State {} Action
performAction (SetQuery q) _ _ = void do
modifyState $ _ { query = q }
performAction GO _ _ = void do
liftEffect $ setHash "/addCorpus"
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 (unsafeEventValue e))
]
, br'
]
-}
]
, div [ className "col-md-2"]
[ br'
, br'
, button [onClick \_ -> dispatch GO] [text "GO"]
]
, br'
]
]
]
]
...@@ -9,15 +9,11 @@ import Gargantext.Components.Login as LN ...@@ -9,15 +9,11 @@ import Gargantext.Components.Login as LN
import Gargantext.Config (EndConfig, endConfigStateful) import Gargantext.Config (EndConfig, endConfigStateful)
import Gargantext.Pages.Corpus.Graph as GE 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(..)) import Gargantext.Router (Routes(..))
type AppState = type AppState =
{ currentRoute :: Maybe Routes { currentRoute :: Maybe Routes
, loginState :: LN.State , loginState :: LN.State
, addCorpusState :: AC.State
, searchState :: S.State
, showLogin :: Boolean , showLogin :: Boolean
, showCorpus :: Boolean , showCorpus :: Boolean
, graphExplorerState :: GE.State , graphExplorerState :: GE.State
...@@ -31,8 +27,6 @@ initAppState = do ...@@ -31,8 +27,6 @@ initAppState = do
pure pure
{ currentRoute : Just Home { currentRoute : Just Home
, loginState , loginState
, addCorpusState : AC.initialState
, searchState : S.initialState
, showLogin : false , showLogin : false
, showCorpus : false , showCorpus : false
, graphExplorerState : GE.initialState , graphExplorerState : GE.initialState
...@@ -46,12 +40,6 @@ initAppState = do ...@@ -46,12 +40,6 @@ initAppState = do
_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})
_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' AppState GE.State
_graphExplorerState = lens (\s -> s.graphExplorerState) (\s ss -> s{graphExplorerState = ss}) _graphExplorerState = lens (\s -> s.graphExplorerState) (\s ss -> s{graphExplorerState = ss})
...@@ -89,6 +89,7 @@ docViewSpec tst = R2.elSpec $ R.hooksComponent "DocViewSpecWithCorpus" cpt ...@@ -89,6 +89,7 @@ docViewSpec tst = R2.elSpec $ R.hooksComponent "DocViewSpecWithCorpus" cpt
, totalRecords: 4737 , totalRecords: 4737
, listId: defaultListId , listId: defaultListId
, corpusId: Just corpusId , corpusId: Just corpusId
, showSearch: true
} }
params TabMoreLikeFav = { params TabMoreLikeFav = {
nodeId: corpusId nodeId: corpusId
...@@ -98,6 +99,7 @@ docViewSpec tst = R2.elSpec $ R.hooksComponent "DocViewSpecWithCorpus" cpt ...@@ -98,6 +99,7 @@ docViewSpec tst = R2.elSpec $ R.hooksComponent "DocViewSpecWithCorpus" cpt
, totalRecords: 4737 , totalRecords: 4737
, listId: defaultListId , listId: defaultListId
, corpusId: Just corpusId , corpusId: Just corpusId
, showSearch: false
} }
params TabMoreLikeTrash = { params TabMoreLikeTrash = {
nodeId: corpusId nodeId: corpusId
...@@ -107,6 +109,7 @@ docViewSpec tst = R2.elSpec $ R.hooksComponent "DocViewSpecWithCorpus" cpt ...@@ -107,6 +109,7 @@ docViewSpec tst = R2.elSpec $ R.hooksComponent "DocViewSpecWithCorpus" cpt
, totalRecords: 4737 , totalRecords: 4737
, listId: defaultListId , listId: defaultListId
, corpusId: Just corpusId , corpusId: Just corpusId
, showSearch: false
} }
params TabTrash = { params TabTrash = {
nodeId: corpusId nodeId: corpusId
...@@ -116,6 +119,7 @@ docViewSpec tst = R2.elSpec $ R.hooksComponent "DocViewSpecWithCorpus" cpt ...@@ -116,6 +119,7 @@ docViewSpec tst = R2.elSpec $ R.hooksComponent "DocViewSpecWithCorpus" cpt
, totalRecords: 4737 , totalRecords: 4737
, listId: defaultListId , listId: defaultListId
, corpusId: Nothing , corpusId: Nothing
, showSearch: true
} }
-- DUMMY -- DUMMY
params _ = { params _ = {
...@@ -126,4 +130,5 @@ docViewSpec tst = R2.elSpec $ R.hooksComponent "DocViewSpecWithCorpus" cpt ...@@ -126,4 +130,5 @@ docViewSpec tst = R2.elSpec $ R.hooksComponent "DocViewSpecWithCorpus" cpt
, totalRecords: 4737 , totalRecords: 4737
, listId: defaultListId , listId: defaultListId
, corpusId: Nothing , corpusId: Nothing
, showSearch: true
} }
...@@ -16,10 +16,8 @@ import Web.Storage.Storage (getItem) ...@@ -16,10 +16,8 @@ import Web.Storage.Storage (getItem)
data Routes data Routes
= Home = Home
| Login | Login
| SearchView
| Folder Int | Folder Int
| Corpus Int | Corpus Int
| AddCorpus
| Document Int Int | Document Int Int
| CorpusDocument Int Int Int | CorpusDocument Int Int Int
| PGraphExplorer Int | PGraphExplorer Int
...@@ -33,8 +31,6 @@ data Routes ...@@ -33,8 +31,6 @@ data Routes
routing :: Match Routes routing :: Match Routes
routing = oneOf routing = oneOf
[ Login <$ route "login" [ Login <$ route "login"
, SearchView <$ route "search"
, AddCorpus <$ route "addCorpus"
, Folder <$> (route "folder" *> int) , Folder <$> (route "folder" *> int)
, CorpusDocument <$> (route "corpus" *> int) <*> (lit "list" *> int) <*> (lit "document" *> int) , CorpusDocument <$> (route "corpus" *> int) <*> (lit "list" *> int) <*> (lit "document" *> int)
, Corpus <$> (route "corpus" *> int) , Corpus <$> (route "corpus" *> int)
...@@ -57,8 +53,6 @@ routing = oneOf ...@@ -57,8 +53,6 @@ routing = oneOf
instance showRoutes :: Show Routes where instance showRoutes :: Show Routes where
show Login = "Login" show Login = "Login"
show AddCorpus = "AddCorpus"
show SearchView = "Search"
show (UserPage i) = "User" <> show i show (UserPage i) = "User" <> show i
show (ContactPage i) = "Contact" <> show i show (ContactPage i) = "Contact" <> show i
show (CorpusDocument _ _ i) = "Document" <> show i show (CorpusDocument _ _ i) = "Document" <> show i
......
...@@ -89,3 +89,7 @@ select = createDOMElement "select" ...@@ -89,3 +89,7 @@ select = createDOMElement "select"
effToggler :: forall e. R.State Boolean -> EffectFn1 e Unit effToggler :: forall e. R.State Boolean -> EffectFn1 e Unit
effToggler (value /\ setValue) = mkEffectFn1 $ \e -> setValue $ const $ not value effToggler (value /\ setValue) = mkEffectFn1 $ \e -> setValue $ const $ not value
unsafeEventValue :: forall event. event -> String
unsafeEventValue e = (unsafeCoerce e).target.value
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