JobsUnifiedTopCard.purs 12 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306
  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 (List, NonEmptyList)
  10. import Data.Maybe (Maybe(..))
  11. import Data.Show.Generic (genericShow)
  12. import Data.Traversable (class Traversable, sequence, traverseDefault)
  13. import Data.Tuple (Tuple(..))
  14. import LinkedIn.CanBeQueried (class CanBeQueried, subQueryNEL, subQueryList, subQueryOne)
  15. import LinkedIn.QueryRunner (QueryError(..), queryList, queryOne, querySelf, queryText)
  16. import LinkedIn.Queryable (class Queryable, toNode)
  17. import Type.Proxy (Proxy(..))
  18. import Web.DOM.Node as N
  19. type JobsUnifiedTopCardElementObject a = {
  20. header :: a,
  21. primaryDescription :: TopCardPrimaryDescription a,
  22. insights :: List (TopCardInsight a),
  23. actions :: List (TopCardAction a)
  24. }
  25. newtype JobsUnifiedTopCardElement a = JobsUnifiedTopCardElement (JobsUnifiedTopCardElementObject a)
  26. type TopCardPrimaryDescriptionObject a = { link :: a, text :: a, tvmText :: List a }
  27. newtype TopCardPrimaryDescription a = TopCardPrimaryDescription (TopCardPrimaryDescriptionObject a)
  28. type TopCardInsightObject a = { icon :: a, content :: TopCardInsightContent a }
  29. newtype TopCardInsight a = TopCardInsight (TopCardInsightObject a)
  30. data TopCardInsightContent a =
  31. TopCardInsightContentSingle a
  32. | TopCardInsightContentSecondary {primary :: a, secondary :: NonEmptyList (TopCardSecondaryInsight a)}
  33. | TopCardInsightContentButton a
  34. data TopCardSecondaryInsight a =
  35. TopCardSecondaryInsightNested a
  36. | TopCardSecondaryInsightPlain a
  37. -- 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">
  38. -- LinkedIn Applcation : <button id="ember115" class="jobs-apply-button artdeco-button artdeco-button--3 artdeco-button--primary ember-view" data-job-id="3786945580">
  39. data TopCardAction a = TopCardActionButton a
  40. derive instance Generic (JobsUnifiedTopCardElement a) _
  41. derive instance Eq a => Eq (JobsUnifiedTopCardElement a)
  42. instance Show a => Show (JobsUnifiedTopCardElement a) where show = genericShow
  43. derive instance Functor JobsUnifiedTopCardElement
  44. instance Foldable JobsUnifiedTopCardElement where
  45. foldMap f (JobsUnifiedTopCardElement {header, primaryDescription, insights, actions}) =
  46. f header
  47. <> foldMap f primaryDescription
  48. <> foldMap (foldMap f) insights
  49. <> foldMap (foldMap f) actions
  50. foldl = \x -> foldlDefault x
  51. foldr = \x -> foldrDefault x
  52. instance Traversable JobsUnifiedTopCardElement where
  53. sequence (JobsUnifiedTopCardElement {header, primaryDescription, insights, actions}) = ado
  54. h <- header
  55. pd <- sequence primaryDescription
  56. i <- sequence (map sequence insights)
  57. a <- sequence (map sequence actions)
  58. in JobsUnifiedTopCardElement {header: h, primaryDescription: pd, insights: i, actions: a}
  59. traverse = \x -> traverseDefault x
  60. instance Queryable q => CanBeQueried q JobsUnifiedTopCardElement where
  61. query n = do
  62. header <- queryOne "h1.job-details-jobs-unified-top-card__job-title" n
  63. primaryDescription <- subQueryOne "div.job-details-jobs-unified-top-card__primary-description-container > div" n
  64. insights <- subQueryList "li.job-details-jobs-unified-top-card__job-insight" n
  65. actions <- subQueryList ".mt5 button" n
  66. pure $ JobsUnifiedTopCardElement {
  67. header,
  68. primaryDescription,
  69. insights,
  70. actions
  71. }
  72. derive instance Generic (TopCardPrimaryDescription a) _
  73. derive instance Eq a => Eq (TopCardPrimaryDescription a)
  74. instance Show a => Show (TopCardPrimaryDescription a) where show = genericShow
  75. derive instance Functor TopCardPrimaryDescription
  76. instance Foldable TopCardPrimaryDescription where
  77. foldMap f (TopCardPrimaryDescription {link, text, tvmText}) = f link <> f text <> (foldMap f) tvmText
  78. foldl = \x -> foldlDefault x
  79. foldr = \x -> foldrDefault x
  80. instance Traversable TopCardPrimaryDescription where
  81. sequence (TopCardPrimaryDescription {link, text, tvmText}) = ado
  82. l <- link
  83. t <- text
  84. tvm <- sequence tvmText
  85. in TopCardPrimaryDescription {link: l, text: t, tvmText: tvm}
  86. traverse = \x -> traverseDefault x
  87. instance Queryable q => CanBeQueried q TopCardPrimaryDescription where
  88. query n = do
  89. link <- queryOne ":scope > a" n
  90. text <- queryText 1 n
  91. tvmText <- queryList "span.tvm__text" n
  92. pure $ TopCardPrimaryDescription {link, text, tvmText: tvmText}
  93. derive instance Generic (TopCardInsight a) _
  94. derive instance Eq a => Eq (TopCardInsight a)
  95. instance Show a => Show (TopCardInsight a) where show = genericShow
  96. derive instance Functor TopCardInsight
  97. instance Foldable TopCardInsight where
  98. foldMap f (TopCardInsight {icon, content}) = f icon <> foldMap f content
  99. foldl = \x -> foldlDefault x
  100. foldr = \x -> foldrDefault x
  101. instance Traversable TopCardInsight where
  102. sequence (TopCardInsight {icon, content}) = ado
  103. i <- icon
  104. c <- sequence content
  105. in TopCardInsight {icon: i, content: c}
  106. traverse = \x -> traverseDefault x
  107. instance Queryable q => CanBeQueried q TopCardInsight where
  108. query n = do
  109. icon <- queryOne ":scope li-icon" n <|> queryOne ":scope svg" n <|> queryOne ":scope img" n
  110. content <- subQueryOne ":scope > span" n <|> subQueryOne ":scope > button" n
  111. pure $ TopCardInsight {icon, content}
  112. derive instance Generic (TopCardInsightContent a) _
  113. derive instance Eq a => Eq (TopCardInsightContent a)
  114. instance Show a => Show (TopCardInsightContent a) where show = genericShow
  115. derive instance Functor TopCardInsightContent
  116. instance Foldable TopCardInsightContent where
  117. foldMap f (TopCardInsightContentSingle a) = f a
  118. foldMap f (TopCardInsightContentButton a) = f a
  119. foldMap f (TopCardInsightContentSecondary {primary, secondary}) = f primary <> foldMap (foldMap f) secondary
  120. foldl = \x -> foldlDefault x
  121. foldr = \x -> foldrDefault x
  122. instance Traversable TopCardInsightContent where
  123. sequence (TopCardInsightContentSingle ins) = TopCardInsightContentSingle <$> ins
  124. sequence (TopCardInsightContentButton ins) = TopCardInsightContentButton <$> ins
  125. sequence (TopCardInsightContentSecondary {primary, secondary}) = ado
  126. p <- primary
  127. s <- sequence (map sequence secondary)
  128. in TopCardInsightContentSecondary {primary: p, secondary: s}
  129. traverse = \x -> traverseDefault x
  130. instance Queryable q => CanBeQueried q TopCardInsightContent where
  131. query n =
  132. queryTopCardInsightContentSecondary n
  133. <|> queryTopCardInsightContentButton n
  134. <|> queryTopCardInsightContentSingle n
  135. where
  136. queryTopCardInsightContentSingle n = do
  137. n' <- querySelf n
  138. pure $ TopCardInsightContentSingle n'
  139. queryTopCardInsightContentButton n =
  140. if type_ == "BUTTON"
  141. then do
  142. n' <- querySelf n
  143. pure $ TopCardInsightContentButton n'
  144. else throwError (QNodeUnexpectedType "BUTTON" type_)
  145. where type_ = N.nodeName $ toNode n
  146. queryTopCardInsightContentSecondary n = do
  147. primary <- queryOne ":scope > span:first-child span[aria-hidden=true]" n
  148. secondary <- subQueryNEL ":scope > span.job-details-jobs-unified-top-card__job-insight-view-model-secondary" n
  149. pure $ TopCardInsightContentSecondary {primary, secondary}
  150. derive instance Generic (TopCardSecondaryInsight a) _
  151. derive instance Eq a => Eq (TopCardSecondaryInsight a)
  152. instance Show a => Show (TopCardSecondaryInsight a) where show = genericShow
  153. derive instance Functor TopCardSecondaryInsight
  154. instance Foldable TopCardSecondaryInsight where
  155. foldMap f (TopCardSecondaryInsightNested a) = f a
  156. foldMap f (TopCardSecondaryInsightPlain a) = f a
  157. foldl = \x -> foldlDefault x
  158. foldr = \x -> foldrDefault x
  159. instance Traversable TopCardSecondaryInsight where
  160. sequence (TopCardSecondaryInsightNested ins) = TopCardSecondaryInsightNested <$> ins
  161. sequence (TopCardSecondaryInsightPlain ins) = TopCardSecondaryInsightPlain <$> ins
  162. traverse = \x -> traverseDefault x
  163. instance Queryable q => CanBeQueried q TopCardSecondaryInsight where
  164. query n = queryTopCardSecondaryInsightNested n <|> queryTopCardSecondaryInsightPlain n
  165. where
  166. queryTopCardSecondaryInsightNested n = do
  167. nested <- queryOne ":scope span[aria-hidden=true]" n
  168. pure $ TopCardSecondaryInsightNested nested
  169. queryTopCardSecondaryInsightPlain n = do
  170. n' <- querySelf n
  171. pure $ TopCardSecondaryInsightPlain n'
  172. derive instance Generic (TopCardAction a) _
  173. derive instance Eq a => Eq (TopCardAction a)
  174. instance Show a => Show (TopCardAction a) where show = genericShow
  175. derive instance Functor TopCardAction
  176. instance Foldable TopCardAction where
  177. foldMap f (TopCardActionButton a) = f a
  178. foldl = \x -> foldlDefault x
  179. foldr = \x -> foldrDefault x
  180. instance Traversable TopCardAction where
  181. sequence (TopCardActionButton app) = ado
  182. a <- app
  183. in TopCardActionButton a
  184. traverse = \x -> traverseDefault x
  185. instance Queryable q => CanBeQueried q TopCardAction where
  186. query n = do
  187. n' <- querySelf n
  188. pure $ TopCardActionButton n'
  189. toHeader ∷ forall a. JobsUnifiedTopCardElement a → a
  190. toHeader = view $ _top_card <<< prop (Proxy :: Proxy "header")
  191. toPrimaryDescriptionLink ∷ forall a. JobsUnifiedTopCardElement a → a
  192. toPrimaryDescriptionLink = view $ _top_card
  193. <<< prop (Proxy :: Proxy "primaryDescription")
  194. <<< _primary_description
  195. <<< prop (Proxy :: Proxy "link")
  196. toPrimaryDescriptionText ∷ forall a. JobsUnifiedTopCardElement a → a
  197. toPrimaryDescriptionText = view $ _top_card
  198. <<< prop (Proxy :: Proxy "primaryDescription")
  199. <<< _primary_description
  200. <<< prop (Proxy :: Proxy "text")
  201. _top_to_insights ∷ ∀ a. Traversal' (JobsUnifiedTopCardElement a) (TopCardInsight a)
  202. _top_to_insights = _top_card
  203. <<< prop (Proxy :: Proxy "insights")
  204. <<< traversed
  205. _insight_to_content = prop (Proxy :: Proxy "content")
  206. <<< traversed
  207. _top_to_action_buttons ∷ ∀ a. Traversal' (JobsUnifiedTopCardElement a) a
  208. _top_to_action_buttons = _top_card
  209. <<< prop (Proxy :: Proxy "actions")
  210. <<< traversed
  211. <<< _action_button
  212. _top_card ∷ forall a. Lens' (JobsUnifiedTopCardElement a) { actions ∷ List (TopCardAction a) , header ∷ a , insights ∷ List (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_button ∷ forall a. Lens' (TopCardAction a) a
  217. _action_button = lens' \(TopCardActionButton i) -> Tuple i \i' -> TopCardActionButton i'
  218. _primary_description ∷ ∀ a. Lens' (TopCardPrimaryDescription a) { link ∷ a , text ∷ a , tvmText ∷ List 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