Pārlūkot izejas kodu

Improve dotSeparated to return a non empty list of non empty strings

jherve 1 gadu atpakaļ
vecāks
revīzija
2c5308974d

+ 6 - 3
src/LinkedIn/Jobs/JobOffer.purs

@@ -7,7 +7,10 @@ import Data.Argonaut.Encode.Generic (genericEncodeJson)
 import Data.Either (Either, note)
 import Data.Generic.Rep (class Generic)
 import Data.Lens (findOf)
+import Data.List (List(..), (:))
+import Data.List.Types (NonEmptyList(..))
 import Data.Maybe (Maybe(..), isJust)
+import Data.NonEmpty ((:|))
 import Data.Show.Generic (genericShow)
 import LinkedIn.UI.Basic.Types (JobFlexibility)
 import LinkedIn.UI.Components.JobsUnifiedTopCard (JobsUnifiedTopCardElement, TopCardInsight(..), TopCardInsightContent(..), _top_to_action_buttons, _top_to_insights, toHeader, toPrimaryDescriptionLink, toPrimaryDescriptionText)
@@ -84,17 +87,17 @@ extractCompanyLink = case _ of
 
 extractCompanyDomain ∷ TopCardInsight UIElement → Maybe String
 extractCompanyDomain = case _ of
-  TopCardInsight {content: TopCardInsightContentSingle (UIElement (UIStringDotSeparated _ (UIStringPlain str)))} -> Just str
+  TopCardInsight {content: TopCardInsightContentSingle (UIElement (UIStringDotSeparated (NonEmptyList (_ :| (UIStringPlain str) : _))))} -> Just str
   _ -> Nothing
 
 extractCompanySize ∷ TopCardInsight UIElement → Maybe String
 extractCompanySize = case _ of
-  TopCardInsight {content: TopCardInsightContentSingle (UIElement (UIStringDotSeparated (UIStringPlain str) _))} -> Just str
+  TopCardInsight {content: TopCardInsightContentSingle (UIElement (UIStringDotSeparated (NonEmptyList(UIStringPlain str :| _))))} -> Just str
   _ -> Nothing
 
 extractLocation :: UIElement -> Maybe String
 extractLocation = case _ of
-  UIElement (UIStringDotSeparated _ (UIStringPlain str)) -> Just str
+  UIElement (UIStringDotSeparated (NonEmptyList ((UIStringPlain str) :| Nil))) -> Just str
   _ -> Nothing
 
 extractJobRemote :: TopCardInsight UIElement -> Maybe JobFlexibility

+ 3 - 1
src/LinkedIn/Profile/Project.purs

@@ -7,6 +7,8 @@ import Data.Argonaut.Encode.Generic (genericEncodeJson)
 import Data.Either (Either, note)
 import Data.Generic.Rep (class Generic)
 import Data.List as L
+import Data.List.Types (NonEmptyList(..))
+import Data.NonEmpty ((:|))
 import Data.Maybe (Maybe(..))
 import Data.Show.Generic (genericShow)
 import LinkedIn.UI.Basic.Types (TimeSpan)
@@ -49,7 +51,7 @@ extractName = case _ of
 extractTimeSpan ∷ UIElement → Maybe TimeSpan
 extractTimeSpan = case _ of
   UIElement (UIStringTimeSpan s) -> Just s
-  UIElement (UIStringDotSeparated (UIStringTimeSpan s) _) -> Just s
+  UIElement (UIStringDotSeparated (NonEmptyList(UIStringTimeSpan s :| _))) -> Just s
   _ -> Nothing
 
 extractDescription ∷ UIElement → Maybe String

+ 7 - 4
src/LinkedIn/Profile/WorkExperience.purs

@@ -7,8 +7,11 @@ import Data.Argonaut.Encode.Generic (genericEncodeJson)
 import Data.Either (Either, note)
 import Data.Foldable (findMap)
 import Data.Generic.Rep (class Generic)
+import Data.List ((:))
 import Data.List as L
+import Data.List.Types (NonEmptyList(..))
 import Data.Maybe (Maybe(..))
+import Data.NonEmpty ((:|))
 import Data.Show.Generic (genericShow)
 import LinkedIn.UI.Basic.Types (Duration, TimeSpan)
 import LinkedIn.UI.Components.ArtDecoCard (ArtDecoCardElement, toCenterContent, toHeaderBold, toHeaderLight, toHeaderNormal)
