Просмотр исходного кода

Make data types for TopCard generic

jherve 1 год назад
Родитель
Сommit
96496314d7
2 измененных файлов с 90 добавлено и 52 удалено
  1. 87 49
      src/LinkedIn/JobsUnifiedTopCard.purs
  2. 3 3
      test/JobsUnifiedTopCard.purs

+ 87 - 49
src/LinkedIn/JobsUnifiedTopCard.purs

@@ -5,75 +5,99 @@ import Prelude
 
 
 import Data.Either (Either(..), hush)
 import Data.Either (Either(..), hush)
 import Data.Generic.Rep (class Generic)
 import Data.Generic.Rep (class Generic)
-import Data.List.Types (NonEmptyList(..))
-import Data.Maybe (Maybe(..))
+import Data.List.Types (NonEmptyList)
+import Data.Maybe (Maybe)
 import Data.Show.Generic (genericShow)
 import Data.Show.Generic (genericShow)
 import LinkedIn (DetachedNode(..))
 import LinkedIn (DetachedNode(..))
 import LinkedIn.Types (ParseError(..), Parser)
 import LinkedIn.Types (ParseError(..), Parser)
 import LinkedIn.Utils (detachNonEmptyTextChild, parseDetachedNode, queryAndDetachMany, queryAndDetachOne, queryManyAndParse, queryOneAndParse)
 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)
+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">
 -- 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">
 -- 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
   show = genericShow
-
-derive instance Generic TopCardPrimaryDescription _
-derive instance Eq TopCardPrimaryDescription
-instance Show TopCardPrimaryDescription where
+instance Functor JobsUnifiedTopCardElement where
+  map f (JobsUnifiedTopCardElement {header, primaryDescription, insights, actions}) =
+    JobsUnifiedTopCardElement {
+      header: f header,
+      primaryDescription: map f primaryDescription,
+      insights: map (map (map f)) insights,
+      actions: map (map (map f)) actions
+    }
+
+derive instance Generic (TopCardPrimaryDescription a) _
+derive instance Eq a => Eq (TopCardPrimaryDescription a)
+instance Show a => Show (TopCardPrimaryDescription a) where
   show = genericShow
   show = genericShow
+instance Functor TopCardPrimaryDescription where
+  map f (TopCardPrimaryDescription {link, text, tvmText}) =
+    TopCardPrimaryDescription {link: f link, text: f text, tvmText: map (map f) tvmText}
 
 
-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
   show = genericShow
+instance Functor TopCardInsight where
+  map f (TopCardInsight {icon, content}) =
+    TopCardInsight {icon: f icon, content: map f content}
 
 
-derive instance Generic TopCardInsightContent _
-derive instance Eq TopCardInsightContent
-instance Show TopCardInsightContent where
+derive instance Generic (TopCardInsightContent a) _
+derive instance Eq a => Eq (TopCardInsightContent a)
+instance Show a => Show (TopCardInsightContent a) where
   show = genericShow
   show = genericShow
-
-derive instance Generic TopCardSecondaryInsight _
-derive instance Eq TopCardSecondaryInsight
-instance Show TopCardSecondaryInsight where
+instance Functor TopCardInsightContent where
+  map f (TopCardInsightContentSingle c) = TopCardInsightContentSingle (f c)
+  map f (TopCardInsightContentSecondary {primary, secondary}) =
+    TopCardInsightContentSecondary {primary: f primary, secondary: map (map f) secondary}
+  map f (TopCardInsightContentButton c) = TopCardInsightContentButton (f c)
+
+derive instance Generic (TopCardSecondaryInsight a) _
+derive instance Eq a => Eq (TopCardSecondaryInsight a)
+instance Show a => Show (TopCardSecondaryInsight a) where
   show = genericShow
   show = genericShow
+instance Functor TopCardSecondaryInsight where
+  map f (TopCardSecondaryInsightNested c) = TopCardSecondaryInsightNested (f c)
+  map f (TopCardSecondaryInsightPlain c) = TopCardSecondaryInsightPlain (f c)
 
 
-derive instance Generic TopCardAction _
-derive instance Eq TopCardAction
-instance Show TopCardAction where
+derive instance Generic (TopCardAction a) _
+derive instance Eq a => Eq (TopCardAction a)
+instance Show a => Show (TopCardAction a) where
   show = genericShow
   show = genericShow
+instance Functor TopCardAction where
+  map f (TopCardActionApplyButton c) = TopCardActionApplyButton (f c)
 
 
-parseTopCardAction :: Parser TopCardAction
+parseTopCardAction :: Parser (TopCardAction DetachedNode)
 parseTopCardAction n = do
 parseTopCardAction n = do
   self <- parseDetachedNode n
   self <- parseDetachedNode n
 
 
@@ -81,7 +105,7 @@ parseTopCardAction n = do
     s <- self
     s <- self
   in TopCardActionApplyButton s
   in TopCardActionApplyButton s
 
 
-parseTopCardSecondaryInsight :: Parser TopCardSecondaryInsight
+parseTopCardSecondaryInsight :: Parser (TopCardSecondaryInsight DetachedNode)
 parseTopCardSecondaryInsight n = do
 parseTopCardSecondaryInsight n = do
   nested <- queryAndDetachOne ":scope span[aria-hidden=true]" n
   nested <- queryAndDetachOne ":scope span[aria-hidden=true]" n
   plain <- parseDetachedNode n
   plain <- parseDetachedNode n
