Commit a6ee9c07 authored by Alexandre Delanoë's avatar Alexandre Delanoë

Merge branch 'dev-warnings-cleanup' of...

Merge branch 'dev-warnings-cleanup' of ssh://gitlab.iscpif.fr:20022/gargantext/purescript-gargantext into dev
parents 1b88dd0f 0d626b03
......@@ -179,7 +179,6 @@ _localCategories = prop (SProxy :: SProxy "localCategories")
data Action
= MarkCategory Int Category
newtype DocumentsView
= DocumentsView
{ _id :: Int
......@@ -329,22 +328,24 @@ type PageParams =
, query :: Query
, params :: T.Params}
loadPage :: Session -> PageParams -> Aff (Array DocumentsView)
loadPage :: Session -> PageParams -> Aff (Tuple Int (Array DocumentsView))
loadPage session {nodeId, tabType, query, listId, corpusId, params: {limit, offset, orderBy}} = do
liftEffect $ log3 "loading documents page: loadPage with Offset and limit" offset limit
-- res <- get $ toUrl endConfigStateful Back (Tab tabType offset limit (convOrderBy <$> orderBy)) (Just nodeId)
let p = NodeAPI Node (Just nodeId) "table"
res <- post session p $ TabPostQuery {
res <- (post session p $ TabPostQuery {
offset
, limit
, orderBy: convOrderBy orderBy
, tabType
, query
}
let docs = res2corpus <$> res
}) :: Aff {count :: Int, docs :: Array Response}
let docs = res2corpus <$> res.docs
pure $
if mock then take limit $ drop offset sampleData else
docs
if mock then
Tuple 4737 (take limit $ drop offset sampleData)
else
Tuple res.count docs
where
res2corpus :: Response -> DocumentsView
res2corpus (Response r) =
......@@ -374,7 +375,8 @@ pageLayoutCpt = R.memo' $ R.staticComponent "G.C.DocsTable.pageLayout" cpt where
loader path (loadPage session) paint
where
path = {nodeId, listId, corpusId, tabType, query, params: fst params}
paint loaded = page params props loaded
paint (Tuple count docs) = page params (newProps count) docs
newProps count = props { totalRecords = count }
type PageProps =
( params :: R.State T.Params
......
......@@ -35,8 +35,7 @@ tab :: Frontends -> Session -> TextQuery -> GraphSideCorpus -> Tuple String R.El
tab frontends session query (GraphSideCorpus {corpusId: nodeId, corpusLabel, listId}) =
Tuple corpusLabel (docView dvProps)
where
dvProps = {frontends, session, nodeId, listId, query, chart, totalRecords: 4736, container}
-- TODO totalRecords: probably need to insert a corpusLoader.
dvProps = {frontends, session, nodeId, listId, query, chart, totalRecords: 0, container}
chart = mempty
container = T.graphContainer {title: corpusLabel}
......@@ -2,8 +2,8 @@ module Gargantext.Types where
import Prelude
import Data.Argonaut ( class DecodeJson, decodeJson, class EncodeJson, encodeJson, (:=), (~>), jsonEmptyObject)
import Data.Maybe (Maybe(..), maybe)
import Data.Either (Either(..))
import Data.Maybe (Maybe(..), maybe)
import Prim.Row (class Union)
import URI.Query (Query)
import Data.Generic.Rep (class Generic)
......
......@@ -6,7 +6,6 @@ import Data.Newtype (class Newtype, unwrap, wrap)
import Data.Set as Set
import Data.Set (Set)
import Data.String (length)
import Math (log)
-- | Astonishingly, not in the prelude
id :: forall a. a -> a
......@@ -59,13 +58,6 @@ glyphicon t = "btn glyphitem glyphicon glyphicon-" <> t
glyphiconActive :: String -> Boolean -> String
glyphiconActive icon b = glyphicon icon <> if b then " active" else ""
-- | Logarithm with given base
logb :: Number -> Number -> Number
logb base n = (log n) / (log base)
log10 :: Number -> Number
log10 = logb 10.0
-- | Format a number with specified amount of zero-padding
zeroPad :: Int -> Int -> String
zeroPad pad num = zeros <> (show num)
......
......@@ -5,3 +5,10 @@ import Math as Math
roundToMultiple :: Number -> Number -> Number
roundToMultiple eps num = eps * Math.round (num / eps)
-- | Logarithm with given base
logb :: Number -> Number -> Number
logb base n = (Math.log n) / (Math.log base)
log10 :: Number -> Number
log10 = logb 10.0
......@@ -7,6 +7,7 @@ import Data.Maybe (Maybe(..), isJust)
import Data.String (drop, stripPrefix, Pattern(..))
import Data.Tuple (Tuple(..))
import Gargantext.Utils as U
import Gargantext.Utils.Math as UM
-- import Test.QuickCheck ((===), (/==), (<?>), Result(..))
import Test.Spec (Spec, describe, it)
import Test.Spec.Assertions (shouldEqual)
......@@ -33,4 +34,4 @@ spec =
U.zeroPad 3 101 `shouldEqual` "101"
U.zeroPad 3 1000 `shouldEqual` "1000"
it "log10 10" do
U.log10 10.0 `shouldEqual` 1.0
UM.log10 10.0 `shouldEqual` 1.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