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

Turn all queryX functions into QueryRunner'

jherve 1 год назад
Родитель
Сommit
42bd0601ca

+ 5 - 3
src/LinkedIn/QueryRunner.purs

@@ -2,8 +2,7 @@ module LinkedIn.QueryRunner where
 
 import Prelude
 
-import Control.Alt ((<|>))
-import Control.Monad.Except (ExceptT(..), mapExceptT, runExceptT)
+import Control.Monad.Except (ExceptT(..), except, mapExceptT, runExceptT)
 import Data.Argonaut.Encode (class EncodeJson)
 import Data.Argonaut.Encode.Generic (genericEncodeJson)
 import Data.Array as A
@@ -14,7 +13,7 @@ import Data.Maybe (Maybe(..))
 import Data.Show.Generic (genericShow)
 import Data.Traversable (traverse)
 import Effect (Effect)
-import LinkedIn.Queryable (class Queryable, getChildrenArray, queryAllNodes, queryOneNode)
+import LinkedIn.Queryable (class Queryable, getChildrenArray, queryAllNodes, queryOneNode, toNode)
 import Web.DOM (Node)
 import Web.DOM.Text as T
 
@@ -58,6 +57,9 @@ ignoreErrors = mapExceptT (map ignoreErrors')
       (Left _) -> Right Nothing
       (Right n') -> Right (Just n')
 
+querySelf ∷ forall q. Queryable q => QueryRunner' q Node
+querySelf node = except $ Right $ toNode node
+
 queryOne ∷ forall q. Queryable q => String → QueryRunner' q Node
 queryOne selector node = ExceptT $ do
   maybeNode <- queryOneNode selector node

+ 4 - 0
src/LinkedIn/Queryable.purs

@@ -17,6 +17,7 @@ import Web.DOM.ParentNode (QuerySelector(..), querySelector, querySelectorAll)
 -- A light abstraction layer above the DOM query API
 
 class Queryable a where
+  toNode :: a -> Node
   toParentNode :: a -> ParentNode
   toChildrenArray :: a -> Effect (Array Node)
 
@@ -29,11 +30,14 @@ instance Queryable Node where
           he <- E.fromNode node
           pure $ E.toParentNode he
 
+  toNode = identity
+
   toChildrenArray n = do
     children <- N.childNodes n
     NL.toArray children
 
 instance Queryable Document where
+  toNode = D.toNode
   toParentNode = D.toParentNode
   toChildrenArray d = toChildrenArray $ D.toNode d
 

+ 11 - 6
src/LinkedIn/UI/Components/ArtDeco.purs

@@ -11,7 +11,9 @@ import Data.Maybe (Maybe)
 import Data.Show.Generic (genericShow)
 import Data.Traversable (class Traversable, sequence, traverseDefault)
 import Data.Tuple (Tuple(..))
-import LinkedIn.QueryRunner (QueryRunner, ignoreNotFound, queryAll, queryOne, subQueryMany, subQueryOne)
+import LinkedIn.CanBeQueried (class CanBeQueried)
+import LinkedIn.QueryRunner (QueryRunner', ignoreNotFound, queryAll, queryOne, subQueryMany, subQueryOne)
+import LinkedIn.Queryable (class Queryable)
 import Type.Proxy (Proxy(..))
 import Web.DOM (Node)
 
@@ -56,6 +58,9 @@ instance Traversable ArtDecoPvsEntitySubComponent where
 
   traverse = \x -> traverseDefault x
 
+instance Queryable q => CanBeQueried q ArtDecoPvsEntitySubComponent where
+  query' = queryArtDecoPvsEntitySubComponent
+
 derive instance Generic (ArtDecoCenterContent a) _
 derive instance Eq a => Eq(ArtDecoCenterContent a)
 instance Show a => Show(ArtDecoCenterContent a) where
@@ -136,17 +141,17 @@ instance Traversable ArtDecoPvsEntity where
 
   traverse = \x -> traverseDefault x
 
-queryArtDecoPvsEntitySubComponent ∷ QueryRunner (ArtDecoPvsEntitySubComponent Node)
+queryArtDecoPvsEntitySubComponent ∷ forall q. Queryable q=> QueryRunner' q (ArtDecoPvsEntitySubComponent Node)
 queryArtDecoPvsEntitySubComponent n = do
   content <- ignoreNotFound $ queryOne "span[aria-hidden=true]" n
   pure $ ArtDecoPvsEntitySubComponent content
 
-queryArtDecoCenterContent ∷ QueryRunner (ArtDecoCenterContent Node)
+queryArtDecoCenterContent :: forall q. Queryable q => QueryRunner' q (ArtDecoCenterContent Node)
 queryArtDecoCenterContent n = do
   sc <- subQueryMany queryArtDecoPvsEntitySubComponent ":scope > ul > li" n
   pure $ ArtDecoCenterContent sc
 
-queryArtDecoCenterHeader ∷ QueryRunner (ArtDecoCenterHeader Node)
+queryArtDecoCenterHeader :: forall q. Queryable q => QueryRunner' q (ArtDecoCenterHeader Node)
 queryArtDecoCenterHeader n = do
   bold <- queryOne ":scope div.t-bold > span[aria-hidden=true]" n
   normal <-
@@ -158,14 +163,14 @@ queryArtDecoCenterHeader n = do
 
   pure $ ArtDecoCenterHeader {bold, normal, light}
 
-queryArtDecoCenter ∷ QueryRunner (ArtDecoCenter Node)
+queryArtDecoCenter :: forall q. Queryable q => QueryRunner' q (ArtDecoCenter Node)
 queryArtDecoCenter n = do
   header <- subQueryOne queryArtDecoCenterHeader ":scope > div" n
   content <- subQueryOne queryArtDecoCenterContent ":scope > div.pvs-entity__sub-components" n
 
   pure $ ArtDecoCenter {header, content}
 
-queryArtDecoPvsEntity ∷ QueryRunner (ArtDecoPvsEntity Node)
+queryArtDecoPvsEntity :: forall q. Queryable q => QueryRunner' q (ArtDecoPvsEntity Node)
 queryArtDecoPvsEntity n = do
   center <- subQueryOne queryArtDecoCenter ":scope > div.display-flex" n
   pure $ ArtDecoPvsEntity {side: unit, center}

+ 3 - 2
src/LinkedIn/UI/Components/ArtDecoCard.purs

@@ -13,8 +13,9 @@ import Data.Maybe (Maybe)
 import Data.Show.Generic (genericShow)
 import Data.Traversable (class Traversable, sequence, traverseDefault)
 import Data.Tuple (Tuple(..))
+import LinkedIn.QueryRunner (QueryRunner', subQueryOne)
+import LinkedIn.Queryable (class Queryable)
 import LinkedIn.UI.Components.ArtDeco (ArtDecoPvsEntity, _pvs_to_header_bold, _pvs_to_header_light, _pvs_to_header_normal, _pvs_to_subcomponents, queryArtDecoPvsEntity)
-import LinkedIn.QueryRunner (QueryRunner, subQueryOne)
 import Type.Proxy (Proxy(..))
 import Web.DOM (Node)
 
@@ -42,7 +43,7 @@ instance Traversable ArtDecoCardElement where
 
   traverse = \x -> traverseDefault x
 
-queryArtDecoCard :: QueryRunner (ArtDecoCardElement Node)
+queryArtDecoCard :: forall q. Queryable q => QueryRunner' q (ArtDecoCardElement Node)
 queryArtDecoCard n = do
   pvs_entity <- subQueryOne queryArtDecoPvsEntity ":scope div.pvs-entity--padded" n
   pure $ ArtDecoCardElement {pvs_entity}

+ 3 - 2
src/LinkedIn/UI/Components/ArtDecoTab.purs

@@ -13,8 +13,9 @@ import Data.Maybe (Maybe)
 import Data.Show.Generic (genericShow)
 import Data.Traversable (class Traversable, sequence, traverseDefault)
 import Data.Tuple (Tuple(..))
+import LinkedIn.QueryRunner (QueryRunner', subQueryOne)
+import LinkedIn.Queryable (class Queryable)
 import LinkedIn.UI.Components.ArtDeco (ArtDecoPvsEntity, _pvs_to_header_bold, _pvs_to_header_light, _pvs_to_header_normal, _pvs_to_subcomponents, queryArtDecoPvsEntity)
-import LinkedIn.QueryRunner (QueryRunner, subQueryOne)
 import Type.Proxy (Proxy(..))
 import Web.DOM (Node)
 
@@ -42,7 +43,7 @@ instance Traversable ArtDecoTabElement where
 
   traverse = \x -> traverseDefault x
 
-queryArtDecoTab :: QueryRunner (ArtDecoTabElement Node)
+queryArtDecoTab :: forall q. Queryable q => QueryRunner' q (ArtDecoTabElement Node)
 queryArtDecoTab n = do
   pvs_entity <- subQueryOne queryArtDecoPvsEntity ":scope div.pvs-entity--padded" n
   pure $ ArtDecoTabElement {pvs_entity}

+ 26 - 17
src/LinkedIn/UI/Components/JobsUnifiedTopCard.purs

@@ -13,7 +13,8 @@ import Data.Maybe (Maybe(..))
 import Data.Show.Generic (genericShow)
 import Data.Traversable (class Traversable, sequence, traverse, traverseDefault)
 import Data.Tuple (Tuple(..))
-import LinkedIn.QueryRunner (QueryError(..), QueryRunner, ignoreNotFound, queryAll, queryOne, queryText)
+import LinkedIn.QueryRunner (QueryError(..), QueryRunner, QueryRunner', ignoreNotFound, queryAll, queryOne, querySelf, queryText)
+import LinkedIn.Queryable (class Queryable, toNode)
 import Type.Proxy (Proxy(..))
 import Web.DOM (Node)
 import Web.DOM.Node as N
@@ -182,46 +183,54 @@ instance Traversable TopCardAction where
 
   traverse = \x -> traverseDefault x
 
-queryTopCardAction :: QueryRunner (TopCardAction Node)
-queryTopCardAction n = pure $ TopCardActionButton n
+queryTopCardAction :: forall q. Queryable q => QueryRunner' q (TopCardAction Node)
+queryTopCardAction n = do
+  n' <- querySelf n
+  pure $ TopCardActionButton n'
 
-queryTopCardSecondaryInsightNested :: QueryRunner (TopCardSecondaryInsight Node)
+queryTopCardSecondaryInsightNested :: forall q. Queryable q => QueryRunner' q (TopCardSecondaryInsight Node)
 queryTopCardSecondaryInsightNested n = do
   nested <- queryOne ":scope span[aria-hidden=true]" n
   pure $ TopCardSecondaryInsightNested nested
 
-queryTopCardSecondaryInsightPlain :: QueryRunner (TopCardSecondaryInsight Node)
-queryTopCardSecondaryInsightPlain n = pure $ TopCardSecondaryInsightPlain n
+queryTopCardSecondaryInsightPlain :: forall q. Queryable q => QueryRunner' q (TopCardSecondaryInsight Node)
+queryTopCardSecondaryInsightPlain n = do
+  n' <- querySelf n
+  pure $ TopCardSecondaryInsightPlain n'
 
-queryTopCardSecondaryInsight :: QueryRunner (TopCardSecondaryInsight Node)
+queryTopCardSecondaryInsight :: forall q. Queryable q => QueryRunner' q (TopCardSecondaryInsight Node)
 queryTopCardSecondaryInsight n =
   queryTopCardSecondaryInsightNested n <|> queryTopCardSecondaryInsightPlain n
 
-queryTopCardInsightContentSingle :: QueryRunner (TopCardInsightContent Node)
-queryTopCardInsightContentSingle n = pure $ TopCardInsightContentSingle n
+queryTopCardInsightContentSingle :: forall q. Queryable q => QueryRunner' q (TopCardInsightContent Node)
+queryTopCardInsightContentSingle n = do
+  n' <- querySelf n
+  pure $ TopCardInsightContentSingle n'
 
-queryTopCardInsightContentButton :: QueryRunner (TopCardInsightContent Node)
+queryTopCardInsightContentButton :: forall q. Queryable q => QueryRunner' q (TopCardInsightContent Node)
 queryTopCardInsightContentButton n =
   if type_ == "BUTTON"
-  then pure $ TopCardInsightContentButton n
+  then do
+    n' <- querySelf n
+    pure $ TopCardInsightContentButton n'
   else throwError (QNodeUnexpectedType "BUTTON" type_)
 
-  where type_ = N.nodeName n
+  where type_ = N.nodeName $ toNode n
 
-queryTopCardInsightContentSecondary :: QueryRunner (TopCardInsightContent Node)
+queryTopCardInsightContentSecondary :: forall q. Queryable q => QueryRunner' q (TopCardInsightContent Node)
 queryTopCardInsightContentSecondary n = do
   primary <- queryOne ":scope > span:first-child span[aria-hidden=true]" n
   secondary <- traverse queryTopCardSecondaryInsight
                 =<< queryAll ":scope > span.job-details-jobs-unified-top-card__job-insight-view-model-secondary" n
   pure $ TopCardInsightContentSecondary {primary, secondary}
 
-queryTopCardInsightContent :: QueryRunner (TopCardInsightContent Node)
+queryTopCardInsightContent :: forall q. Queryable q => QueryRunner' q (TopCardInsightContent Node)
 queryTopCardInsightContent n =
   queryTopCardInsightContentSecondary n
   <|> queryTopCardInsightContentButton n
   <|> queryTopCardInsightContentSingle n
 
-queryTopCardInsight :: QueryRunner (TopCardInsight Node)
+queryTopCardInsight :: forall q. Queryable q => QueryRunner' q (TopCardInsight Node)
 queryTopCardInsight n = do
   icon <- queryOne ":scope li-icon" n <|> queryOne ":scope svg" n
   content <- queryTopCardInsightContent =<< getContentNode n
@@ -231,7 +240,7 @@ queryTopCardInsight n = do
   where
     getContentNode n' = queryOne ":scope > span" n' <|> queryOne ":scope > button" n'
 
-queryTopCardPrimaryDescription :: QueryRunner (TopCardPrimaryDescription Node)
+queryTopCardPrimaryDescription :: forall q. Queryable q => QueryRunner' q (TopCardPrimaryDescription Node)
 queryTopCardPrimaryDescription n = do
   link <- queryOne ":scope > a" n
   text <- queryText 1 n
@@ -239,7 +248,7 @@ queryTopCardPrimaryDescription n = do
 
   pure $ TopCardPrimaryDescription {link, text, tvmText: tvmText}
 
-queryJobsUnifiedTopCardElement :: QueryRunner (JobsUnifiedTopCardElement Node)
+queryJobsUnifiedTopCardElement :: forall q. Queryable q => QueryRunner' q (JobsUnifiedTopCardElement Node)
 queryJobsUnifiedTopCardElement n = do
   header <- queryOne "h1.job-details-jobs-unified-top-card__job-title" n
   primaryDescription <- queryTopCardPrimaryDescription