@@ -57,23 +60,23 @@ extractPosition = case _ of
 extractCompany ∷ UIElement → Maybe String
 extractCompany = case _ of
   UIElement (UIStringPlain str) -> Just str
-  UIElement (UIStringDotSeparated (UIStringPlain str) _) -> Just str
+  UIElement (UIStringDotSeparated (NonEmptyList(UIStringPlain str :| _))) -> Just str
   _ -> Nothing
 
 extractContractType ∷ UIElement → Maybe String
 extractContractType = case _ of
-  UIElement (UIStringDotSeparated _ (UIStringPlain str)) -> Just str
+  UIElement (UIStringDotSeparated (NonEmptyList(_ :| UIStringPlain str : _))) -> Just str
   _ -> Nothing
 
 extractTimeSpan ∷ UIElement → Maybe TimeSpan
 extractTimeSpan = case _ of
   UIElement (UIStringTimeSpan s) -> Just s
-  UIElement (UIStringDotSeparated (UIStringTimeSpan s) _) -> Just s
+  UIElement (UIStringDotSeparated (NonEmptyList(UIStringTimeSpan s :| _))) -> Just s
   _ -> Nothing
 
 extractDuration ∷ UIElement → Maybe Duration
 extractDuration = case _ of
-  UIElement (UIStringDotSeparated _ (UIStringDuration d)) -> Just d
+  UIElement (UIStringDotSeparated (NonEmptyList(_ :| UIStringDuration d : _))) -> Just d
   _ -> Nothing
 
 extractDescription ∷ UIElement → Maybe String

+ 11 - 5
src/LinkedIn/UI/Basic/Parser.purs

@@ -20,7 +20,7 @@ import Data.Tuple (Tuple(..))
 import LinkedIn.UI.Basic.Types (Duration(..), JobFlexibility(..), MonthYear(..), MonthYearOrToday(..), TimeSpan(..))
 import Parsing (Parser, ParserT, fail)
 import Parsing.Combinators (choice, try)
-import Parsing.String (char, rest, string)
+import Parsing.String (char, string)
 import Parsing.String.Basic (intDecimal, number, space, takeWhile)
 
 monthStrToMonth :: Map String Month
@@ -153,8 +153,14 @@ sepBy2 p sep = do
 commaSeparated ∷ Parser String (NonEmptyList String)
 commaSeparated = stringWithoutCommaP `sepBy2` commaP
 
-medianDotSeparated ∷ Parser String (Tuple String String)
+medianDotSeparated ∷ Parser String (NonEmptyList String)
 medianDotSeparated = do
-  a0 <- stringWithoutMedianDotP
-  a1 <- medianDotP *> rest
-  pure $ Tuple (S.trim a0) (S.trim a1)
+  strings <- stringWithoutMedianDotP `sepBy2` medianDotP
+  case  NEL.fromList $ NEL.mapMaybe toMaybeTrimmedNotEmpty strings of
+    Nothing -> fail "Nope"
+    Just strings' -> pure strings'
+
+  where
+    toMaybeTrimmedNotEmpty s = case S.trim s of
+      "" -> Nothing
+      s' -> Just s'

+ 4 - 5
src/LinkedIn/UI/Strings/Parser.purs

@@ -4,7 +4,7 @@ import Prelude
 
 import Control.Alt ((<|>))
 import Data.Either (hush)
-import Data.Tuple (Tuple(..))
+import Data.Traversable (traverse)
 import LinkedIn.UI.Basic.Parser (durationP, jobFlexP, medianDotSeparated, timeSpanP)
 import LinkedIn.UI.Strings.Types (UIString(..))
 import Parsing (Parser, liftMaybe, runParser)
@@ -21,16 +21,15 @@ uiStringWithoutMedianDotP = do
 
 uiStringdotSeparatedP ∷ Parser String UIString
 uiStringdotSeparatedP = do
-  Tuple s1 s2 <- medianDotSeparated
+  stringsNel <- medianDotSeparated
 
   let
     intoUiElement :: String -> Parser String UIString
     intoUiElement s = liftMaybe (\_ -> "could not convert to ui element") $ hush $ runParser s uiStringSingleP
 
-  s1' <- intoUiElement s1
-  s2' <- intoUiElement s2
+  stringsNel' <- traverse intoUiElement stringsNel
 
-  pure $ UIStringDotSeparated s1' s2'
+  pure $ UIStringDotSeparated stringsNel'
 
 uiStringSingleP ∷ Parser String UIString
 uiStringSingleP = (try uiStringDurationP) <|> (try uiStringTimeSpanP) <|> (try uiStringJobFlexP) <|> uiStringPlainP

