Commit 54d7b3fe authored by Sudhir Kumar's avatar Sudhir Kumar

api call added for delete documents

parent 2a9787c1
module Gargantext.Pages.Corpus.Tabs.Documents where module Gargantext.Pages.Corpus.Tabs.Documents where
import Data.Array (take, drop) import Gargantext.Prelude
import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, jsonEmptyObject, (.?), (:=), (~>))
import Affjax (defaultRequest, request)
import Affjax.RequestBody (RequestBody(..))
import Affjax.ResponseFormat (printResponseFormatError)
import Affjax.ResponseFormat as ResponseFormat
import Control.Monad.Cont.Trans (lift)
import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, encodeJson, jsonEmptyObject, (.?), (:=), (~>))
import Data.Array (take, drop)
import Data.Either (Either(..))
import Data.Generic.Rep (class Generic) import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Show (genericShow) import Data.Generic.Rep.Show (genericShow)
import Data.Maybe (maybe) import Data.HTTP.Method (Method(..))
import Data.List (List)
import Data.Maybe (Maybe(..), maybe)
import Data.Tuple (Tuple(..)) import Data.Tuple (Tuple(..))
import Effect.Aff (Aff) import Effect.Aff (Aff)
import React.DOM (a, br', div, input, p, text) import Effect.Class (liftEffect)
import React.DOM.Props (_type, className, href, style, placeholder, name) import Effect.Console (log)
import Thermite (Render, Spec, defaultPerformAction, simpleSpec)
------------------------------------------------------------------------
import Gargantext.Prelude
import Gargantext.Config (NodeType(..), TabType(..), toUrl, End(..), OrderBy(..))
import Gargantext.Config.REST (get, post)
import Gargantext.Utils.DecodeMaybe ((.|))
import Gargantext.Components.Charts.Options.ECharts (chart) import Gargantext.Components.Charts.Options.ECharts (chart)
import Gargantext.Components.Table as T
import Gargantext.Components.Node (NodePoly(..)) import Gargantext.Components.Node (NodePoly(..))
import Gargantext.Pages.Corpus.Tabs.Types (CorpusInfo(..), Props) import Gargantext.Components.Table as T
import Gargantext.Config (NodeType(..), TabType(..), toUrl, End(..), OrderBy(..))
import Gargantext.Config.REST (get, post)
import Gargantext.Pages.Corpus.Dashboard (globalPublis) import Gargantext.Pages.Corpus.Dashboard (globalPublis)
import Gargantext.Pages.Corpus.Tabs.Types (CorpusInfo(..), Props)
import Gargantext.Utils.DecodeMaybe ((.|))
import React.DOM (a, br', button, div, i, input, p, text)
import React.DOM.Props (_type, className, href, name, onClick, placeholder, style, value)
import Thermite (PerformAction, Render, Spec, defaultPerformAction, modifyState, simpleSpec)
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- TODO: Pagination Details are not available from the BackEnd -- TODO: Pagination Details are not available from the BackEnd
-- TODO: Search is pending -- TODO: Search is pending
...@@ -29,9 +38,41 @@ import Gargantext.Pages.Corpus.Dashboard (globalPublis) ...@@ -29,9 +38,41 @@ import Gargantext.Pages.Corpus.Dashboard (globalPublis)
-- TODO: Filter is Pending -- TODO: Filter is Pending
-- TODO: When a pagination link is clicked, reload data. -- TODO: When a pagination link is clicked, reload data.
type State = {} type State =
{ documents :: DocumentsView
, deleteRows :: Boolean
, deleteRowId :: Int
}
data Action
= SendFavorites Int
| DeleteDocuments Int
| Trash
performAction :: PerformAction State Props Action
performAction (SendFavorites nid) _ _ = void $ do
s' <- lift $ favorites nid (FavoriteQuery {favorites : [nid]})
case s' of
Left err -> do
_ <- liftEffect $ log err
modifyState identity
Right d -> modifyState identity
performAction (DeleteDocuments nid) _ _ = void $ do
_ <- liftEffect $ log $ show nid
modifyState \state -> state {deleteRowId = nid, deleteRows = true}
performAction (Trash) _ state = void $ do
s' <- lift $ deleteDocuments state.deleteRowId (DeleteDocumentQuery {documents : [state.deleteRowId]})
case s' of
Left err -> do
_ <- liftEffect $ log err
modifyState identity
Right d -> modifyState identity
type Action = Void
newtype DocumentsView newtype DocumentsView
= DocumentsView = DocumentsView
...@@ -103,7 +144,7 @@ instance decodeResponse :: DecodeJson Response where ...@@ -103,7 +144,7 @@ instance decodeResponse :: DecodeJson Response where
-- | Filter -- | Filter
filterSpec :: Spec {} {} Void filterSpec :: Spec State Props Action
filterSpec = simpleSpec defaultPerformAction render filterSpec = simpleSpec defaultPerformAction render
where where
render d p s c = [div [] [ text " Filter " render d p s c = [div [] [ text " Filter "
...@@ -111,11 +152,11 @@ filterSpec = simpleSpec defaultPerformAction render ...@@ -111,11 +152,11 @@ filterSpec = simpleSpec defaultPerformAction render
]] ]]
-- | Main layout of the Documents Tab of a Corpus -- | Main layout of the Documents Tab of a Corpus
layoutDocview :: Spec {} Props Void layoutDocview :: Spec State Props Action
layoutDocview = simpleSpec absurd render layoutDocview = simpleSpec performAction render
where where
render :: Render {} Props Void render :: Render State Props Action
render dispatch {path: nodeId, loaded} _ _ = render dispatch {path: nodeId, loaded} _ s =
[ p [] [] [ p [] []
, div [ style {textAlign : "center"}] [input [placeholder "Filter here"]] , div [ style {textAlign : "center"}] [input [placeholder "Filter here"]]
, br' , br'
...@@ -142,6 +183,16 @@ layoutDocview = simpleSpec absurd render ...@@ -142,6 +183,16 @@ layoutDocview = simpleSpec absurd render
<$> loaded) <$> loaded)
} }
] ]
, div [className "col-md-12"]
[ button [style {backgroundColor: "peru", padding : "9px", color : "white", border : "white", float: "right"}
, onClick $ (\_ -> dispatch $ Trash )
]
[ i [className "glyphitem glyphicon glyphicon-trash", style {marginRight : "9px"}] []
, text "Trash it !"
]
]
] ]
] ]
] ]
...@@ -153,14 +204,16 @@ layoutDocview = simpleSpec absurd render ...@@ -153,14 +204,16 @@ layoutDocview = simpleSpec absurd render
pure $ pure $
(\(DocumentsView r) -> (\(DocumentsView r) ->
{ row: { row:
[ div [className $ fa r.fav <> "fa-star"] [] [ div []
[ a [className $ fa r.fav <> "fa-star" ,onClick $ (\_-> dispatch $ (SendFavorites r._id))] []
]
-- TODO show date: Year-Month-Day only -- TODO show date: Year-Month-Day only
, text r.date , text r.date
, a [ href (toUrl Front Url_Document r._id) ] [ text r.title ] , a [ href (toUrl Front Url_Document r._id) ] [ text r.title ]
, text r.source , text r.source
, input [ _type "checkbox"] , input [ _type "checkbox", onClick $ (\_ -> dispatch $ (DeleteDocuments r._id))]
] ]
, delete: false , delete: true
}) <$> res }) <$> res
fa true = "fas " fa true = "fas "
fa false = "far " fa false = "far "
...@@ -227,3 +280,79 @@ instance encodeJsonSQuery :: EncodeJson SearchQuery where ...@@ -227,3 +280,79 @@ instance encodeJsonSQuery :: EncodeJson SearchQuery where
searchResults :: SearchQuery -> Aff Int searchResults :: SearchQuery -> Aff Int
searchResults squery = post "http://localhost:8008/count" unit searchResults squery = post "http://localhost:8008/count" unit
-- TODO -- TODO
newtype FavoriteQuery = FavoriteQuery
{ favorites :: Array Int
}
instance encodeJsonFQuery :: EncodeJson FavoriteQuery where
encodeJson (FavoriteQuery post)
= "favorites" := post.favorites
~> jsonEmptyObject
newtype DeleteDocumentQuery = DeleteDocumentQuery
{
documents :: Array Int
}
instance encodeJsonDDQuery :: EncodeJson DeleteDocumentQuery where
encodeJson (DeleteDocumentQuery post)
= "documents" := post.documents
~> jsonEmptyObject
favorites :: Int -> FavoriteQuery -> Aff (Either String (Array Int))
favorites nodeId reqbody= do
res <- request $ defaultRequest
{ url = "http://localhost:8008/api/v1.0/node/"<>show nodeId <>"/favorites"
, responseFormat = ResponseFormat.json
, method = Left PUT
, headers = []
, content = Just $ Json $ encodeJson reqbody
}
case res.body of
Left err -> do
_ <- liftEffect $ log $ printResponseFormatError err
pure $ Left $ printResponseFormatError err
Right json -> do
let obj = decodeJson json
pure obj
deleteFavorites :: Int -> FavoriteQuery -> Aff (Either String (Array Int))
deleteFavorites nodeId reqbody= do
res <- request $ defaultRequest
{ url = "http://localhost:8008/api/v1.0/node/"<>show nodeId<>"/favorites"
, responseFormat = ResponseFormat.json
, method = Left DELETE
, headers = []
, content = Just $ Json $ encodeJson reqbody
}
case res.body of
Left err -> do
_ <- liftEffect $ log $ printResponseFormatError err
pure $ Left $ printResponseFormatError err
Right json -> do
let obj = decodeJson json
pure obj
deleteDocuments :: Int -> DeleteDocumentQuery -> Aff (Either String Unit)
deleteDocuments ddid reqbody= do
res <- request $ defaultRequest
{ url = "http://localhost:8008/api/v1.0/annuaire/"<>show ddid<>"/documents"
, responseFormat = ResponseFormat.json
, method = Left DELETE
, headers = []
, content = Just $ Json $ encodeJson reqbody
}
case res.body of
Left err -> do
_ <- liftEffect $ log $ printResponseFormatError err
pure $ Left $ printResponseFormatError err
Right json -> do
-- let obj = decodeJson json
pure $ Right unit
...@@ -14,7 +14,11 @@ type State = ...@@ -14,7 +14,11 @@ type State =
initialState :: State initialState :: State
initialState = initialState =
{ docsView : {} { docsView :
{ documents : D.sampleData'
, deleteRows : false
, deleteRowId : 1
}
, ngramsView : {} -- N.initialState , ngramsView : {} -- N.initialState
, activeTab : 0 , activeTab : 0
} }
......
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