JobsUnifiedTopCard.purs 13 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325
  1. module LinkedIn.UI.Components.JobsUnifiedTopCard where
  2. import Prelude
  3. import Control.Alt ((<|>))
  4. import Control.Monad.Error.Class (throwError)
  5. import Data.Foldable (class Foldable, foldMap, foldlDefault, foldrDefault)
  6. import Data.Generic.Rep (class Generic)
  7. import Data.Lens (Lens', Prism', Traversal', lens', prism', traversed, view)
  8. import Data.Lens.Record (prop)
  9. import Data.List.Types (NonEmptyList)
  10. import Data.Maybe (Maybe(..))
  11. import Data.Show.Generic (genericShow)
  12. import Data.Traversable (class Traversable, sequence, traverse, traverseDefault)
  13. import Data.Tuple (Tuple(..))
  14. import LinkedIn.QueryRunner (QueryError(..), QueryRunner, ignoreNotFound, queryAll, queryOne, queryText)
  15. import Type.Proxy (Proxy(..))
  16. import Web.DOM (Node)
  17. import Web.DOM.Node as N
  18. data JobsUnifiedTopCardElement a = JobsUnifiedTopCardElement {
  19. header :: a,
  20. primaryDescription :: TopCardPrimaryDescription a,
  21. insights :: Maybe (NonEmptyList (TopCardInsight a)),
  22. actions :: Maybe (NonEmptyList (TopCardAction a))
  23. }
  24. data TopCardPrimaryDescription a = TopCardPrimaryDescription {
  25. link :: a,
  26. text :: a,
  27. tvmText :: Maybe (NonEmptyList a)
  28. }
  29. data TopCardInsight a = TopCardInsight {
  30. icon :: a,
  31. content :: TopCardInsightContent a
  32. }
  33. data TopCardInsightContent a =
  34. TopCardInsightContentSingle a
  35. | TopCardInsightContentSecondary {primary :: a, secondary :: NonEmptyList (TopCardSecondaryInsight a)}
  36. | TopCardInsightContentButton a
  37. data TopCardSecondaryInsight a =
  38. TopCardSecondaryInsightNested a
  39. | TopCardSecondaryInsightPlain a
  40. -- 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">
  41. -- LinkedIn Applcation : <button id="ember115" class="jobs-apply-button artdeco-button artdeco-button--3 artdeco-button--primary ember-view" data-job-id="3786945580">
  42. data TopCardAction a = TopCardActionButton a
  43. derive instance Generic (JobsUnifiedTopCardElement a) _
  44. derive instance Eq a => Eq (JobsUnifiedTopCardElement a)
  45. instance Show a => Show (JobsUnifiedTopCardElement a) where
  46. show = genericShow
  47. derive instance Functor JobsUnifiedTopCardElement
  48. instance Foldable JobsUnifiedTopCardElement where
  49. foldMap f (JobsUnifiedTopCardElement {header, primaryDescription, insights, actions}) =
  50. f header
  51. <> foldMap f primaryDescription
  52. <> foldMap (foldMap (foldMap f)) insights
  53. <> foldMap (foldMap (foldMap f)) actions
  54. foldl = \x -> foldlDefault x
  55. foldr = \x -> foldrDefault x
  56. instance Traversable JobsUnifiedTopCardElement where
  57. sequence (JobsUnifiedTopCardElement {header, primaryDescription, insights, actions}) = ado
  58. h <- header
  59. pd <- sequence primaryDescription
  60. i <- traverseMayNel insights
  61. a <- traverseMayNel actions
  62. in JobsUnifiedTopCardElement {header: h, primaryDescription: pd, insights: i, actions: a}
  63. traverse = \x -> traverseDefault x
  64. traverseMayNel :: forall m t a. Traversable t => Applicative m => Maybe(NonEmptyList (t (m a))) -> m (Maybe (NonEmptyList (t a)))
  65. traverseMayNel (Just o) = map pure (sequence (map sequence o))
  66. traverseMayNel Nothing = pure Nothing
  67. derive instance Generic (TopCardPrimaryDescription a) _
  68. derive instance Eq a => Eq (TopCardPrimaryDescription a)
  69. instance Show a => Show (TopCardPrimaryDescription a) where
  70. show = genericShow
  71. derive instance Functor TopCardPrimaryDescription
  72. instance Foldable TopCardPrimaryDescription where
  73. foldMap f (TopCardPrimaryDescription {link, text, tvmText}) = f link <> f text <> foldMap (foldMap f) tvmText
  74. foldl = \x -> foldlDefault x
  75. foldr = \x -> foldrDefault x
  76. instance Traversable TopCardPrimaryDescription where
  77. sequence (TopCardPrimaryDescription {link, text, tvmText}) = ado
  78. l <- link
  79. t <- text
  80. tvm <- sequence (map sequence tvmText)
  81. in TopCardPrimaryDescription {link: l, text: t, tvmText: tvm}
  82. traverse = \x -> traverseDefault x
  83. derive instance Generic (TopCardInsight a) _
  84. derive instance Eq a => Eq (TopCardInsight a)
  85. instance Show a => Show (TopCardInsight a) where
  86. show = genericShow
  87. derive instance Functor TopCardInsight
  88. instance Foldable TopCardInsight where
  89. foldMap f (TopCardInsight {icon, content}) = f icon <> foldMap f content
  90. foldl = \x -> foldlDefault x
  91. foldr = \x -> foldrDefault x
  92. instance Traversable TopCardInsight where
  93. sequence (TopCardInsight {icon, content}) = ado
  94. i <- icon
  95. c <- sequence content
  96. in TopCardInsight {icon: i, content: c}
  97. traverse = \x -> traverseDefault x
  98. derive instance Generic (TopCardInsightContent a) _
  99. derive instance Eq a => Eq (TopCardInsightContent a)
  100. instance Show a => Show (TopCardInsightContent a) where
  101. show = genericShow
  102. derive instance Functor TopCardInsightContent
  103. instance Foldable TopCardInsightContent where
  104. foldMap f (TopCardInsightContentSingle a) = f a
  105. foldMap f (TopCardInsightContentButton a) = f a
  106. foldMap f (TopCardInsightContentSecondary {primary, secondary}) = f primary <> foldMap (foldMap f) secondary
  107. foldl = \x -> foldlDefault x
  108. foldr = \x -> foldrDefault x
  109. instance Traversable TopCardInsightContent where
  110. sequence (TopCardInsightContentSingle ins) = TopCardInsightContentSingle <$> ins
  111. sequence (TopCardInsightContentButton ins) = TopCardInsightContentButton <$> ins
  112. sequence (TopCardInsightContentSecondary {primary, secondary}) = ado
  113. p <- primary
  114. s <- sequence (map sequence secondary)
  115. in TopCardInsightContentSecondary {primary: p, secondary: s}
  116. traverse = \x -> traverseDefault x
  117. derive instance Generic (TopCardSecondaryInsight a) _
  118. derive instance Eq a => Eq (TopCardSecondaryInsight a)
  119. instance Show a => Show (TopCardSecondaryInsight a) where
  120. show = genericShow
  121. derive instance Functor TopCardSecondaryInsight
  122. instance Foldable TopCardSecondaryInsight where
  123. foldMap f (TopCardSecondaryInsightNested a) = f a
  124. foldMap f (TopCardSecondaryInsightPlain a) = f a
  125. foldl = \x -> foldlDefault x
  126. foldr = \x -> foldrDefault x
  127. instance Traversable TopCardSecondaryInsight where
  128. sequence (TopCardSecondaryInsightNested ins) = TopCardSecondaryInsightNested <$> ins
  129. sequence (TopCardSecondaryInsightPlain ins) = TopCardSecondaryInsightPlain <$> ins
  130. traverse = \x -> traverseDefault x
  131. derive instance Generic (TopCardAction a) _
  132. derive instance Eq a => Eq (TopCardAction a)
  133. instance Show a => Show (TopCardAction a) where
  134. show = genericShow
  135. derive instance Functor TopCardAction
  136. instance Foldable TopCardAction where
  137. foldMap f (TopCardActionButton a) = f a
  138. foldl = \x -> foldlDefault x
  139. foldr = \x -> foldrDefault x
  140. instance Traversable TopCardAction where
  141. sequence (TopCardActionButton app) = ado
  142. a <- app
  143. in TopCardActionButton a
  144. traverse = \x -> traverseDefault x
  145. queryTopCardAction :: QueryRunner (TopCardAction Node)
  146. queryTopCardAction n = pure $ TopCardActionButton n
  147. queryTopCardSecondaryInsightNested :: QueryRunner (TopCardSecondaryInsight Node)
  148. queryTopCardSecondaryInsightNested n = do
  149. nested <- queryOne ":scope span[aria-hidden=true]" n
  150. pure $ TopCardSecondaryInsightNested nested
  151. queryTopCardSecondaryInsightPlain :: QueryRunner (TopCardSecondaryInsight Node)
  152. queryTopCardSecondaryInsightPlain n = pure $ TopCardSecondaryInsightPlain n
  153. queryTopCardSecondaryInsight :: QueryRunner (TopCardSecondaryInsight Node)
  154. queryTopCardSecondaryInsight n =
  155. queryTopCardSecondaryInsightNested n <|> queryTopCardSecondaryInsightPlain n
  156. queryTopCardInsightContentSingle :: QueryRunner (TopCardInsightContent Node)
  157. queryTopCardInsightContentSingle n = pure $ TopCardInsightContentSingle n
  158. queryTopCardInsightContentButton :: QueryRunner (TopCardInsightContent Node)
  159. queryTopCardInsightContentButton n =
  160. if type_ == "BUTTON"
  161. then pure $ TopCardInsightContentButton n
  162. else throwError (QNodeUnexpectedType "BUTTON" type_)
  163. where type_ = N.nodeName n
  164. queryTopCardInsightContentSecondary :: QueryRunner (TopCardInsightContent Node)
  165. queryTopCardInsightContentSecondary n = do
  166. primary <- queryOne ":scope > span:first-child span[aria-hidden=true]" n
  167. secondary <- traverse queryTopCardSecondaryInsight
  168. =<< queryAll ":scope > span.job-details-jobs-unified-top-card__job-insight-view-model-secondary" n
  169. pure $ TopCardInsightContentSecondary {primary, secondary}
  170. queryTopCardInsightContent :: QueryRunner (TopCardInsightContent Node)
  171. queryTopCardInsightContent n =
  172. queryTopCardInsightContentSecondary n
  173. <|> queryTopCardInsightContentButton n
  174. <|> queryTopCardInsightContentSingle n
  175. queryTopCardInsight :: QueryRunner (TopCardInsight Node)
  176. queryTopCardInsight n = do
  177. icon <- queryOne ":scope li-icon" n <|> queryOne ":scope svg" n
  178. content <- queryTopCardInsightContent =<< getContentNode n
  179. pure $ TopCardInsight {icon, content}
  180. where
  181. getContentNode n' = queryOne ":scope > span" n' <|> queryOne ":scope > button" n'
  182. queryTopCardPrimaryDescription :: QueryRunner (TopCardPrimaryDescription Node)
  183. queryTopCardPrimaryDescription n = do
  184. link <- queryOne ":scope > a" n
  185. text <- queryText 1 n
  186. tvmText <- ignoreNotFound $ queryAll "span.tvm__text" n
  187. pure $ TopCardPrimaryDescription {link, text, tvmText: tvmText}
  188. queryJobsUnifiedTopCardElement :: QueryRunner (JobsUnifiedTopCardElement Node)
  189. queryJobsUnifiedTopCardElement n = do
  190. header <- queryOne "h1.job-details-jobs-unified-top-card__job-title" n
  191. primaryDescription <- queryTopCardPrimaryDescription
  192. =<< queryOne "div.job-details-jobs-unified-top-card__primary-description-container > div" n
  193. insights <- ignoreNotFound
  194. <<< traverse queryTopCardInsight
  195. =<< queryAll "li.job-details-jobs-unified-top-card__job-insight" n
  196. actions <- ignoreNotFound <<< traverse queryTopCardAction =<< queryAll ".mt5 button" n
  197. pure $ JobsUnifiedTopCardElement {
  198. header,
  199. primaryDescription,
  200. insights,
  201. actions
  202. }
  203. toHeader ∷ forall a. JobsUnifiedTopCardElement a → a
  204. toHeader = view $ _top_card <<< prop (Proxy :: Proxy "header")
  205. toPrimaryDescriptionLink ∷ forall a. JobsUnifiedTopCardElement a → a
  206. toPrimaryDescriptionLink = view $ _top_card
  207. <<< prop (Proxy :: Proxy "primaryDescription")
  208. <<< _primary_description
  209. <<< prop (Proxy :: Proxy "link")
  210. toPrimaryDescriptionText ∷ forall a. JobsUnifiedTopCardElement a → a
  211. toPrimaryDescriptionText = view $ _top_card
  212. <<< prop (Proxy :: Proxy "primaryDescription")
  213. <<< _primary_description
  214. <<< prop (Proxy :: Proxy "text")
  215. _top_to_insights ∷ ∀ a. Traversal' (JobsUnifiedTopCardElement a) (TopCardInsight a)
  216. _top_to_insights = _top_card
  217. <<< prop (Proxy :: Proxy "insights")
  218. <<< traversed
  219. <<< traversed
  220. _insight_to_content = prop (Proxy :: Proxy "content")
  221. <<< traversed
  222. _top_to_action_buttons ∷ ∀ a. Traversal' (JobsUnifiedTopCardElement a) a
  223. _top_to_action_buttons = _top_card
  224. <<< prop (Proxy :: Proxy "actions")
  225. <<< traversed
  226. <<< traversed
  227. <<< _action_button
  228. _top_card ∷ forall a. Lens' (JobsUnifiedTopCardElement a) { actions ∷ Maybe (NonEmptyList (TopCardAction a)) , header ∷ a , insights ∷ Maybe (NonEmptyList (TopCardInsight a)) , primaryDescription ∷ TopCardPrimaryDescription a }
  229. _top_card = lens' \(JobsUnifiedTopCardElement c) -> Tuple c \c' -> JobsUnifiedTopCardElement c'
  230. _insight ∷ forall a. Lens' (TopCardInsight a) { content ∷ TopCardInsightContent a , icon ∷ a }
  231. _insight = lens' \(TopCardInsight i) -> Tuple i \i' -> TopCardInsight i'
  232. _action_button ∷ forall a. Lens' (TopCardAction a) a
  233. _action_button = lens' \(TopCardActionButton i) -> Tuple i \i' -> TopCardActionButton i'
  234. _primary_description ∷ ∀ a. Lens' (TopCardPrimaryDescription a) { link ∷ a , text ∷ a , tvmText ∷ Maybe (NonEmptyList a) }
  235. _primary_description = lens' \(TopCardPrimaryDescription i) -> Tuple i \i' -> TopCardPrimaryDescription i'
  236. _insight_content_single ∷ forall a. Prism' (TopCardInsightContent a) a
  237. _insight_content_single = prism' TopCardInsightContentSingle case _ of
  238. TopCardInsightContentSingle i -> Just i
  239. _ -> Nothing
  240. _insight_content_button ∷ forall a. Prism' (TopCardInsightContent a) a
  241. _insight_content_button = prism' TopCardInsightContentButton case _ of
  242. TopCardInsightContentButton i -> Just i
  243. _ -> Nothing
  244. _insight_content_secondary ∷ forall a. Prism' (TopCardInsightContent a) { primary ∷ a , secondary ∷ NonEmptyList (TopCardSecondaryInsight a) }
  245. _insight_content_secondary = prism' TopCardInsightContentSecondary case _ of
  246. TopCardInsightContentSecondary i -> Just i
  247. _ -> Nothing
  248. _insight_content_secondary_nested ∷ forall a. Prism' (TopCardSecondaryInsight a) a
  249. _insight_content_secondary_nested = prism' TopCardSecondaryInsightNested case _ of
  250. TopCardSecondaryInsightNested i -> Just i
  251. _ -> Nothing
  252. _insight_content_secondary_plain ∷ forall a. Prism' (TopCardSecondaryInsight a) a
  253. _insight_content_secondary_plain = prism' TopCardSecondaryInsightPlain case _ of
  254. TopCardSecondaryInsightPlain i -> Just i
  255. _ -> Nothing