JobsUnifiedTopCard.purs 14 KB

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