Forráskód Böngészése

Change Maybe NonEmptyList to List

jherve 1 éve
szülő
commit
ddb999d270

+ 5 - 1
src/LinkedIn/CanBeQueried.purs

@@ -2,9 +2,10 @@ module LinkedIn.CanBeQueried where
 
 import Prelude
 
+import Data.List (List)
 import Data.List.Types (NonEmptyList)
 import Data.Traversable (traverse)
-import LinkedIn.QueryRunner (Query, queryAll, queryOne)
+import LinkedIn.QueryRunner (Query, queryAll, queryAll', queryOne)
 import LinkedIn.Queryable (class Queryable)
 import Web.DOM (Node)
 
@@ -16,3 +17,6 @@ subQueryOne selector n = query =<< queryOne selector n
 
 subQueryMany ∷ ∀ q t. CanBeQueried Node t ⇒ Queryable q ⇒ String → Query q (NonEmptyList (t Node))
 subQueryMany selector n = traverse query =<< queryAll selector n
+
+subQueryMany' ∷ ∀ q t. CanBeQueried Node t ⇒ Queryable q ⇒ String → Query q (List (t Node))
+subQueryMany' selector n = traverse query =<< queryAll' selector n

+ 7 - 2
src/LinkedIn/QueryRunner.purs

@@ -8,11 +8,11 @@ import Data.Argonaut.Encode.Generic (genericEncodeJson)
 import Data.Array as A
 import Data.Either (Either(..), note)
 import Data.Generic.Rep (class Generic)
-import Data.List.Types (NonEmptyList)
+import Data.List.Types (List, NonEmptyList)
 import Data.Maybe (Maybe(..))
 import Data.Show.Generic (genericShow)
 import Effect (Effect)
-import LinkedIn.Queryable (class Queryable, getChildrenArray, queryAllNodes, queryOneNode, toNode)
+import LinkedIn.Queryable (class Queryable, getChildrenArray, queryAllNodes, queryAllNodes', queryOneNode, toNode)
 import Web.DOM (Node)
 import Web.DOM.Text as T
 
@@ -76,3 +76,8 @@ queryAll ∷ forall q. Queryable q => String → Query q (NonEmptyList Node)
 queryAll selector node = ExceptT $ do
   maybeNodes <- queryAllNodes selector node
   pure $ note (QNodeListNotFoundError selector) maybeNodes
+
+queryAll' ∷ forall q. Queryable q => String → Query q (List Node)
+queryAll' selector node = ExceptT $ do
+  nodes <- queryAllNodes' selector node
+  pure $ Right nodes

+ 9 - 0
src/LinkedIn/Queryable.purs

@@ -2,9 +2,12 @@ module LinkedIn.Queryable where
 
 import Prelude
 
+import Data.List (List)
+import Data.List as L
 import Data.List.NonEmpty (NonEmptyList)
 import Data.List.NonEmpty as NEL
 import Data.Maybe (Maybe(..), fromJust)
+import Data.Traversable (traverse)
 import Effect (Effect)
 import Partial.Unsafe (unsafePartial)
 import Web.DOM (Document, Node, ParentNode)
@@ -47,6 +50,12 @@ queryAllNodes selector n = do
   found <- querySelectorAll (QuerySelector selector) $ toParentNode n
   liftA1 NEL.fromFoldable $ NL.toArray found
 
+queryAllNodes' :: forall a. Queryable a => String -> a -> Effect (List Node)
+queryAllNodes' selector n = do
+  found <- querySelectorAll (QuerySelector selector) $ toParentNode n
+  foundArr <- NL.toArray found
+  pure $ L.fromFoldable foundArr
+
 getChildrenArray :: forall a. Queryable a => a -> Effect (Array Node)
 getChildrenArray n = do
     children <- N.childNodes $ toNode n

+ 17 - 23
src/LinkedIn/UI/Components/JobsUnifiedTopCard.purs

@@ -8,13 +8,13 @@ import Data.Foldable (class Foldable, foldMap, foldlDefault, foldrDefault)
 import Data.Generic.Rep (class Generic)
 import Data.Lens (Lens', Prism', Traversal', lens', prism', traversed, view)
 import Data.Lens.Record (prop)
-import Data.List.Types (NonEmptyList)
+import Data.List.Types (List, NonEmptyList)
 import Data.Maybe (Maybe(..))
 import Data.Show.Generic (genericShow)
 import Data.Traversable (class Traversable, sequence, traverseDefault)
 import Data.Tuple (Tuple(..))
-import LinkedIn.CanBeQueried (class CanBeQueried, subQueryMany, subQueryOne)
-import LinkedIn.QueryRunner (QueryError(..), ignoreNotFound, queryAll, queryOne, querySelf, queryText)
+import LinkedIn.CanBeQueried (class CanBeQueried, subQueryMany, subQueryMany', subQueryOne)
+import LinkedIn.QueryRunner (QueryError(..), queryAll', queryOne, querySelf, queryText)
 import LinkedIn.Queryable (class Queryable, toNode)
 import Type.Proxy (Proxy(..))
 import Web.DOM.Node as N
@@ -22,14 +22,14 @@ import Web.DOM.Node as N
 data JobsUnifiedTopCardElement a = JobsUnifiedTopCardElement {
   header :: a,
   primaryDescription :: TopCardPrimaryDescription a,
-  insights :: Maybe (NonEmptyList (TopCardInsight a)),
-  actions :: Maybe (NonEmptyList (TopCardAction a))
+  insights :: List (TopCardInsight a),
+  actions :: List (TopCardAction a)
 }
 
 data TopCardPrimaryDescription a = TopCardPrimaryDescription {
   link :: a,
   text :: a,
-  tvmText :: Maybe (NonEmptyList a)
+  tvmText :: List a
 }
 
 data TopCardInsight a = TopCardInsight {
@@ -60,8 +60,8 @@ instance Foldable JobsUnifiedTopCardElement where
   foldMap f (JobsUnifiedTopCardElement {header, primaryDescription, insights, actions}) =
     f header
     <> foldMap f primaryDescription
-    <> foldMap (foldMap (foldMap f)) insights
-    <> foldMap (foldMap (foldMap f)) actions
+    <> foldMap (foldMap f) insights
+    <> foldMap (foldMap f) actions
 
   foldl = \x -> foldlDefault x
   foldr = \x -> foldrDefault x
@@ -70,22 +70,18 @@ instance Traversable JobsUnifiedTopCardElement where
   sequence (JobsUnifiedTopCardElement {header, primaryDescription, insights, actions}) = ado
     h <- header
     pd <- sequence primaryDescription
-    i <- traverseMayNel insights
-    a <- traverseMayNel actions
+    i <- sequence (map sequence insights)
+    a <- sequence (map sequence actions)
   in JobsUnifiedTopCardElement {header: h, primaryDescription: pd, insights: i, actions: a}
 
   traverse = \x -> traverseDefault x
 
-traverseMayNel :: forall m t a. Traversable t => Applicative m => Maybe(NonEmptyList (t (m a))) -> m (Maybe (NonEmptyList (t a)))
-traverseMayNel (Just o) = map pure (sequence (map sequence o))
-traverseMayNel Nothing = pure Nothing
-
 instance Queryable q => CanBeQueried q JobsUnifiedTopCardElement where
   query n = do
     header <- queryOne "h1.job-details-jobs-unified-top-card__job-title" n
     primaryDescription <- subQueryOne "div.job-details-jobs-unified-top-card__primary-description-container > div" n
-    insights <- ignoreNotFound $ subQueryMany "li.job-details-jobs-unified-top-card__job-insight" n
-    actions <- ignoreNotFound $ subQueryMany ".mt5 button" n
+    insights <- subQueryMany' "li.job-details-jobs-unified-top-card__job-insight" n
+    actions <- subQueryMany' ".mt5 button" n
 
     pure $ JobsUnifiedTopCardElement {
       header,
@@ -101,7 +97,7 @@ instance Show a => Show (TopCardPrimaryDescription a) where
 derive instance Functor TopCardPrimaryDescription
 
 instance Foldable TopCardPrimaryDescription where
-  foldMap f (TopCardPrimaryDescription {link, text, tvmText}) = f link <> f text <> foldMap (foldMap f) tvmText
+  foldMap f (TopCardPrimaryDescription {link, text, tvmText}) = f link <> f text <> (foldMap f) tvmText
 
   foldl = \x -> foldlDefault x
   foldr = \x -> foldrDefault x
@@ -110,7 +106,7 @@ instance Traversable TopCardPrimaryDescription where
   sequence (TopCardPrimaryDescription {link, text, tvmText}) = ado
     l <- link
     t <- text
-    tvm <- sequence (map sequence tvmText)
+    tvm <- sequence tvmText
   in TopCardPrimaryDescription {link: l, text: t, tvmText: tvm}
 
   traverse = \x -> traverseDefault x
@@ -119,7 +115,7 @@ instance Queryable q => CanBeQueried q TopCardPrimaryDescription where
   query n = do
     link <- queryOne ":scope > a" n
     text <- queryText 1 n
-    tvmText <- ignoreNotFound $ queryAll "span.tvm__text" n
+    tvmText <- queryAll' "span.tvm__text" n
 
     pure $ TopCardPrimaryDescription {link, text, tvmText: tvmText}
 
@@ -272,7 +268,6 @@ _top_to_insights ∷ ∀ a. Traversal' (JobsUnifiedTopCardElement a) (TopCardIns
 _top_to_insights = _top_card
   <<< prop (Proxy :: Proxy "insights")
   <<< traversed
-  <<< traversed
 
 _insight_to_content = prop (Proxy :: Proxy "content")
   <<< traversed
@@ -281,10 +276,9 @@ _top_to_action_buttons ∷ ∀ a. Traversal' (JobsUnifiedTopCardElement a) a
 _top_to_action_buttons = _top_card
   <<< prop (Proxy :: Proxy "actions")
   <<< traversed
-  <<< traversed
   <<< _action_button
 
-_top_card ∷ forall a. Lens' (JobsUnifiedTopCardElement a) { actions ∷ Maybe (NonEmptyList (TopCardAction a)) , header ∷ a , insights ∷ Maybe (NonEmptyList (TopCardInsight a)) , primaryDescription ∷ TopCardPrimaryDescription a }
+_top_card ∷ forall a. Lens' (JobsUnifiedTopCardElement a) { actions ∷ List (TopCardAction a) , header ∷ a , insights ∷ List (TopCardInsight a) , primaryDescription ∷ TopCardPrimaryDescription a }
 _top_card = lens' \(JobsUnifiedTopCardElement c) -> Tuple c \c' -> JobsUnifiedTopCardElement c'
 
 _insight ∷ forall a. Lens' (TopCardInsight a) { content ∷ TopCardInsightContent a , icon ∷ a }
@@ -293,7 +287,7 @@ _insight = lens' \(TopCardInsight i) -> Tuple i \i' -> TopCardInsight i'
 _action_button ∷ forall a. Lens' (TopCardAction a) a
 _action_button = lens' \(TopCardActionButton i) -> Tuple i \i' -> TopCardActionButton i'
 
-_primary_description ∷ ∀ a. Lens' (TopCardPrimaryDescription a) { link ∷ a , text ∷ a , tvmText ∷ Maybe (NonEmptyList a) }
+_primary_description ∷ ∀ a. Lens' (TopCardPrimaryDescription a) { link ∷ a , text ∷ a , tvmText ∷ List a }
 _primary_description = lens' \(TopCardPrimaryDescription i) -> Tuple i \i' -> TopCardPrimaryDescription i'
 
 _insight_content_single ∷ forall a. Prism' (TopCardInsightContent a) a

+ 13 - 15
test/JobsUnifiedTopCard.purs

@@ -49,25 +49,25 @@ jobOfferPage_3786945580 = {
   filePath: "test/examples/job_offer_3786945580.html",
   url: "https://www.linkedin.com/jobs/view/3786945580/",
   detached: JobOfferPage (JobsUnifiedTopCardElement {
-    actions: (Just (NonEmptyList (NonEmpty (TopCardActionButton
+    actions: TopCardActionButton
       (DetachedButton {
         classes: ("jobs-apply-button" : "artdeco-button" : "artdeco-button--3" : "artdeco-button--primary" : "ember-view" : Nil),
         content: "Candidature simplifiée",
         role: Nothing
-      }))
-      ((TopCardActionButton (DetachedButton {
+      })
+      : TopCardActionButton (DetachedButton {
         classes: ("jobs-save-button" : "artdeco-button" : "artdeco-button--3" : "artdeco-button--secondary" : Nil),
         content: "Enregistrer Enregistrer Data Engineer H/F - Secteur Energie chez LINCOLN",
         role: Nothing
-      })) : Nil)
-    ))),
+      })
+      : Nil,
     header: (DetachedElement {
       classes: ("t-24" : "t-bold" : "job-details-jobs-unified-top-card__job-title" : Nil),
       content: "Data Engineer H/F - Secteur Energie",
       id: Nothing,
       tag: "H1"
     }),
-    insights: (Just (NonEmptyList (NonEmpty (TopCardInsight {
+    insights: (TopCardInsight {
         content: (TopCardInsightContentSecondary {
           primary: (DetachedElement {classes: Nil, content: "Sur site", id: Nothing, tag: "SPAN"}),
           secondary: (NonEmptyList (NonEmpty (TopCardSecondaryInsightNested
@@ -77,7 +77,7 @@ jobOfferPage_3786945580 = {
           )
         }),
         icon: DetachedLiIcon "job"
-      }) ((TopCardInsight {
+      }) : (TopCardInsight {
           content: (TopCardInsightContentSingle (
             DetachedElement {classes: Nil, content: "201-500 employés · Technologies et services de l’information", id: Nothing, tag: "SPAN" }
           )),
@@ -96,17 +96,15 @@ jobOfferPage_3786945580 = {
                 DetachedButton {classes: ("job-details-jobs-unified-top-card__job-insight-text-button" : Nil), content: "9 compétences sur 11 correspondent à votre profil, vous pourriez bien convenir pour ce poste", role: Nothing}
               )),
               icon: (DetachedSvgElement { dataTestIcon: (Just "checklist-medium"), id: Nothing, tag: "svg" })
-            }) : Nil)))),
+            }) : Nil,
     primaryDescription: (TopCardPrimaryDescription {
       link: (DetachedA { content: "LINCOLN", href: "https://www.linkedin.com/company/lincoln-/life" }),
       text: (DetachedText "· Boulogne-Billancourt, Île-de-France, France"),
-      tvmText: (Just (NonEmptyList (NonEmpty (
-        DetachedElement {classes: ("tvm__text" : "tvm__text--neutral" : Nil), content: "il y a 2 semaines", id: Nothing, tag: "SPAN"})
-        ((DetachedElement {classes: ("tvm__text" : "tvm__text--neutral" : Nil), content: "·", id: Nothing, tag: "SPAN"})
-          : (DetachedElement {classes: ("tvm__text" : "tvm__text--neutral" : Nil), content: "87 candidats", id: Nothing, tag: "SPAN"})
-          : Nil
-        ))
-      ))
+      tvmText:
+        DetachedElement {classes: ("tvm__text" : "tvm__text--neutral" : Nil), content: "il y a 2 semaines", id: Nothing, tag: "SPAN"}
+        : DetachedElement {classes: ("tvm__text" : "tvm__text--neutral" : Nil), content: "·", id: Nothing, tag: "SPAN"}
+        : DetachedElement {classes: ("tvm__text" : "tvm__text--neutral" : Nil), content: "87 candidats", id: Nothing, tag: "SPAN"}
+        : Nil
     })
   }),
   output: OutJobOffer (JobOffer {