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

Move QueryRunner code to a specific module

jherve 1 год назад
Родитель
Сommit
33a145d155
4 измененных файлов с 54 добавлено и 46 удалено
  1. 2 1
      src/Content.purs
  2. 6 32
      src/LinkedIn/ArtDecoCardAlt.purs
  3. 46 0
      src/LinkedIn/QueryRunner.purs
  4. 0 13
      src/LinkedIn/Types.purs

+ 2 - 1
src/Content.purs

@@ -13,13 +13,14 @@ import Effect (Effect)
 import Effect.Class.Console (logShow)
 import Effect.Class.Console (logShow)
 import Effect.Console (log)
 import Effect.Console (log)
 import LinkedIn.ArtDecoCard (parseArtDecoCard)
 import LinkedIn.ArtDecoCard (parseArtDecoCard)
-import LinkedIn.ArtDecoCardAlt (ArtDecoCardAltElement, queryArtDecoCardAlt, runQuery)
+import LinkedIn.ArtDecoCardAlt (ArtDecoCardAltElement, queryArtDecoCardAlt)
 import LinkedIn.ArtDecoTab (parseArtDecoTab)
 import LinkedIn.ArtDecoTab (parseArtDecoTab)
 import LinkedIn.JobsUnifiedTopCard (parseJobsUnifiedTopCardElement)
 import LinkedIn.JobsUnifiedTopCard (parseJobsUnifiedTopCardElement)
 import LinkedIn.Profile.Project as PP
 import LinkedIn.Profile.Project as PP
 import LinkedIn.Profile.Skill as PS
 import LinkedIn.Profile.Skill as PS
 import LinkedIn.Profile.Utils (toUIElement)
 import LinkedIn.Profile.Utils (toUIElement)
 import LinkedIn.Profile.WorkExperience as PWE
 import LinkedIn.Profile.WorkExperience as PWE
+import LinkedIn.QueryRunner (runQuery)
 import Web.DOM (Node)
 import Web.DOM (Node)
 import Yoga.Tree (Tree, showTree)
 import Yoga.Tree (Tree, showTree)
 
 

+ 6 - 32
src/LinkedIn/ArtDecoCardAlt.purs

@@ -1,22 +1,17 @@
 module LinkedIn.ArtDecoCardAlt where
 module LinkedIn.ArtDecoCardAlt where
 
 
-import Control.Monad.Except.Trans
 import Prelude
 import Prelude
 
 
-import Data.Either (Either(..), note)
 import Data.Foldable (class Foldable, foldMap, foldlDefault, foldrDefault)
 import Data.Foldable (class Foldable, foldMap, foldlDefault, foldrDefault)
 import Data.Generic.Rep (class Generic)
 import Data.Generic.Rep (class Generic)
 import Data.List.Types (NonEmptyList)
 import Data.List.Types (NonEmptyList)
-import Data.Maybe (Maybe(..))
+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 Effect (Effect)
-import LinkedIn.Types (QueryError(..), QueryRunner)
-import LinkedIn.Utils (queryAll, queryOne)
+import LinkedIn.QueryRunner (QueryRunner, ignoreNotFound, queryAll, queryOne)
 import Web.DOM (Node)
 import Web.DOM (Node)
 import Web.DOM.Node (nodeName)
 import Web.DOM.Node (nodeName)
 
 
