[utils] fix nonemptyIntercalate

parent 79b7fa9c
Pipeline #7107 passed with stages
in 47 minutes and 29 seconds
......@@ -17,7 +17,7 @@ import Data.LanguageCodes qualified as ISO639
import Data.Map.Strict qualified as Map
import Data.Text (pack)
import Gargantext.Core.Text.Corpus.Parsers.Date qualified as Date
import Gargantext.Core.Utils (nonemptyJoin)
import Gargantext.Core.Utils (nonemptyIntercalate)
import Gargantext.Database.Admin.Types.Hyperdata.Document ( HyperdataDocument(..) )
import Gargantext.Defaults qualified as Defaults
import Gargantext.Prelude hiding (intercalate)
......@@ -53,8 +53,8 @@ toDoc' la (HAL.Document { .. }) = do
, _hd_url = Nothing
, _hd_page = Nothing
, _hd_title = Just $ unwords _document_title
, _hd_authors = Just $ nonemptyJoin ", " _document_authors_names
, _hd_institutes = Just $ nonemptyJoin ", " $ zipWith (\affialition structId -> affialition <> " | " <> structId) _document_authors_affiliations $ map show _document_struct_id
, _hd_authors = Just $ nonemptyIntercalate ", " _document_authors_names
, _hd_institutes = Just $ nonemptyIntercalate ", " $ zipWith (\affialition structId -> affialition <> " | " <> structId) _document_authors_affiliations $ map show _document_struct_id
, _hd_source = Just $ maybe "Nothing" identity _document_source
, _hd_abstract = Just abstract
, _hd_publication_date = fmap show utctime
......
......@@ -19,7 +19,7 @@ module Gargantext.Core.Text.Corpus.Parsers.JSON.Istex where
import Data.Text qualified as T
import Gargantext.Core (Lang(..))
import Gargantext.Core.Text.Corpus.Parsers.Date qualified as Date
import Gargantext.Core.Utils (nonemptyJoin)
import Gargantext.Core.Utils (nonemptyIntercalate)
import Gargantext.Database.Admin.Types.Hyperdata.Document (HyperdataDocument(..))
import Gargantext.Defaults qualified as Defaults
import Gargantext.Prelude hiding (length)
......@@ -39,9 +39,9 @@ toDoc la (ISTEX.Document i t a ab d s) = do
, _hd_url = Nothing
, _hd_page = Nothing
, _hd_title = t
, _hd_authors = Just $ nonemptyJoin ", " (map ISTEX._author_name a)
, _hd_institutes = Just $ nonemptyJoin ", " (concatMap ISTEX._author_affiliations a)
, _hd_source = Just $ nonemptyJoin ", " $ maybeToList $ join (ISTEX._source_title <$> s)
, _hd_authors = Just $ nonemptyIntercalate ", " (map ISTEX._author_name a)
, _hd_institutes = Just $ nonemptyIntercalate ", " (concatMap ISTEX._author_affiliations a)
, _hd_source = Just $ nonemptyIntercalate ", " $ maybeToList $ join (ISTEX._source_title <$> s)
, _hd_abstract = ab
, _hd_publication_date = fmap (T.pack . show) utctime
, _hd_publication_year = pub_year
......
......@@ -23,7 +23,7 @@ module Gargantext.Core.Utils (
, addTuples
, (?!)
, (?|)
, nonemptyJoin
, nonemptyIntercalate
) where
import Data.List qualified as List
......@@ -91,9 +91,6 @@ infixr 4 ?|
(?|) = flip fromMaybe
-- | Join strings, but only nonempty ones
nonemptyJoin :: Text -> [Text] -> Text
nonemptyJoin _sep [] = ""
nonemptyJoin _sep [x] = x
nonemptyJoin sep ("":xs) = nonemptyJoin sep xs
nonemptyJoin sep (x:xs) = x <> sep <> (nonemptyJoin sep xs)
-- | Intercalate strings, but only nonempty ones
nonemptyIntercalate :: Text -> [Text] -> Text
nonemptyIntercalate sep xs = T.intercalate sep $ filter (/= "") xs
......@@ -21,11 +21,11 @@ test = do
describe "check if groupWithCounts works" $ do
it "simple integer array" $ groupWithCounts testArray `shouldBe` groupedArray
it "string" $ groupWithCounts testString `shouldBe` groupedString
describe "check nonemptyJoin" $ do
it "empty list" $ nonemptyJoin "," [] `shouldBe` ""
it "simple list" $ nonemptyJoin "," ["x"] `shouldBe` "x"
it "two-element list" $ nonemptyJoin "," ["x", "y"] `shouldBe` "x,y"
it "with empty strings" $ nonemptyJoin "," ["a", "", "b", "", "c", ""] `shouldBe` "a,b,c"
describe "check nonemptyIntercalate" $ do
it "empty list" $ nonemptyIntercalate "," [] `shouldBe` ""
it "simple list" $ nonemptyIntercalate "," ["x"] `shouldBe` "x"
it "two-element list" $ nonemptyIntercalate "," ["x", "y"] `shouldBe` "x,y"
it "with empty strings" $ nonemptyIntercalate "," ["a", "", "b", "", "c", ""] `shouldBe` "a,b,c"
where
testArray :: [Int]
testArray = [1, 2, 3, 1, 2, 3]
......
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