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

Use new parsing method for TopCard

jherve 1 éve
szülő
commit
970339d113

+ 8 - 3
src/Content.purs

@@ -14,7 +14,7 @@ import Effect.Class.Console (logShow)
 import Effect.Console (log)
 import LinkedIn.ArtDecoCard (queryArtDecoCard)
 import LinkedIn.ArtDecoTab (queryArtDecoTab)
-import LinkedIn.JobsUnifiedTopCard (parseJobsUnifiedTopCardElement)
+import LinkedIn.JobsUnifiedTopCard (queryJobsUnifiedTopCardElement)
 import LinkedIn.Profile.Project as PP
 import LinkedIn.Profile.Skill as PS
 import LinkedIn.Profile.Utils (toUIElement)
@@ -64,8 +64,13 @@ main = do
   case jobsUnifiedTopCard of
     Nothing -> log "nothing"
     Just l -> do
-      parsed <- (\(LinkedInUIElement _ n) -> parseJobsUnifiedTopCardElement n) $ NEL.head l
-      logShow parsed
+      queried <- (\(LinkedInUIElement _ n) -> runQuery $ queryJobsUnifiedTopCardElement n) $ NEL.head l
+      case queried of
+        Left l -> logShow l
+        Right p -> do
+          detached <- traverse toDetached p
+          log "parsed OK"
+          logShow detached
 
 maybeShowTree ∷ Maybe (NonEmptyList LinkedInUIElement) → Effect String
 maybeShowTree Nothing = pure "nope"

+ 230 - 122
src/LinkedIn/JobsUnifiedTopCard.purs

@@ -1,155 +1,263 @@
 module LinkedIn.JobsUnifiedTopCard where
 
-import Control.Alt
 import Prelude
 
-import Data.Either (Either(..), hush)
+import Control.Monad.Error.Class (throwError)
+import Data.Foldable (class Foldable, foldMap, foldlDefault, foldrDefault)
 import Data.Generic.Rep (class Generic)
-import Data.List.Types (NonEmptyList(..))
+import Data.List.Types (NonEmptyList)
 import Data.Maybe (Maybe(..))
 import Data.Show.Generic (genericShow)
-import LinkedIn (DetachedNode(..))
-import LinkedIn.Types (ParseError(..), Parser)
-import LinkedIn.Utils (detachNonEmptyTextChild, parseDetachedNode, queryAndDetachMany, queryAndDetachOne, queryManyAndParse, queryOneAndParse)
-
-data JobsUnifiedTopCardElement = JobsUnifiedTopCardElement {
-  header :: DetachedNode,
-  primaryDescription :: Maybe TopCardPrimaryDescription,
-  insights :: Maybe (NonEmptyList TopCardInsight),
-  actions :: Maybe (NonEmptyList TopCardAction)
+import Data.Traversable (class Traversable, sequence, traverse, traverseDefault)
+import LinkedIn.QueryRunner (QueryError(..), QueryRunner, chooseOne, chooseOne3, ignoreNotFound, queryAll, queryOne, queryText)
+import Web.DOM (Node)
+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))
 }
 