-
 data ArtDecoCenterHeaderAlt a = ArtDecoCenterHeaderAlt {
 data ArtDecoCenterHeaderAlt a = ArtDecoCenterHeaderAlt {
   bold :: a,
   bold :: a,
   normal :: Maybe a,
   normal :: Maybe a,
@@ -74,40 +69,19 @@ instance Traversable ArtDecoCardAltElement where
 
 
 queryArtDecoCenterHeaderAlt ∷ QueryRunner (ArtDecoCenterHeaderAlt Node)
 queryArtDecoCenterHeaderAlt ∷ QueryRunner (ArtDecoCenterHeaderAlt Node)
 queryArtDecoCenterHeaderAlt n = do
 queryArtDecoCenterHeaderAlt n = do
-  bold <- runOne ":scope div.t-bold > span[aria-hidden=true]" n
+  bold <- queryOne ":scope div.t-bold > span[aria-hidden=true]" n
   normal <-
   normal <-
     ignoreNotFound $
     ignoreNotFound $
-    runOne ":scope span.t-normal:not(t-black--light) > span[aria-hidden=true]" n
+    queryOne ":scope span.t-normal:not(t-black--light) > span[aria-hidden=true]" n
   light <-
   light <-
     ignoreNotFound $
     ignoreNotFound $
-    runAll ":scope span.t-black--light > span[aria-hidden=true]" n
+    queryAll ":scope span.t-black--light > span[aria-hidden=true]" n
 
 
   pure $ ArtDecoCenterHeaderAlt {bold, normal, light}
   pure $ ArtDecoCenterHeaderAlt {bold, normal, light}
 
 
 queryArtDecoCardAlt ∷ QueryRunner (ArtDecoCardAltElement Node)
 queryArtDecoCardAlt ∷ QueryRunner (ArtDecoCardAltElement Node)
 queryArtDecoCardAlt n = do
 queryArtDecoCardAlt n = do
-  pvs <- runOne ":scope div.pvs-entity--padded" n
+  pvs <- queryOne ":scope div.pvs-entity--padded" n
   header <- queryArtDecoCenterHeaderAlt pvs
   header <- queryArtDecoCenterHeaderAlt pvs
 
 
   pure $ ArtDecoCardAltElement { pvs_entity: header }
   pure $ ArtDecoCardAltElement { pvs_entity: header }
-
-runQuery ∷ ∀ a. ExceptT QueryError Effect a → Effect (Either QueryError a)
-runQuery = runExceptT
-
-ignoreNotFound ∷ ∀ a f. Functor f ⇒ ExceptT QueryError f a → ExceptT QueryError f (Maybe a)
-ignoreNotFound = mapExceptT (map ignoreNotFound')
-  where
-    ignoreNotFound' = case _ of
-      (Left (QNodeNotFoundError _ )) -> Right Nothing
-      (Left q) -> Left q
-      (Right n') -> Right (Just n')
-
-runOne ∷ String → QueryRunner Node
-runOne selector node = ExceptT $ do
-  maybeNode <- queryOne selector node
-  pure $ note (QNodeNotFoundError selector) maybeNode
-
-runAll ∷ String → QueryRunner (NonEmptyList Node)
-runAll selector node = ExceptT $ do
-  maybeNodes <- queryAll selector node
-  pure $ note (QNodeListNotFoundError selector) maybeNodes

+ 46 - 0
src/LinkedIn/QueryRunner.purs

@@ -0,0 +1,46 @@
+module LinkedIn.QueryRunner where
+
+import Prelude
+
+import Control.Monad.Except (ExceptT(..), mapExceptT, runExceptT)
+import Data.Either (Either(..), note)
+import Data.Generic.Rep (class Generic)
+import Data.List.Types (NonEmptyList)
+import Data.Maybe (Maybe(..))
+import Data.Show.Generic (genericShow)
+import Effect (Effect)
+import LinkedIn.Utils as U
+import Web.DOM (Node)
+
+data QueryError =
+  QNodeNotFoundError String
+  | QNodeListNotFoundError String
+  | QTextNotFoundError
+
+derive instance Generic QueryError _
+derive instance Eq QueryError
+instance Show QueryError where
+  show = genericShow
+
+type QueryRunner a = Node → ExceptT QueryError Effect a
+
+runQuery ∷ ∀ a. ExceptT QueryError Effect a → Effect (Either QueryError a)
+runQuery = runExceptT
+
+ignoreNotFound ∷ ∀ a f. Functor f ⇒ ExceptT QueryError f a → ExceptT QueryError f (Maybe a)
+ignoreNotFound = mapExceptT (map ignoreNotFound')
+  where
+    ignoreNotFound' = case _ of
+      (Left (QNodeNotFoundError _ )) -> Right Nothing
+      (Left q) -> Left q
+      (Right n') -> Right (Just n')
+
+queryOne ∷ String → QueryRunner Node
+queryOne selector node = ExceptT $ do
+  maybeNode <- U.queryOne selector node
+  pure $ note (QNodeNotFoundError selector) maybeNode
+
+queryAll ∷ String → QueryRunner (NonEmptyList Node)
+queryAll selector node = ExceptT $ do
+  maybeNodes <- U.queryAll selector node
+  pure $ note (QNodeListNotFoundError selector) maybeNodes

+ 0 - 13
src/LinkedIn/Types.purs

@@ -2,7 +2,6 @@ module LinkedIn.Types where
 
 
 import Prelude
 import Prelude
 
 
-import Control.Monad.Except (ExceptT)
 import Data.Either (Either)
 import Data.Either (Either)
 import Data.Generic.Rep (class Generic)
 import Data.Generic.Rep (class Generic)
 import Data.Show.Generic (genericShow)
 import Data.Show.Generic (genericShow)
@@ -21,15 +20,3 @@ instance Show ParseError where
   show = genericShow
   show = genericShow
 
 
 type Parser a = Node → Effect (Either ParseError a)
 type Parser a = Node → Effect (Either ParseError a)
-
-data QueryError =
-  QNodeNotFoundError String
-  | QNodeListNotFoundError String
-  | QTextNotFoundError
-
-derive instance Generic QueryError _
-derive instance Eq QueryError
-instance Show QueryError where
-  show = genericShow
-
-type QueryRunner a = Node → ExceptT QueryError Effect a