@@ -91,7 +115,7 @@ parseTopCardSecondaryInsight n = do
     _, Right p@(DetachedElement _) -> Right $ TopCardSecondaryInsightPlain p
     _, Right p@(DetachedElement _) -> Right $ TopCardSecondaryInsightPlain p
     _, _ -> Left TextNotFoundError
     _, _ -> Left TextNotFoundError
 
 
-parseTopCardInsightContent :: Parser TopCardInsightContent
+parseTopCardInsightContent :: Parser (TopCardInsightContent DetachedNode)
 parseTopCardInsightContent n = do
 parseTopCardInsightContent n = do
   primary <- queryAndDetachOne ":scope > span:first-child span[aria-hidden=true]" n
   primary <- queryAndDetachOne ":scope > span:first-child span[aria-hidden=true]" n
   secondary <- queryManyAndParse
   secondary <- queryManyAndParse
@@ -106,7 +130,7 @@ parseTopCardInsightContent n = do
     _, _, Right el@(DetachedElement _) -> Right $ TopCardInsightContentSingle el
     _, _, Right el@(DetachedElement _) -> Right $ TopCardInsightContentSingle el
     _, _, _ -> Left TextNotFoundError
     _, _, _ -> Left TextNotFoundError
 
 
-parseTopCardInsight :: Parser TopCardInsight
+parseTopCardInsight :: Parser (TopCardInsight DetachedNode)
 parseTopCardInsight n = do
 parseTopCardInsight n = do
   icon <- queryAndDetachOne ":scope li-icon" n
   icon <- queryAndDetachOne ":scope li-icon" n
   svg <- queryAndDetachOne ":scope svg" n
   svg <- queryAndDetachOne ":scope svg" n
@@ -118,7 +142,7 @@ parseTopCardInsight n = do
     c <- content <|> actionButton
     c <- content <|> actionButton
   in TopCardInsight {icon: i, content: c}
   in TopCardInsight {icon: i, content: c}
 
 
-parseTopCardPrimaryDescription :: Parser TopCardPrimaryDescription
+parseTopCardPrimaryDescription :: Parser (TopCardPrimaryDescription DetachedNode)
 parseTopCardPrimaryDescription n = do
 parseTopCardPrimaryDescription n = do
   link <- queryAndDetachOne ":scope > a" n
   link <- queryAndDetachOne ":scope > a" n
   text <- detachNonEmptyTextChild n
   text <- detachNonEmptyTextChild n
@@ -129,7 +153,7 @@ parseTopCardPrimaryDescription n = do
     t <- text
     t <- text
   in TopCardPrimaryDescription {link: l, text: t, tvmText: hush tvmText}
   in TopCardPrimaryDescription {link: l, text: t, tvmText: hush tvmText}
 
 
-parseJobsUnifiedTopCardElement :: Parser JobsUnifiedTopCardElement
+parseJobsUnifiedTopCardElement :: Parser (JobsUnifiedTopCardElement DetachedNode)
 parseJobsUnifiedTopCardElement n = do
 parseJobsUnifiedTopCardElement n = do
   h1 <- queryAndDetachOne "h1.job-details-jobs-unified-top-card__job-title" n
   h1 <- queryAndDetachOne "h1.job-details-jobs-unified-top-card__job-title" n
   primary <- queryOneAndParse
   primary <- queryOneAndParse
@@ -147,9 +171,23 @@ parseJobsUnifiedTopCardElement n = do
 
 
   pure $ ado
   pure $ ado
     h <- h1
     h <- h1
+    p <- primary
   in JobsUnifiedTopCardElement {
   in JobsUnifiedTopCardElement {
     header: h,
     header: h,
-    primaryDescription: hush primary,
+    primaryDescription: p,
     insights: hush insights,
     insights: hush insights,
     actions: hush actions
     actions: hush 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

+ 3 - 3
test/JobsUnifiedTopCard.purs

@@ -123,7 +123,7 @@ testJobsUnifiedTopCard = do
                 tag: "svg"
                 tag: "svg"
               })
               })
             }) : Nil)))),
             }) : Nil)))),
-      primaryDescription: (Just (TopCardPrimaryDescription {
+      primaryDescription: (TopCardPrimaryDescription {
         link: (DetachedElement {
         link: (DetachedElement {
           classes: ("app-aware-link" : Nil),
           classes: ("app-aware-link" : Nil),
           content: "LINCOLN",
           content: "LINCOLN",
@@ -149,12 +149,12 @@ testJobsUnifiedTopCard = do
           }) : Nil
           }) : Nil
           ))
           ))
         ))
         ))
-      }))
+      })
     })
     })
   }
   }
 
 
 
 
-parseHeadCard ∷ Partial => Maybe (NonEmptyList LinkedInUIElement) → Effect (Either ParseError JobsUnifiedTopCardElement)
+parseHeadCard ∷ Partial => Maybe (NonEmptyList LinkedInUIElement) → Effect (Either ParseError (JobsUnifiedTopCardElement DetachedNode))
 parseHeadCard (Just l) = do
 parseHeadCard (Just l) = do
   parsed <- (\(LinkedInUIElement _ n) -> parseJobsUnifiedTopCardElement n) $ NEL.head l
   parsed <- (\(LinkedInUIElement _ n) -> parseJobsUnifiedTopCardElement n) $ NEL.head l
   pure $ parsed
   pure $ parsed