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

Add CanBeQueried typeclass and instances

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

+ 8 - 0
src/LinkedIn/CanBeQueried.purs

@@ -0,0 +1,8 @@
+module LinkedIn.CanBeQueried where
+
+import LinkedIn.QueryRunner (QueryRunner')
+import LinkedIn.Queryable (class Queryable)
+import Web.DOM (Node)
+
+class Queryable root <= CanBeQueried root t where
+  query' :: QueryRunner' root (t Node)

+ 12 - 0
src/LinkedIn/UI/Components/ArtDeco.purs

@@ -80,6 +80,9 @@ instance Traversable ArtDecoCenterContent where
 
 
   traverse = \x -> traverseDefault x
   traverse = \x -> traverseDefault x
 
 
+instance Queryable q => CanBeQueried q ArtDecoCenterContent where
+  query' = queryArtDecoCenterContent
+
 derive instance Generic (ArtDecoCenterHeader a) _
 derive instance Generic (ArtDecoCenterHeader a) _
 derive instance Eq a => Eq(ArtDecoCenterHeader a)
 derive instance Eq a => Eq(ArtDecoCenterHeader a)
 instance Show a => Show(ArtDecoCenterHeader a) where
 instance Show a => Show(ArtDecoCenterHeader a) where
@@ -101,6 +104,9 @@ instance Traversable ArtDecoCenterHeader where
 
 
   traverse = \x -> traverseDefault x
   traverse = \x -> traverseDefault x
 
 
+instance Queryable q => CanBeQueried q ArtDecoCenterHeader where
+  query' = queryArtDecoCenterHeader
+
 derive instance Generic (ArtDecoCenter a) _
 derive instance Generic (ArtDecoCenter a) _
 derive instance Eq a => Eq(ArtDecoCenter a)
 derive instance Eq a => Eq(ArtDecoCenter a)
 instance Show a => Show(ArtDecoCenter a) where
 instance Show a => Show(ArtDecoCenter a) where
@@ -121,6 +127,9 @@ instance Traversable ArtDecoCenter where
 
 
   traverse = \x -> traverseDefault x
   traverse = \x -> traverseDefault x
 
 
+instance Queryable q => CanBeQueried q ArtDecoCenter where
+  query' = queryArtDecoCenter
+
 derive instance Generic (ArtDecoPvsEntity a) _
 derive instance Generic (ArtDecoPvsEntity a) _
 derive instance Eq a => Eq(ArtDecoPvsEntity a)
 derive instance Eq a => Eq(ArtDecoPvsEntity a)
 instance Show a => Show(ArtDecoPvsEntity a) where
 instance Show a => Show(ArtDecoPvsEntity a) where
@@ -141,6 +150,9 @@ instance Traversable ArtDecoPvsEntity where
 
 
   traverse = \x -> traverseDefault x
   traverse = \x -> traverseDefault x
 
 
+instance Queryable q => CanBeQueried q ArtDecoPvsEntity where
+  query' = queryArtDecoPvsEntity
+
 queryArtDecoPvsEntitySubComponent ∷ forall q. Queryable q=> QueryRunner' q (ArtDecoPvsEntitySubComponent Node)
 queryArtDecoPvsEntitySubComponent ∷ forall q. Queryable q=> QueryRunner' q (ArtDecoPvsEntitySubComponent Node)
 queryArtDecoPvsEntitySubComponent n = do
 queryArtDecoPvsEntitySubComponent n = do
   content <- ignoreNotFound $ queryOne "span[aria-hidden=true]" n
   content <- ignoreNotFound $ queryOne "span[aria-hidden=true]" n

+ 4 - 0
src/LinkedIn/UI/Components/ArtDecoCard.purs

@@ -13,6 +13,7 @@ import Data.Maybe (Maybe)
 import Data.Show.Generic (genericShow)
 import Data.Show.Generic (genericShow)
 import Data.Traversable (class Traversable, sequence, traverseDefault)
 import Data.Traversable (class Traversable, sequence, traverseDefault)
 import Data.Tuple (Tuple(..))
 import Data.Tuple (Tuple(..))
+import LinkedIn.CanBeQueried (class CanBeQueried)
 import LinkedIn.QueryRunner (QueryRunner', subQueryOne)
 import LinkedIn.QueryRunner (QueryRunner', subQueryOne)
 import LinkedIn.Queryable (class Queryable)
 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.UI.Components.ArtDeco (ArtDecoPvsEntity, _pvs_to_header_bold, _pvs_to_header_light, _pvs_to_header_normal, _pvs_to_subcomponents, queryArtDecoPvsEntity)
@@ -43,6 +44,9 @@ instance Traversable ArtDecoCardElement where
 
 
   traverse = \x -> traverseDefault x
   traverse = \x -> traverseDefault x
 
 
+instance Queryable q => CanBeQueried q ArtDecoCardElement where
+  query' = queryArtDecoCard
+
 queryArtDecoCard :: forall q. Queryable q => QueryRunner' q (ArtDecoCardElement Node)
 queryArtDecoCard :: forall q. Queryable q => QueryRunner' q (ArtDecoCardElement Node)
 queryArtDecoCard n = do
 queryArtDecoCard n = do
   pvs_entity <- subQueryOne queryArtDecoPvsEntity ":scope div.pvs-entity--padded" n
   pvs_entity <- subQueryOne queryArtDecoPvsEntity ":scope div.pvs-entity--padded" n

+ 4 - 0
src/LinkedIn/UI/Components/ArtDecoTab.purs

@@ -13,6 +13,7 @@ import Data.Maybe (Maybe)
 import Data.Show.Generic (genericShow)
 import Data.Show.Generic (genericShow)
 import Data.Traversable (class Traversable, sequence, traverseDefault)
 import Data.Traversable (class Traversable, sequence, traverseDefault)
 import Data.Tuple (Tuple(..))
 import Data.Tuple (Tuple(..))
+import LinkedIn.CanBeQueried (class CanBeQueried)
 import LinkedIn.QueryRunner (QueryRunner', subQueryOne)
 import LinkedIn.QueryRunner (QueryRunner', subQueryOne)
 import LinkedIn.Queryable (class Queryable)
 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.UI.Components.ArtDeco (ArtDecoPvsEntity, _pvs_to_header_bold, _pvs_to_header_light, _pvs_to_header_normal, _pvs_to_subcomponents, queryArtDecoPvsEntity)
@@ -43,6 +44,9 @@ instance Traversable ArtDecoTabElement where
 
 
   traverse = \x -> traverseDefault x
   traverse = \x -> traverseDefault x
 
 
+instance Queryable q => CanBeQueried q ArtDecoTabElement where
+  query' = queryArtDecoTab
+
 queryArtDecoTab :: forall q. Queryable q => QueryRunner' q (ArtDecoTabElement Node)
 queryArtDecoTab :: forall q. Queryable q => QueryRunner' q (ArtDecoTabElement Node)
 queryArtDecoTab n = do
 queryArtDecoTab n = do
   pvs_entity <- subQueryOne queryArtDecoPvsEntity ":scope div.pvs-entity--padded" n
   pvs_entity <- subQueryOne queryArtDecoPvsEntity ":scope div.pvs-entity--padded" n

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

@@ -13,7 +13,8 @@ import Data.Maybe (Maybe(..))
 import Data.Show.Generic (genericShow)
 import Data.Show.Generic (genericShow)
 import Data.Traversable (class Traversable, sequence, traverse, traverseDefault)
 import Data.Traversable (class Traversable, sequence, traverse, traverseDefault)
 import Data.Tuple (Tuple(..))
 import Data.Tuple (Tuple(..))
-import LinkedIn.QueryRunner (QueryError(..), QueryRunner, QueryRunner', ignoreNotFound, queryAll, queryOne, querySelf, queryText)
+import LinkedIn.CanBeQueried (class CanBeQueried)
+import LinkedIn.QueryRunner (QueryError(..), QueryRunner', ignoreNotFound, queryAll, queryOne, querySelf, queryText)
 import LinkedIn.Queryable (class Queryable, toNode)
 import LinkedIn.Queryable (class Queryable, toNode)
 import Type.Proxy (Proxy(..))
 import Type.Proxy (Proxy(..))
 import Web.DOM (Node)
 import Web.DOM (Node)
@@ -101,6 +102,9 @@ instance Traversable TopCardPrimaryDescription where
 
 
   traverse = \x -> traverseDefault x
   traverse = \x -> traverseDefault x
 
 
+instance Queryable q => CanBeQueried q TopCardPrimaryDescription where
+  query' = queryTopCardPrimaryDescription
+
 derive instance Generic (TopCardInsight a) _
 derive instance Generic (TopCardInsight a) _
 derive instance Eq a => Eq (TopCardInsight a)
 derive instance Eq a => Eq (TopCardInsight a)
 instance Show a => Show (TopCardInsight a) where
 instance Show a => Show (TopCardInsight a) where
@@ -121,6 +125,9 @@ instance Traversable TopCardInsight where
 
 
   traverse = \x -> traverseDefault x
   traverse = \x -> traverseDefault x
 
 
+instance Queryable q => CanBeQueried q TopCardInsight where
+  query' = queryTopCardInsight
+
 derive instance Generic (TopCardInsightContent a) _
 derive instance Generic (TopCardInsightContent a) _
 derive instance Eq a => Eq (TopCardInsightContent a)
 derive instance Eq a => Eq (TopCardInsightContent a)
 instance Show a => Show (TopCardInsightContent a) where
 instance Show a => Show (TopCardInsightContent a) where
@@ -145,6 +152,9 @@ instance Traversable TopCardInsightContent where
 
 
   traverse = \x -> traverseDefault x
   traverse = \x -> traverseDefault x
 
 
+instance Queryable q => CanBeQueried q TopCardInsightContent where
+  query' = queryTopCardInsightContent
+
 derive instance Generic (TopCardSecondaryInsight a) _
 derive instance Generic (TopCardSecondaryInsight a) _
 derive instance Eq a => Eq (TopCardSecondaryInsight a)
 derive instance Eq a => Eq (TopCardSecondaryInsight a)
 instance Show a => Show (TopCardSecondaryInsight a) where
 instance Show a => Show (TopCardSecondaryInsight a) where
@@ -164,6 +174,9 @@ instance Traversable TopCardSecondaryInsight where
 
 
   traverse = \x -> traverseDefault x
   traverse = \x -> traverseDefault x
 
 
+instance Queryable q => CanBeQueried q TopCardSecondaryInsight where
+  query' = queryTopCardSecondaryInsight
+
 derive instance Generic (TopCardAction a) _
 derive instance Generic (TopCardAction a) _
 derive instance Eq a => Eq (TopCardAction a)
 derive instance Eq a => Eq (TopCardAction a)
 instance Show a => Show (TopCardAction a) where
 instance Show a => Show (TopCardAction a) where
@@ -183,6 +196,9 @@ instance Traversable TopCardAction where
 
 
   traverse = \x -> traverseDefault x
   traverse = \x -> traverseDefault x
 
 
+instance Queryable q => CanBeQueried q TopCardAction where
+  query' = queryTopCardAction
+
 queryTopCardAction :: forall q. Queryable q => QueryRunner' q (TopCardAction Node)
 queryTopCardAction :: forall q. Queryable q => QueryRunner' q (TopCardAction Node)
 queryTopCardAction n = do
 queryTopCardAction n = do
   n' <- querySelf n
   n' <- querySelf n