Преглед на файлове

Add data constructors for SVG elements

jherve преди 1 година
родител
ревизия
9e56205769
променени са 4 файла, в които са добавени 17 реда и са изтрити 17 реда
  1. 4 3
      src/LinkedIn/DetachedNode.purs
  2. 10 2
      src/LinkedIn/Profile/Utils.purs
  3. 1 0
      src/LinkedIn/UIElements/Types.purs
  4. 2 12
      test/JobsUnifiedTopCard.purs

+ 4 - 3
src/LinkedIn/DetachedNode.purs

@@ -27,6 +27,7 @@ import Yoga.Tree (Tree, leaf, mkTree)
 
 data DetachedNode =
   DetachedElement {tag :: String, content :: String, id :: Maybe String, classes :: List String}
+  | DetachedSvgElement {tag :: String, id :: Maybe String, dataTestIcon :: Maybe String}
   | DetachedA {content :: String, href :: String}
   | DetachedButton {content :: String, role :: Maybe String, classes :: List String}
   | DetachedComment String
@@ -78,12 +79,12 @@ elementToDetached el tag text = case tag of
   -- On SVG elements "className" returns a weird "SVGString" type that cannot be trimmed
   tag' | tag' == "svg" || tag' == "use" || tag' == "path" -> do
     id <- E.id el
+    data_ <- getAttribute "data-test-icon" el
 
-    pure $ DetachedElement {
+    pure $ DetachedSvgElement {
       tag: tag',
-      content: normalize text,
       id: if S.null id then Nothing else Just id,
-      classes: Nil
+      dataTestIcon: data_
     }
 
   tag' -> do

+ 10 - 2
src/LinkedIn/Profile/Utils.purs

@@ -2,7 +2,8 @@ module LinkedIn.Profile.Utils where
 
 import Prelude
 
-import Data.Either (Either, hush)
+import Control.Alt ((<|>))
+import Data.Either (Either(..), hush)
 import Data.Foldable (class Foldable, findMap)
 import Data.List (List)
 import Data.List as L
@@ -10,7 +11,7 @@ import Data.Maybe (Maybe(..))
 import LinkedIn.DetachedNode (DetachedNode(..))
 import LinkedIn.UIElements.Parser (uiElementP)
 import LinkedIn.UIElements.Types (UIElement(..))
-import Parsing (runParser, ParseError)
+import Parsing (ParseError(..), initialPos, runParser)
 
 maybeGetInList ::
   ∀ a. (UIElement → Maybe a)
@@ -34,11 +35,18 @@ maybeFindInMaybeNEL extract = case _ of
   Just nel -> findMap (hush >>> (extract =<< _)) nel
   Nothing -> Nothing
 
+-- TODO : should certainly use another type than ParseError here
 toUIElement ∷ DetachedNode → Either ParseError UIElement
 toUIElement (DetachedElement {content}) = runParser content uiElementP
 toUIElement (DetachedComment str) = runParser str uiElementP
 toUIElement (DetachedText str) = runParser str uiElementP
+toUIElement (DetachedSvgElement {id, dataTestIcon, tag: "svg"}) = case id <|> dataTestIcon of
+  Just i -> Right (UIIcon i)
+  Nothing -> Left (ParseError "SVG element could not be identified" initialPos)
+toUIElement (DetachedSvgElement _) = Left (ParseError "SVG element could not be identified" initialPos)
+
 toUIElement (DetachedButton {content, role}) =  map toButton $ runParser content uiElementP
   where toButton ui = UIButton role ui
+
 toUIElement (DetachedA {content, href}) = map toLink $ runParser content uiElementP
   where toLink ui = UILink href ui

+ 1 - 0
src/LinkedIn/UIElements/Types.purs

@@ -42,6 +42,7 @@ data UIElement =
   | UIDotSeparated UIElement UIElement
   | UILink String UIElement
   | UIButton (Maybe String) UIElement
+  | UIIcon String
 
 derive instance Generic UIElement _
 instance Show UIElement where

+ 2 - 12
test/JobsUnifiedTopCard.purs

@@ -99,24 +99,14 @@ testJobsUnifiedTopCard = do
                 content: "Découvrez comment vous vous positionnez par rapport à 87 candidats. Essai Premium pour 0 EUR",
                 id: (Just "undefined"),
                 tag: "SPAN" })),
-              icon: (DetachedElement {
-                classes: Nil,
-                content: "",
-                id: Nothing,
-                tag: "svg"
-              })
+              icon: (DetachedSvgElement { dataTestIcon: (Just "lightbulb-medium"), id: Nothing, tag: "svg" })
             }) : (TopCardInsight {
               content: (TopCardInsightContentButton (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: (DetachedElement {
-                classes: Nil,
-                content: "",
-                id: Nothing,
-                tag: "svg"
-              })
+              icon: (DetachedSvgElement { dataTestIcon: (Just "checklist-medium"), id: Nothing, tag: "svg" })
             }) : Nil)))),
       primaryDescription: (TopCardPrimaryDescription {
         link: (DetachedA { content: "LINCOLN", href: "https://www.linkedin.com/company/lincoln-/life" }),