Commit 1832703a authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[Graph] zero-padded publication dates (with no time)

Also, bump up purescript-spec-discover to 4.0.0 and make tests run.
parent a1870bf8
......@@ -2729,7 +2729,7 @@
"node-fs"
],
"repo": "https://github.com/purescript-spec/purescript-spec-discovery",
"version": "v3.1.0"
"version": "v4.0.0"
},
"spec-quickcheck": {
"dependencies": [
......
......@@ -8,7 +8,8 @@
"sass": "sass dist/styles/",
"dev": "webpack-dev-server --env dev --mode development",
"repl": "pulp --psc-package repl",
"clean": "rm -Rf output"
"clean": "rm -Rf output",
"test": "pulp test"
},
"dependencies": {
"@babel/polyfill": "^7.0.0",
......
......@@ -156,7 +156,7 @@ let additions =
mkPackage
[ "prelude", "effect", "arrays", "spec", "node-fs" ]
"https://github.com/purescript-spec/purescript-spec-discovery"
"v3.1.0"
"v4.0.0"
, spec-quickcheck =
mkPackage
[ "prelude", "aff", "random", "quickcheck", "spec" ]
......
......@@ -26,7 +26,7 @@ import Gargantext.Routes (SessionRoute(Search, NodeAPI))
import Gargantext.Routes as Routes
import Gargantext.Sessions (Session, sessionId, post, deleteWithBody)
import Gargantext.Types (NodeType(..), OrderBy(..), NodePath(..))
import Gargantext.Utils (toggleSet)
import Gargantext.Utils (toggleSet, zeroPad)
import Gargantext.Utils.DecodeMaybe ((.|))
------------------------------------------------------------------------
......@@ -89,8 +89,15 @@ newtype DocumentsView =
, pairs :: Array Pair
, delete :: Boolean
, category :: Category
, publication_year :: Int
, publication_month :: Int
, publication_day :: Int
}
publicationDate :: DocumentsView -> String
publicationDate (DocumentsView {publication_year, publication_month, publication_day}) =
(zeroPad 2 publication_year) <> "-" <> (zeroPad 2 publication_month) <> "-" <> (zeroPad 2 publication_day)
derive instance genericDocumentsView :: Generic DocumentsView _
instance showDocumentsView :: Show DocumentsView where
......@@ -111,6 +118,9 @@ newtype Hyperdata = Hyperdata
{ authors :: String
, title :: String
, source :: String
, publication_year :: Int
, publication_month :: Int
, publication_day :: Int
}
--instance decodeHyperdata :: DecodeJson Hyperdata where
......@@ -133,7 +143,10 @@ instance decodeHyperdata :: DecodeJson Hyperdata where
authors <- obj .| "authors"
title <- obj .| "title"
source <- obj .| "source"
pure $ Hyperdata { authors, title,source }
publication_year <- obj .: "publication_year"
publication_month <- obj .: "publication_month"
publication_day <- obj .: "publication_day"
pure $ Hyperdata { authors, title, source, publication_year, publication_month, publication_day }
{-
instance decodeResponse :: DecodeJson Response where
......@@ -250,8 +263,20 @@ loadPage {session, nodeId, listId, query, params: {limit, offset, orderBy}} = do
where
res2corpus :: Response -> DocumentsView
res2corpus (Response { id, created: date, ngramCount: score, category
, hyperdata: Hyperdata {authors, title, source} }) =
DocumentsView { id, date, title, source, score, authors, category, pairs: [], delete: false }
, hyperdata: Hyperdata {authors, title, source, publication_year, publication_month, publication_day} }) =
DocumentsView { id
, date
, title
, source
, score
, authors
, category
, pairs: []
, delete: false
, publication_year
, publication_month
, publication_day
}
convOrderBy (T.ASC (T.ColumnName "Date")) = DateAsc
convOrderBy (T.DESC (T.ColumnName "Date")) = DateDesc
convOrderBy (T.ASC (T.ColumnName "Title")) = TitleAsc
......@@ -308,11 +333,11 @@ pageCpt = R.hooksComponent "G.C.FacetsTable.Page" cpt
url frontends $ Routes.CorpusDocument (sessionId session) nodeId listId id
comma = H.span {} [ H.text ", " ]
rows = row <$> filter (not <<< isDeleted) documents
row dv@(DocumentsView {id,score,title,source,date, authors,pairs,delete,category}) =
row dv@(DocumentsView {id, score, title, source, authors, pairs, delete, category}) =
{ row:
[ H.div {} [ H.a { className: gi category, on: {click: markClick} } [] ]
-- TODO show date: Year-Month-Day only
, maybeStricken delete [ H.text date ]
, maybeStricken delete [ H.text $ publicationDate dv ]
, maybeStricken delete [ H.a {target: "_blank", href: documentUrl id} [ H.text title ] ]
, maybeStricken delete [ H.text source ]
, maybeStricken delete [ H.text authors ]
......
......@@ -84,7 +84,6 @@ controlsCpt = R.hooksComponent "GraphControls" cpt
Graph.Init -> R.setRef mFAPauseRef Nothing
_ -> pure unit
--R.useEffect $ handleForceAtlasPause props.sigmaRef localControls.pauseForceAtlas mFAPauseRef
R.useEffect' $ Sigmax.handleForceAtlas2Pause props.sigmaRef localControls.pauseForceAtlas (get1 localControls.showEdges) mFAPauseRef
R.useEffectOnce' $ do
......
module Gargantext.Components.Nodes.Corpus.Document where
import Prelude (class Show, bind, identity, mempty, pure, ($))
import Prelude (class Show, bind, identity, mempty, pure, ($), (<>))
import Data.Argonaut (class DecodeJson, decodeJson, (.:), (.:?))
import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Show (genericShow)
......@@ -23,6 +23,7 @@ import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Routes (SessionRoute(..))
import Gargantext.Sessions (Session, get)
import Gargantext.Types (CTabNgramType(..), NodeType(..), TabSubType(..), TabType(..), TermList, ScoreType(..))
import Gargantext.Utils as U
import Gargantext.Utils.Reactix as R2
type DocPath =
......@@ -143,6 +144,12 @@ data Document
--, text :: Maybe String
}
publicationDate :: Document -> String
publicationDate (Document doc@{publication_year: Nothing}) = ""
publicationDate (Document doc@{publication_year: Just py, publication_month: Nothing}) = U.zeroPad 2 py
publicationDate (Document doc@{publication_year: Just py, publication_month: Just pm, publication_day: Nothing}) = (U.zeroPad 2 py) <> "-" <> (U.zeroPad 2 pm)
publicationDate (Document doc@{publication_year: Just py, publication_month: Just pm, publication_day: Just pd}) = (U.zeroPad 2 py) <> "-" <> (U.zeroPad 2 pm) <> "-" <> (U.zeroPad 2 pd)
defaultNodeDocument :: NodeDocument
defaultNodeDocument =
NodePoly { id : 0
......@@ -322,7 +329,7 @@ docViewSpec = simpleSpec performAction render
, li' [ span [] [text' doc.authors]
, badge "authors"
]
, li' [ span [] [text' doc.publication_date]
, li' [ span [] [text $ publicationDate $ Document doc]
, badge "date"
]
]
......
......@@ -5,6 +5,8 @@ import Data.Lens (Lens', lens)
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
......@@ -57,5 +59,18 @@ 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)
where
numDigits = length $ show num
zeros = if numDigits < pad then zeros' (pad - numDigits) else ""
zeros' 0 = ""
zeros' n = "0" <> (zeros' (n - 1))
module Gargantext.Utils.Spec where
import Prelude
import Data.Array (index)
import Data.Foldable (all)
import Data.Maybe (Maybe(..), isJust)
import Data.String (drop, stripPrefix, Pattern(..))
import Data.Tuple (Tuple(..))
import Gargantext.Utils as U
-- import Test.QuickCheck ((===), (/==), (<?>), Result(..))
import Test.Spec (Spec, describe, it)
import Test.Spec.Assertions (shouldEqual)
import Test.Spec.QuickCheck (quickCheck')
spec :: Spec Unit
spec =
describe "G.Utils" do
it "zeroPad 1 works" do
U.zeroPad 1 0 `shouldEqual` "0"
U.zeroPad 1 1 `shouldEqual` "1"
U.zeroPad 1 10 `shouldEqual` "10"
it "zeroPad 2 works" do
U.zeroPad 2 0 `shouldEqual` "00"
U.zeroPad 2 1 `shouldEqual` "01"
U.zeroPad 2 10 `shouldEqual` "10"
U.zeroPad 2 100 `shouldEqual` "100"
it "zeroPad 3 works" do
U.zeroPad 3 0 `shouldEqual` "000"
U.zeroPad 3 1 `shouldEqual` "001"
U.zeroPad 3 10 `shouldEqual` "010"
U.zeroPad 3 99 `shouldEqual` "099"
U.zeroPad 3 100 `shouldEqual` "100"
U.zeroPad 3 101 `shouldEqual` "101"
U.zeroPad 3 1000 `shouldEqual` "1000"
it "log10 10" do
U.log10 10.0 `shouldEqual` 1.0
......@@ -5,7 +5,9 @@ import Effect (Effect)
import Effect.Aff (launchAff_)
import Test.Spec.Discovery (discover)
import Test.Spec.Reporter.Console (consoleReporter)
import Test.Spec.Runner (run)
import Test.Spec.Runner (runSpec)
main :: Effect Unit
main = discover "Gargantext\\..*Spec" >>= run [consoleReporter] >>> launchAff_
main = launchAff_ do
specs <- discover "Gargantext\\..*Spec"
runSpec [consoleReporter] specs
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