+ 2 - 2
src/LinkedIn/UI/Strings/Types.purs

@@ -3,6 +3,7 @@ module LinkedIn.UI.Strings.Types where
 import Prelude
 
 import Data.Generic.Rep (class Generic)
+import Data.List.Types (NonEmptyList)
 import Data.Show.Generic (genericShow)
 import LinkedIn.UI.Basic.Types (Duration, JobFlexibility, TimeSpan)
 
@@ -11,10 +12,9 @@ data UIString =
   | UIStringTimeSpan TimeSpan
   | UIStringJobFlex JobFlexibility
   | UIStringPlain String
-  | UIStringDotSeparated UIString UIString
+  | UIStringDotSeparated (NonEmptyList UIString)
 
 derive instance Eq UIString
 derive instance Generic UIString _
 instance Show UIString where
-  show (UIStringDotSeparated ui1 ui2) = "(UIStringDotSeparated " <> show ui1 <> show ui2 <> ")"
   show u = genericShow u

+ 1 - 1
test/JobsUnifiedTopCard.purs

@@ -179,7 +179,7 @@ jobOfferPage_3797662873 = {
     companySize: Just "1 001-5 000 employés",
     flexibility: Just JobFlexHybrid,
     hasSimplifiedApplicationProcess: true,
-    location: (Just "Paris et périphérie ·"),
+    location: (Just "Paris et périphérie"),
     title: "Data Engineer Confirmé(e)/Senior (CDI)"
   })
 }

+ 15 - 5
test/UIStringParser.purs

@@ -4,7 +4,10 @@ import Prelude
 
 import Data.Date (Month(..))
 import Data.Either (Either(..))
-import LinkedIn.UI.Basic.Parser (durationP, monthYearP, timeSpanP)
+import Data.List (List(..), (:))
+import Data.List.Types (NonEmptyList(..))
+import Data.NonEmpty (NonEmpty(..))
+import LinkedIn.UI.Basic.Parser (durationP, medianDotSeparated, monthYearP, timeSpanP)
 import LinkedIn.UI.Basic.Types (Duration(..), TimeSpan(..))
 import LinkedIn.UI.Strings.Parser (uiStringDurationP, uiStringdotSeparatedP)
 import LinkedIn.UI.Strings.Types (UIString(..))
@@ -39,6 +42,16 @@ uiStringParserSpec = do
       run "3 ans" `shouldEqual` Right(Years 3)
       run "1 an" `shouldEqual` Right(Years 1)
 
+  describe "dot separated strings parser" do
+    let run s = runParser s medianDotSeparated
+
+    it "works" do
+      run "some text 1 · some text 2" `shouldEqual` Right(NonEmptyList(NonEmpty "some text 1" ("some text 2" : Nil)))
+      run "· some text after a dot" `shouldEqual` Right(NonEmptyList(NonEmpty "some text after a dot" Nil))
+      run "some text before a dot ·" `shouldEqual` Right(NonEmptyList(NonEmpty "some text before a dot" Nil))
+      run "string with no dot" `shouldEqual` (Left (ParseError "Expected '•'" (Position { column: 19, index: 18, line: 1 })))
+      run "· some text in between dots ·" `shouldEqual` Right(NonEmptyList(NonEmpty "some text in between dots" Nil))
+
   describe "UI duration parser" do
     let run s = runParser s uiStringDurationP
 
@@ -49,7 +62,4 @@ uiStringParserSpec = do
     let run s = runParser s uiStringdotSeparatedP
 
     it "works" do
-      run "some text 1 · some text 2" `shouldEqual` Right(UIStringDotSeparated (UIStringPlain "some text 1") (UIStringPlain "some text 2"))
-      run "· some text after a dot" `shouldEqual` Right(UIStringDotSeparated (UIStringPlain "") (UIStringPlain "some text after a dot"))
-      run "some text before a dot ·" `shouldEqual` Right(UIStringDotSeparated (UIStringPlain "some text before a dot") (UIStringPlain ""))
-      run "string with no dot" `shouldEqual` (Left (ParseError "Expected '•'" (Position { column: 19, index: 18, line: 1 })))
+      run "some text 1 · some text 2" `shouldEqual` Right(UIStringDotSeparated (NonEmptyList(NonEmpty (UIStringPlain "some text 1") ((UIStringPlain "some text 2") : Nil))))