-data TopCardPrimaryDescription = TopCardPrimaryDescription {
-  link :: DetachedNode,
-  text :: DetachedNode,
-  tvmText :: Maybe (NonEmptyList DetachedNode)
+data TopCardPrimaryDescription a = TopCardPrimaryDescription {
+  link :: a,
+  text :: a,
+  tvmText :: Maybe (NonEmptyList a)
 }
 
-data TopCardInsight = TopCardInsight {
-  icon :: DetachedNode,
-  content :: TopCardInsightContent
+data TopCardInsight a = TopCardInsight {
+  icon :: a,
+  content :: TopCardInsightContent a
 }
 
-data TopCardInsightContent =
-  TopCardInsightContentSingle DetachedNode
-  | TopCardInsightContentSecondary {primary :: DetachedNode, secondary :: NonEmptyList TopCardSecondaryInsight}
-  | TopCardInsightContentButton DetachedNode
+data TopCardInsightContent a =
+  TopCardInsightContentSingle a
+  | TopCardInsightContentSecondary {primary :: a, secondary :: NonEmptyList (TopCardSecondaryInsight a)}
+  | TopCardInsightContentButton a
 
-data TopCardSecondaryInsight =
-  TopCardSecondaryInsightNested DetachedNode
-  | TopCardSecondaryInsightPlain DetachedNode
+data TopCardSecondaryInsight a =
+  TopCardSecondaryInsightNested a
+  | TopCardSecondaryInsightPlain a
 
 -- External application : <button id="ember74"  class="jobs-apply-button artdeco-button artdeco-button--3 artdeco-button--primary ember-view artdeco-button--icon-right" role="link">
 -- LinkedIn Applcation : <button id="ember115" class="jobs-apply-button artdeco-button artdeco-button--3 artdeco-button--primary ember-view" data-job-id="3786945580">
-data TopCardAction = TopCardActionApplyButton DetachedNode
+data TopCardAction a = TopCardActionApplyButton a
 
-derive instance Generic JobsUnifiedTopCardElement _
-derive instance Eq JobsUnifiedTopCardElement
-instance Show JobsUnifiedTopCardElement where
+derive instance Generic (JobsUnifiedTopCardElement a) _
+derive instance Eq a => Eq (JobsUnifiedTopCardElement a)
+instance Show a => Show (JobsUnifiedTopCardElement a) where
   show = genericShow
+derive instance Functor JobsUnifiedTopCardElement
+
+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
+
+  foldl = \x -> foldlDefault x
+  foldr = \x -> foldrDefault x
+
+instance Traversable JobsUnifiedTopCardElement where
+  sequence (JobsUnifiedTopCardElement {header, primaryDescription, insights, actions}) = ado
+    h <- header
+    pd <- sequence primaryDescription
+    i <- traverseMayNel insights
+    a <- traverseMayNel 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
 
-derive instance Generic TopCardPrimaryDescription _
-derive instance Eq TopCardPrimaryDescription
-instance Show TopCardPrimaryDescription where
+derive instance Generic (TopCardPrimaryDescription a) _
+derive instance Eq a => Eq (TopCardPrimaryDescription a)
+instance Show a => Show (TopCardPrimaryDescription a) where
   show = genericShow
+derive instance Functor TopCardPrimaryDescription
+
+instance Foldable TopCardPrimaryDescription where
+  foldMap f (TopCardPrimaryDescription {link, text, tvmText}) = f link <> f text <> foldMap (foldMap f) tvmText
+
+  foldl = \x -> foldlDefault x
+  foldr = \x -> foldrDefault x
+
+instance Traversable TopCardPrimaryDescription where
+  sequence (TopCardPrimaryDescription {link, text, tvmText}) = ado
+    l <- link
+    t <- text
+    tvm <- sequence (map sequence tvmText)
+  in TopCardPrimaryDescription {link: l, text: t, tvmText: tvm}
+
+  traverse = \x -> traverseDefault x
 
-derive instance Generic TopCardInsight _
-derive instance Eq TopCardInsight
-instance Show TopCardInsight where
+derive instance Generic (TopCardInsight a) _
+derive instance Eq a => Eq (TopCardInsight a)
+instance Show a => Show (TopCardInsight a) where
   show = genericShow
+derive instance Functor TopCardInsight
 
-derive instance Generic TopCardInsightContent _
-derive instance Eq TopCardInsightContent
-instance Show TopCardInsightContent where
+instance Foldable TopCardInsight where
+  foldMap f (TopCardInsight {icon, content}) = f icon <> foldMap f content
+
+  foldl = \x -> foldlDefault x
+  foldr = \x -> foldrDefault x
+
+instance Traversable TopCardInsight where
+  sequence (TopCardInsight {icon, content}) = ado
+    i <- icon
+    c <- sequence content
+  in TopCardInsight {icon: i, content: c}
+
+  traverse = \x -> traverseDefault x
+
+derive instance Generic (TopCardInsightContent a) _
+derive instance Eq a => Eq (TopCardInsightContent a)
+instance Show a => Show (TopCardInsightContent a) where
   show = genericShow
+derive instance Functor TopCardInsightContent
+
+instance Foldable TopCardInsightContent where
+  foldMap f (TopCardInsightContentSingle a) = f a
+  foldMap f (TopCardInsightContentButton a) = f a
+  foldMap f (TopCardInsightContentSecondary {primary, secondary}) = f primary <> foldMap (foldMap f) secondary
 
-derive instance Generic TopCardSecondaryInsight _
-derive instance Eq TopCardSecondaryInsight
-instance Show TopCardSecondaryInsight where
+  foldl = \x -> foldlDefault x
+  foldr = \x -> foldrDefault x
+
+instance Traversable TopCardInsightContent where
+  sequence (TopCardInsightContentSingle ins) = TopCardInsightContentSingle <$> ins
+  sequence (TopCardInsightContentButton ins) = TopCardInsightContentButton <$> ins
+  sequence (TopCardInsightContentSecondary {primary, secondary}) = ado
+    p <- primary
+    s <- sequence (map sequence secondary)
+  in TopCardInsightContentSecondary {primary: p, secondary: s}
+
+  traverse = \x -> traverseDefault x
+
+derive instance Generic (TopCardSecondaryInsight a) _
+derive instance Eq a => Eq (TopCardSecondaryInsight a)
+instance Show a => Show (TopCardSecondaryInsight a) where
   show = genericShow
+derive instance Functor TopCardSecondaryInsight
+
+instance Foldable TopCardSecondaryInsight where
+  foldMap f (TopCardSecondaryInsightNested a) = f a
+  foldMap f (TopCardSecondaryInsightPlain a) = f a
+
+  foldl = \x -> foldlDefault x
+  foldr = \x -> foldrDefault x
+
+instance Traversable TopCardSecondaryInsight where
+  sequence (TopCardSecondaryInsightNested ins) = TopCardSecondaryInsightNested <$> ins
+  sequence (TopCardSecondaryInsightPlain ins) = TopCardSecondaryInsightPlain <$> ins
 
-derive instance Generic TopCardAction _
-derive instance Eq TopCardAction
-instance Show TopCardAction where
+  traverse = \x -> traverseDefault x
+
+derive instance Generic (TopCardAction a) _
+derive instance Eq a => Eq (TopCardAction a)
+instance Show a => Show (TopCardAction a) where
   show = genericShow
+derive instance Functor TopCardAction
 
-parseTopCardAction :: Parser TopCardAction
-parseTopCardAction n = do
-  self <- parseDetachedNode n
-
-  pure $ ado
-    s <- self
-  in TopCardActionApplyButton s
-
-parseTopCardSecondaryInsight :: Parser TopCardSecondaryInsight
-parseTopCardSecondaryInsight n = do
-  nested <- queryAndDetachOne ":scope span[aria-hidden=true]" n
-  plain <- parseDetachedNode n
-
-  pure $ case nested, plain of
-    Right p@(DetachedElement _), _ -> Right $ TopCardSecondaryInsightNested p
-    _, Right p@(DetachedElement _) -> Right $ TopCardSecondaryInsightPlain p
-    _, _ -> Left TextNotFoundError
-
-parseTopCardInsightContent :: Parser TopCardInsightContent
-parseTopCardInsightContent n = do
-  primary <- queryAndDetachOne ":scope > span:first-child span[aria-hidden=true]" n
-  secondary <- queryManyAndParse
-    ":scope > span.job-details-jobs-unified-top-card__job-insight-view-model-secondary"
-    parseTopCardSecondaryInsight
-    n
-  self <- parseDetachedNode n
-
-  pure $ case primary, secondary, self of
-    _, _, Right b@(DetachedElement {tag: "BUTTON"}) -> Right $ TopCardInsightContentButton b
-    Right p@(DetachedElement _), Right s, _ -> Right $ TopCardInsightContentSecondary {primary: p, secondary: s}
-    _, _, Right el@(DetachedElement _) -> Right $ TopCardInsightContentSingle el
-    _, _, _ -> Left TextNotFoundError
-
-parseTopCardInsight :: Parser TopCardInsight
-parseTopCardInsight n = do
-  icon <- queryAndDetachOne ":scope li-icon" n
-  svg <- queryAndDetachOne ":scope svg" n
-  content <- queryOneAndParse ":scope > span" parseTopCardInsightContent n
-  actionButton <- queryOneAndParse ":scope > button" parseTopCardInsightContent n
-
-  pure $ ado
-    i <- icon <|> svg
-    c <- content <|> actionButton
-  in TopCardInsight {icon: i, content: c}
+instance Foldable TopCardAction where
+  foldMap f (TopCardActionApplyButton a) = f a
 
-parseTopCardPrimaryDescription :: Parser TopCardPrimaryDescription
-parseTopCardPrimaryDescription n = do
-  link <- queryAndDetachOne ":scope > a" n
-  text <- detachNonEmptyTextChild n
-  tvmText <- queryAndDetachMany "span.tvm__text" n
+  foldl = \x -> foldlDefault x
+  foldr = \x -> foldrDefault x
 
-  pure $ ado
-    l <- link
-    t <- text
-  in TopCardPrimaryDescription {link: l, text: t, tvmText: hush tvmText}
-
-parseJobsUnifiedTopCardElement :: Parser JobsUnifiedTopCardElement
-parseJobsUnifiedTopCardElement n = do
-  h1 <- queryAndDetachOne "h1.job-details-jobs-unified-top-card__job-title" n
-  primary <- queryOneAndParse
-    "div.job-details-jobs-unified-top-card__primary-description-container > div"
-    parseTopCardPrimaryDescription
-    n
-  insights <- queryManyAndParse
-    "li.job-details-jobs-unified-top-card__job-insight"
-    parseTopCardInsight
-    n
-  actions <- queryManyAndParse
-    ".mt5 button"
-    parseTopCardAction
-    n
-
-  pure $ ado
-    h <- h1
-  in JobsUnifiedTopCardElement {
-    header: h,
-    primaryDescription: hush primary,
-    insights: hush insights,
-    actions: hush actions
+instance Traversable TopCardAction where
+  sequence (TopCardActionApplyButton app) = ado
+    a <- app
+  in TopCardActionApplyButton a
+
+  traverse = \x -> traverseDefault x
+
+queryTopCardAction :: QueryRunner (TopCardAction Node)
+queryTopCardAction n = pure $ TopCardActionApplyButton n
+
+queryTopCardSecondaryInsightNested :: QueryRunner (TopCardSecondaryInsight Node)
+queryTopCardSecondaryInsightNested n = do
+  nested <- queryOne ":scope span[aria-hidden=true]" n
+  pure $ TopCardSecondaryInsightNested nested
+
+queryTopCardSecondaryInsightPlain :: QueryRunner (TopCardSecondaryInsight Node)
+queryTopCardSecondaryInsightPlain n = pure $ TopCardSecondaryInsightPlain n
+
+queryTopCardSecondaryInsight :: QueryRunner (TopCardSecondaryInsight Node)
+queryTopCardSecondaryInsight n =
+  chooseOne queryTopCardSecondaryInsightNested queryTopCardSecondaryInsightPlain n
+
+queryTopCardInsightContentSingle :: QueryRunner (TopCardInsightContent Node)
+queryTopCardInsightContentSingle n = pure $ TopCardInsightContentSingle n
+
+queryTopCardInsightContentButton :: QueryRunner (TopCardInsightContent Node)
+queryTopCardInsightContentButton n =
+  if type_ == "BUTTON"
+  then pure $ TopCardInsightContentButton n
+  else throwError (QNodeUnexpectedType "BUTTON" type_)
+
+  where type_ = N.nodeName n
+
+queryTopCardInsightContentSecondary :: QueryRunner (TopCardInsightContent Node)
+queryTopCardInsightContentSecondary n = do
+  primary <- queryOne ":scope > span:first-child span[aria-hidden=true]" n
+  secondary <- traverse queryTopCardSecondaryInsight
+                =<< queryAll ":scope > span.job-details-jobs-unified-top-card__job-insight-view-model-secondary" n
+  pure $ TopCardInsightContentSecondary {primary, secondary}
+
+queryTopCardInsightContent :: QueryRunner (TopCardInsightContent Node)
+queryTopCardInsightContent n =
+  chooseOne3 queryTopCardInsightContentSecondary queryTopCardInsightContentButton queryTopCardInsightContentSingle n
+
+queryTopCardInsight :: QueryRunner (TopCardInsight Node)
+queryTopCardInsight n = do
+  icon <- chooseOne (queryOne ":scope li-icon") (queryOne ":scope svg") n
+  content <- queryTopCardInsightContent =<< getContentNode n
+
+  pure $ TopCardInsight {icon, content}
+
+  where
+    getContentNode = chooseOne (queryOne ":scope > span") (queryOne ":scope > button")
+
+queryTopCardPrimaryDescription :: QueryRunner (TopCardPrimaryDescription Node)
+queryTopCardPrimaryDescription n = do
+  link <- queryOne ":scope > a" n
+  text <- queryText 1 n
+  tvmText <- ignoreNotFound $ queryAll "span.tvm__text" n
+
+  pure $ TopCardPrimaryDescription {link, text, tvmText: tvmText}
+
+queryJobsUnifiedTopCardElement :: QueryRunner (JobsUnifiedTopCardElement Node)
+queryJobsUnifiedTopCardElement n = do
+  header <- queryOne "h1.job-details-jobs-unified-top-card__job-title" n
+  primaryDescription <- queryTopCardPrimaryDescription
+                          =<< queryOne "div.job-details-jobs-unified-top-card__primary-description-container > div" n
+  insights <- ignoreNotFound
+                <<< traverse queryTopCardInsight
+                =<< queryAll "li.job-details-jobs-unified-top-card__job-insight" n
+  actions <- ignoreNotFound <<< traverse queryTopCardAction =<< queryAll ".mt5 button" n
+
+  pure $ JobsUnifiedTopCardElement {
+    header,
+    primaryDescription,
+    insights,
+    actions
   }
+
+toHeader ∷ forall a. JobsUnifiedTopCardElement a → a
+toHeader (JobsUnifiedTopCardElement {header}) = header
+
+toPrimaryDescriptionLink ∷ forall a. JobsUnifiedTopCardElement a → a
+toPrimaryDescriptionLink (JobsUnifiedTopCardElement {
+  primaryDescription: TopCardPrimaryDescription {link}
+}) = link
+
+toPrimaryDescriptionText ∷ forall a. JobsUnifiedTopCardElement a → a
+toPrimaryDescriptionText (JobsUnifiedTopCardElement {
+  primaryDescription: TopCardPrimaryDescription {text}
+}) = text

+ 52 - 1
src/LinkedIn/QueryRunner.purs

@@ -2,7 +2,9 @@ module LinkedIn.QueryRunner where
 
 import Prelude
 
-import Control.Monad.Except (ExceptT(..), mapExceptT, runExceptT)
+import Control.Alt ((<|>))
+import Control.Monad.Except (ExceptT(..), mapExceptT, runExceptT, throwError)
+import Data.Array as A
 import Data.Either (Either(..), note)
 import Data.Generic.Rep (class Generic)
 import Data.List.Types (NonEmptyList)
@@ -12,11 +14,17 @@ import Data.Traversable (traverse)
 import Effect (Effect)
 import LinkedIn.Utils as U
 import Web.DOM (Node)
+import Web.DOM.Node as N
+import Web.DOM.NodeList as NL
+import Web.DOM.NodeType (NodeType(..))
+import Web.DOM.Text as T
 
 data QueryError =
   QNodeNotFoundError String
   | QNodeListNotFoundError String
+  | QNodeUnexpectedType String String
   | QTextNotFoundError
+  | QChooseError
 
 derive instance Generic QueryError _
 derive instance Eq QueryError
@@ -36,11 +44,30 @@ ignoreNotFound = mapExceptT (map ignoreNotFound')
       (Left q) -> Left q
       (Right n') -> Right (Just n')
 
+ignoreErrors ∷ ∀ a f. Functor f ⇒ ExceptT QueryError f a → ExceptT QueryError f (Maybe a)
+ignoreErrors = mapExceptT (map ignoreErrors')
+  where
+    ignoreErrors' = case _ of
+      (Left q) -> Right Nothing
+      (Right n') -> Right (Just n')
+
 queryOne ∷ String → QueryRunner Node
 queryOne selector node = ExceptT $ do
   maybeNode <- U.queryOne selector node
   pure $ note (QNodeNotFoundError selector) maybeNode
 
+queryText ∷ Int -> QueryRunner Node
+queryText idx n = ExceptT $ do
+  children <- N.childNodes n
+  childrenArr <- NL.toArray children
+  let
+    maybeText n' = do
+      _ <- T.fromNode n'
+      pure $ n'
+    allTexts = A.mapMaybe maybeText childrenArr
+
+  pure $ note QTextNotFoundError $ A.index allTexts idx
+
 queryAll ∷ String → QueryRunner (NonEmptyList Node)
 queryAll selector node = ExceptT $ do
   maybeNodes <- U.queryAll selector node
@@ -51,3 +78,27 @@ subQueryMany query selector n = traverse query =<< queryAll selector n
 
 subQueryOne ∷ ∀ a. QueryRunner a → String → QueryRunner a
 subQueryOne query selector n = query =<< queryOne selector n
+
+chooseOne ∷ ∀ a t m. Monad m ⇒ (t → ExceptT QueryError m a) → (t → ExceptT QueryError m a) → (t → ExceptT QueryError m a)
+chooseOne q1 q2 n = do
+  maybeN1 <- (ignoreErrors <<< q1) n
+  maybeN2 <- (ignoreErrors <<< q2) n
+
+  case maybeN1 <|> maybeN2 of
+    Nothing -> throwError QChooseError
+    Just n' -> pure n'
+
+chooseOne3 ∷ ∀ a t m.
+  Monad m
+  ⇒ (t → ExceptT QueryError m a)
+  → (t → ExceptT QueryError m a)
+  → (t → ExceptT QueryError m a)
+  → (t → ExceptT QueryError m a)
+chooseOne3 q1 q2 q3 n = do
+  maybeN1 <- (ignoreErrors <<< q1) n
+  maybeN2 <- (ignoreErrors <<< q2) n
+  maybeN3 <- (ignoreErrors <<< q3) n
+
+  case maybeN1 <|> maybeN2 <|> maybeN3 of
+    Nothing -> throwError QChooseError
+    Just n' -> pure n'

+ 12 - 6
test/JobsUnifiedTopCard.purs

@@ -10,10 +10,12 @@ import Data.List.NonEmpty (NonEmptyList(..))
 import Data.List.NonEmpty as NEL
 import Data.Maybe (Maybe(..), isJust)
 import Data.NonEmpty (NonEmpty(..))
+import Data.Traversable (traverse)
 import Effect (Effect)
-import LinkedIn (DetachedNode(..), LinkedInUIElement(..), getJobsUnifiedTopCard)
+import LinkedIn (DetachedNode(..), LinkedInUIElement(..), getJobsUnifiedTopCard, toDetached)
 import LinkedIn.Profile.WorkExperience (WorkExperience(..))
 import LinkedIn.Profile.WorkExperience as PWE
+import LinkedIn.QueryRunner (QueryError, runQuery)
 import LinkedIn.Types (ParseError(..))
 import LinkedIn.UIElements.Types (Duration(..), TimeSpan(..))
 import Node.JsDom (jsDomFromFile)
@@ -123,7 +125,7 @@ testJobsUnifiedTopCard = do
                 tag: "svg"
               })
             }) : Nil)))),
-      primaryDescription: (Just (TopCardPrimaryDescription {
+      primaryDescription: (TopCardPrimaryDescription {
         link: (DetachedElement {
           classes: ("app-aware-link" : Nil),
           content: "LINCOLN",
@@ -149,13 +151,17 @@ testJobsUnifiedTopCard = do
           }) : Nil
           ))
         ))
-      }))
+      })
     })
   }
 
 
-parseHeadCard ∷ Partial => Maybe (NonEmptyList LinkedInUIElement) → Effect (Either ParseError JobsUnifiedTopCardElement)
+parseHeadCard ∷ Partial ⇒ Maybe (NonEmptyList LinkedInUIElement) → Effect (Either QueryError (JobsUnifiedTopCardElement DetachedNode))
 parseHeadCard (Just l) = do
-  parsed <- (\(LinkedInUIElement _ n) -> parseJobsUnifiedTopCardElement n) $ NEL.head l
-  pure $ parsed
+  queried <- (\(LinkedInUIElement _ n) -> runQuery $ queryJobsUnifiedTopCardElement n) $ NEL.head l
+  case queried of
+    Left l -> pure $ Left l
+    Right q -> do
+      parsed <- traverse toDetached q
+      pure $ Right parsed