JobsUnifiedTopCard.purs 12 KB

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