Prechádzať zdrojové kódy

Simplify query code by making all structures traversable

jherve 1 rok pred
rodič
commit
925ab0ff70

+ 1 - 0
spago.dhall

@@ -25,6 +25,7 @@ You can edit this file as you like.
   , "partial"
   , "partial"
   , "prelude"
   , "prelude"
   , "strings"
   , "strings"
+  , "transformers"
   , "tuples"
   , "tuples"
   , "web-dom"
   , "web-dom"
   , "yoga-tree"
   , "yoga-tree"

+ 17 - 12
src/Content.purs

@@ -8,16 +8,19 @@ import Data.Either (Either(..))
 import Data.List.NonEmpty (NonEmptyList)
 import Data.List.NonEmpty (NonEmptyList)
 import Data.List.NonEmpty as NEL
 import Data.List.NonEmpty as NEL
 import Data.Maybe (Maybe(..))
 import Data.Maybe (Maybe(..))
+import Data.Traversable (traverse)
 import Effect (Effect)
 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.ArtDecoTab (parseArtDecoTab)
+import LinkedIn.ArtDecoCard (queryArtDecoCard)
+import LinkedIn.ArtDecoTab (queryArtDecoTab)
 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 Yoga.Tree (Tree, showTree)
 import Yoga.Tree (Tree, showTree)
 
 
 main :: Effect Unit
 main :: Effect Unit
@@ -38,23 +41,25 @@ main = do
   case artDecoCards of
   case artDecoCards of
     Nothing -> log "nothing"
     Nothing -> log "nothing"
     Just l -> do
     Just l -> do
-      parsed <- (\(LinkedInUIElement _ n) -> parseArtDecoCard n) $ NEL.head l
-      logShow parsed
-      case parsed of
+      queried <- (\(LinkedInUIElement _ n) -> runQuery $ queryArtDecoCard n) $ NEL.head l
+      case queried of
         Left l -> logShow l
         Left l -> logShow l
         Right p -> do
         Right p -> do
-          logShow $ toUIElement <$> p
-          logShow $ PWE.fromUI p
-          logShow $ PP.fromUI p
+          detached <- traverse toDetached p
+          logShow detached
+          logShow $ PWE.fromUI detached
+          logShow $ PP.fromUI detached
+
   case artDecoTabs of
   case artDecoTabs of
     Nothing -> log "nothing"
     Nothing -> log "nothing"
     Just l -> do
     Just l -> do
-      parsed <- (\(LinkedInUIElement _ n) -> parseArtDecoTab n) $ NEL.head l
-      logShow parsed
-      case parsed of
+      queried <- (\(LinkedInUIElement _ n) -> runQuery $ queryArtDecoTab n) $ NEL.head l
+      case queried of
         Left l -> logShow l
         Left l -> logShow l
         Right p -> do
         Right p -> do
-          logShow $ PS.fromUI p
+          detached <- traverse toDetached p
+          logShow detached
+          logShow $ PS.fromUI detached
 
 
   case jobsUnifiedTopCard of
   case jobsUnifiedTopCard of
     Nothing -> log "nothing"
     Nothing -> log "nothing"

+ 106 - 46
src/LinkedIn/ArtDeco.purs

@@ -2,19 +2,16 @@ module LinkedIn.ArtDeco where
 
 
 import Prelude
 import Prelude
 
 
-import Data.Either (Either(..), hush)
+import Data.Foldable (class Foldable, foldMap, foldlDefault, foldrDefault)
 import Data.Generic.Rep (class Generic)
 import Data.Generic.Rep (class Generic)
 import Data.List (List)
 import Data.List (List)
 import Data.List.NonEmpty (NonEmptyList)
 import Data.List.NonEmpty (NonEmptyList)
 import Data.List.NonEmpty as NEL
 import Data.List.NonEmpty as NEL
 import Data.Maybe (Maybe)
 import Data.Maybe (Maybe)
 import Data.Show.Generic (genericShow)
 import Data.Show.Generic (genericShow)
-import LinkedIn (DetachedNode)
-import LinkedIn.Profile.Utils (toUIElement)
-import LinkedIn.Types (Parser)
-import LinkedIn.UIElements.Types (UIElement)
-import LinkedIn.Utils (queryAndDetachMany, queryAndDetachOne, queryManyAndParse, queryOneAndParse)
-import Parsing (ParseError)
+import Data.Traversable (class Traversable, sequence, traverseDefault)
+import LinkedIn.QueryRunner (QueryRunner, ignoreNotFound, queryAll, queryOne, subQueryMany, subQueryOne)
+import Web.DOM (Node)
 
 
 
 
 data ArtDecoPvsEntity a = ArtDecoPvsEntity {
 data ArtDecoPvsEntity a = ArtDecoPvsEntity {
@@ -44,69 +41,132 @@ instance Show a => Show (ArtDecoPvsEntitySubComponent a) where
   show = genericShow
   show = genericShow
 derive instance Functor ArtDecoPvsEntitySubComponent
 derive instance Functor ArtDecoPvsEntitySubComponent
 
 
+instance Foldable ArtDecoPvsEntitySubComponent where
+  foldMap f (ArtDecoPvsEntitySubComponent sc) = foldMap f sc
+
+  foldl = \x -> foldlDefault x
+  foldr = \x -> foldrDefault x
+
+instance Traversable ArtDecoPvsEntitySubComponent where
+  sequence (ArtDecoPvsEntitySubComponent subComponents) = ado
+    sc <- sequence subComponents
+  in ArtDecoPvsEntitySubComponent sc
+
+  traverse = \x -> traverseDefault x
+
 derive instance Generic (ArtDecoCenterContent a) _
 derive instance Generic (ArtDecoCenterContent a) _
 derive instance Eq a => Eq(ArtDecoCenterContent a)
 derive instance Eq a => Eq(ArtDecoCenterContent a)
 instance Show a => Show(ArtDecoCenterContent a) where
 instance Show a => Show(ArtDecoCenterContent a) where
   show = genericShow
   show = genericShow
 derive instance Functor ArtDecoCenterContent
 derive instance Functor ArtDecoCenterContent
 
 
+instance Foldable ArtDecoCenterContent where
+  foldMap f (ArtDecoCenterContent c) = foldMap (foldMap f) c
+
+  foldl = \x -> foldlDefault x
+  foldr = \x -> foldrDefault x
+
+instance Traversable ArtDecoCenterContent where
+  sequence (ArtDecoCenterContent center) = ado
+    c <- sequence (map sequence center)
+  in ArtDecoCenterContent c
+
+  traverse = \x -> traverseDefault x
+
 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
   show = genericShow
   show = genericShow
 derive instance Functor ArtDecoCenterHeader
 derive instance Functor ArtDecoCenterHeader
 
 
+instance Foldable ArtDecoCenterHeader where
+  foldMap f (ArtDecoCenterHeader {bold, normal, light}) = f bold <> foldMap f normal <> foldMap (foldMap f) light
+
+  foldl = \x -> foldlDefault x
+  foldr = \x -> foldrDefault x
+
+instance Traversable ArtDecoCenterHeader where
+  sequence (ArtDecoCenterHeader {bold, normal, light}) = ado
+    b <- bold
+    n <- sequence normal
+    l <- sequence (map sequence light)
+  in ArtDecoCenterHeader {bold: b, normal: n, light: l}
+
+  traverse = \x -> traverseDefault x
+
 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
   show = genericShow
   show = genericShow
 derive instance Functor ArtDecoCenter 
 derive instance Functor ArtDecoCenter 
 
 
+instance Foldable ArtDecoCenter where
+  foldMap f (ArtDecoCenter {header, content}) = foldMap f header <> foldMap f content
+
+  foldl = \x -> foldlDefault x
+  foldr = \x -> foldrDefault x
+
+instance Traversable ArtDecoCenter where
+  sequence (ArtDecoCenter {header, content}) = ado
+    h <- sequence header
+    c <- sequence content
+  in ArtDecoCenter {header: h, content: c}
+
+  traverse = \x -> traverseDefault x
+
 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
   show = genericShow
   show = genericShow
 derive instance Functor ArtDecoPvsEntity
 derive instance Functor ArtDecoPvsEntity
 
 
-parseArtDecoPvsEntitySubComponent ∷ Parser (ArtDecoPvsEntitySubComponent DetachedNode)
-parseArtDecoPvsEntitySubComponent n = do
-  content <- queryAndDetachOne "span[aria-hidden=true]" n
-  pure $ Right $ ArtDecoPvsEntitySubComponent $ hush content
-
-parseArtDecoCenterContent ∷ Parser (ArtDecoCenterContent DetachedNode)
-parseArtDecoCenterContent n = do
-  list <- queryManyAndParse ":scope > ul > li" parseArtDecoPvsEntitySubComponent n
-  pure $ ado
-    l <- list
-  in ArtDecoCenterContent l
-
-parseArtDecoCenterHeader :: Parser (ArtDecoCenterHeader DetachedNode)
-parseArtDecoCenterHeader n = do
-  bold <- queryAndDetachOne ":scope div.t-bold > span[aria-hidden=true]" n
-  normal <- queryAndDetachOne ":scope span.t-normal:not(t-black--light) > span[aria-hidden=true]" n
-  light <- queryAndDetachMany ":scope span.t-black--light > span[aria-hidden=true]" n
-
-  pure $ ado
-    b <- bold
-  in ArtDecoCenterHeader {bold: b, normal: hush normal, light: hush light}
-
-parseArtDecoCenter :: Parser (ArtDecoCenter DetachedNode)
-parseArtDecoCenter n = do
-  header <- queryOneAndParse ":scope > div" parseArtDecoCenterHeader n
-  content <- queryOneAndParse ":scope > div.pvs-entity__sub-components" parseArtDecoCenterContent n
-
-  pure $ ado
-    h <- header
-    c <- content
-  in ArtDecoCenter {header: h, content: c}
-
-parseArtDecoPvsEntity :: Parser (ArtDecoPvsEntity DetachedNode)
-parseArtDecoPvsEntity n = do
-  center <- queryOneAndParse ":scope > div.display-flex" parseArtDecoCenter n
-
-  pure $ ado
-    c <- center
-  in ArtDecoPvsEntity {side: unit, center: c}
+instance Foldable ArtDecoPvsEntity where
+  foldMap f (ArtDecoPvsEntity {side: _, center}) = foldMap f center
+
+  foldl = \x -> foldlDefault x
+  foldr = \x -> foldrDefault x
+
+instance Traversable ArtDecoPvsEntity where
+  sequence (ArtDecoPvsEntity {side, center}) = ado
+    s <- pure side
+    c <- sequence center
+  in ArtDecoPvsEntity {side: s, center: c}
+
+  traverse = \x -> traverseDefault x
+
+queryArtDecoPvsEntitySubComponent ∷ QueryRunner (ArtDecoPvsEntitySubComponent Node)
+queryArtDecoPvsEntitySubComponent n = do
+  content <- ignoreNotFound $ queryOne "span[aria-hidden=true]" n
+  pure $ ArtDecoPvsEntitySubComponent content
+
+queryArtDecoCenterContent ∷ QueryRunner (ArtDecoCenterContent Node)
+queryArtDecoCenterContent n = do
+  sc <- subQueryMany queryArtDecoPvsEntitySubComponent ":scope > ul > li" n
+  pure $ ArtDecoCenterContent sc
+
+queryArtDecoCenterHeader ∷ QueryRunner (ArtDecoCenterHeader Node)
+queryArtDecoCenterHeader n = do
+  bold <- queryOne ":scope div.t-bold > span[aria-hidden=true]" n
+  normal <-
+    ignoreNotFound $
+    queryOne ":scope span.t-normal:not(t-black--light) > span[aria-hidden=true]" n
+  light <-
+    ignoreNotFound $
+    queryAll ":scope span.t-black--light > span[aria-hidden=true]" n
+
+  pure $ ArtDecoCenterHeader {bold, normal, light}
+
+queryArtDecoCenter ∷ QueryRunner (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 n = do
+  center <- subQueryOne queryArtDecoCenter ":scope > div.display-flex" n
+  pure $ ArtDecoPvsEntity {side: unit, center}
 
 
 toHeaderBold ∷ forall a. ArtDecoPvsEntity a → a
 toHeaderBold ∷ forall a. ArtDecoPvsEntity a → a
 toHeaderBold (ArtDecoPvsEntity {
 toHeaderBold (ArtDecoPvsEntity {

+ 20 - 10
src/LinkedIn/ArtDecoCard.purs

@@ -2,17 +2,17 @@ module LinkedIn.ArtDecoCard where
 
 
 import Prelude
 import Prelude
 
 
+import Data.Foldable (class Foldable, foldMap, foldlDefault, foldrDefault)
 import Data.Generic.Rep (class Generic)
 import Data.Generic.Rep (class Generic)
 import Data.List (List)
 import Data.List (List)
 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 LinkedIn (DetachedNode)
-import LinkedIn.ArtDeco (ArtDecoPvsEntity, parseArtDecoPvsEntity)
+import Data.Traversable (class Traversable, sequence, traverseDefault)
+import LinkedIn.ArtDeco (ArtDecoPvsEntity, queryArtDecoPvsEntity)
 import LinkedIn.ArtDeco as AD
 import LinkedIn.ArtDeco as AD
-import LinkedIn.Types (Parser)
-import LinkedIn.Utils (queryOneAndParse)
-import LinkedIn.QueryRunner (QueryRunner, ignoreNotFound, queryAll, queryOne)
+import LinkedIn.QueryRunner (QueryRunner, subQueryOne)
+import Web.DOM (Node)
 
 
 
 
 data ArtDecoCardElement a = ArtDecoCardElement {
 data ArtDecoCardElement a = ArtDecoCardElement {
@@ -25,14 +25,24 @@ instance Show a => Show (ArtDecoCardElement a) where
   show = genericShow
   show = genericShow
 derive instance Functor ArtDecoCardElement
 derive instance Functor ArtDecoCardElement
 
 
-parseArtDecoCard :: Parser (ArtDecoCardElement DetachedNode)
-parseArtDecoCard n = do
-  pvs <- queryOneAndParse ":scope div.pvs-entity--padded" parseArtDecoPvsEntity n
+instance Foldable ArtDecoCardElement where
+  foldMap f (ArtDecoCardElement {pvs_entity}) = foldMap f pvs_entity
 
 
-  pure $ ado
-    p <- pvs
+  foldl = \x -> foldlDefault x
+  foldr = \x -> foldrDefault x
+
+instance Traversable ArtDecoCardElement where
+  sequence (ArtDecoCardElement {pvs_entity}) = ado
+    p <- sequence pvs_entity
   in ArtDecoCardElement {pvs_entity: p}
   in ArtDecoCardElement {pvs_entity: p}
 
 
+  traverse = \x -> traverseDefault x
+
+queryArtDecoCard :: QueryRunner (ArtDecoCardElement Node)
+queryArtDecoCard n = do
+  pvs_entity <- subQueryOne queryArtDecoPvsEntity ":scope div.pvs-entity--padded" n
+  pure $ ArtDecoCardElement {pvs_entity}
+
 toCenterContent ∷ forall a. ArtDecoCardElement a → List a
 toCenterContent ∷ forall a. ArtDecoCardElement a → List a
 toCenterContent = toPvsEntity >>> AD.toCenterContent
 toCenterContent = toPvsEntity >>> AD.toCenterContent
 
 

+ 20 - 9
src/LinkedIn/ArtDecoTab.purs

@@ -2,16 +2,17 @@ module LinkedIn.ArtDecoTab where
 
 
 import Prelude
 import Prelude
 
 
+import Data.Foldable (class Foldable, foldMap, foldlDefault, foldrDefault)
 import Data.Generic.Rep (class Generic)
 import Data.Generic.Rep (class Generic)
 import Data.List (List)
 import Data.List (List)
 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 LinkedIn (DetachedNode)
-import LinkedIn.ArtDeco (ArtDecoPvsEntity, parseArtDecoPvsEntity)
+import Data.Traversable (class Traversable, sequence, traverseDefault)
+import LinkedIn.ArtDeco (ArtDecoPvsEntity, queryArtDecoPvsEntity)
 import LinkedIn.ArtDeco as AD
 import LinkedIn.ArtDeco as AD
-import LinkedIn.Types (Parser)
-import LinkedIn.Utils (queryOneAndParse)
+import LinkedIn.QueryRunner (QueryRunner, subQueryOne)
+import Web.DOM (Node)
 
 
 
 
 data ArtDecoTabElement a = ArtDecoTabElement {
 data ArtDecoTabElement a = ArtDecoTabElement {
@@ -24,14 +25,24 @@ instance Show a => Show (ArtDecoTabElement a) where
   show = genericShow
   show = genericShow
 derive instance Functor ArtDecoTabElement
 derive instance Functor ArtDecoTabElement
 
 
-parseArtDecoTab :: Parser (ArtDecoTabElement DetachedNode)
-parseArtDecoTab n = do
-  pvs <- queryOneAndParse ":scope div.pvs-entity--padded" parseArtDecoPvsEntity n
+instance Foldable ArtDecoTabElement where
+  foldMap f (ArtDecoTabElement {pvs_entity}) = foldMap f pvs_entity
 
 
-  pure $ ado
-    p <- pvs
+  foldl = \x -> foldlDefault x
+  foldr = \x -> foldrDefault x
+
+instance Traversable ArtDecoTabElement where
+  sequence (ArtDecoTabElement {pvs_entity}) = ado
+    p <- sequence pvs_entity
   in ArtDecoTabElement {pvs_entity: p}
   in ArtDecoTabElement {pvs_entity: p}
 
 
+  traverse = \x -> traverseDefault x
+
+queryArtDecoTab :: QueryRunner (ArtDecoTabElement Node)
+queryArtDecoTab n = do
+  pvs_entity <- subQueryOne queryArtDecoPvsEntity ":scope div.pvs-entity--padded" n
+  pure $ ArtDecoTabElement {pvs_entity}
+
 toCenterContent ∷ forall a. ArtDecoTabElement a → List a
 toCenterContent ∷ forall a. ArtDecoTabElement a → List a
 toCenterContent = toPvsEntity >>> AD.toCenterContent
 toCenterContent = toPvsEntity >>> AD.toCenterContent
 
 

+ 53 - 0
src/LinkedIn/QueryRunner.purs

@@ -0,0 +1,53 @@
+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 Data.Traversable (traverse)
+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
+
+subQueryMany ∷ ∀ a. QueryRunner a → String → QueryRunner (NonEmptyList a)
+subQueryMany query selector n = traverse query =<< queryAll selector n
+
+subQueryOne ∷ ∀ a. QueryRunner a → String → QueryRunner a
+subQueryOne query selector n = query =<< queryOne selector n

+ 2 - 1
src/LinkedIn/Types.purs

@@ -1,10 +1,11 @@
 module LinkedIn.Types where
 module LinkedIn.Types where
 
 
 import Prelude
 import Prelude
+
 import Data.Either (Either)
 import Data.Either (Either)
-import Effect (Effect)
 import Data.Generic.Rep (class Generic)
 import Data.Generic.Rep (class Generic)
 import Data.Show.Generic (genericShow)
 import Data.Show.Generic (genericShow)
+import Effect (Effect)
 import Web.DOM (Node)
 import Web.DOM (Node)
 
 
 
 

+ 2 - 50
src/LinkedIn/Utils.purs

@@ -1,23 +1,16 @@
-module LinkedIn.Utils where
+module LinkedIn.Utils (queryOne, queryAll) where
 
 
 import Prelude
 import Prelude
 
 
-import Data.Array as A
-import Data.Either (Either(..), note)
-import Data.List as L
 import Data.List.NonEmpty (NonEmptyList)
 import Data.List.NonEmpty (NonEmptyList)
 import Data.List.NonEmpty as NEL
 import Data.List.NonEmpty as NEL
 import Data.Maybe (Maybe(..), fromJust)
 import Data.Maybe (Maybe(..), fromJust)
-import Data.Traversable (sequence, traverse)
 import Effect (Effect)
 import Effect (Effect)
-import LinkedIn (DetachedNode(..), toDetached)
-import LinkedIn.Types (ParseError(..), Parser)
 import Partial.Unsafe (unsafePartial)
 import Partial.Unsafe (unsafePartial)
 import Web.DOM (Node, ParentNode)
 import Web.DOM (Node, ParentNode)
 import Web.DOM.Element as E
 import Web.DOM.Element as E
-import Web.DOM.Node as N
 import Web.DOM.NodeList as NL
 import Web.DOM.NodeList as NL
-import Web.DOM.ParentNode (QuerySelector(..), children, querySelector, querySelectorAll)
+import Web.DOM.ParentNode (QuerySelector(..), querySelector, querySelectorAll)
 
 
 toParentNode' :: Node -> ParentNode
 toParentNode' :: Node -> ParentNode
 toParentNode' n =
 toParentNode' n =
@@ -38,44 +31,3 @@ queryAll :: String -> Node -> Effect (Maybe (NonEmptyList Node))
 queryAll selector n = do
 queryAll selector n = do
   found <- querySelectorAll (QuerySelector selector) $ toParentNode' n
   found <- querySelectorAll (QuerySelector selector) $ toParentNode' n
   liftA1 NEL.fromFoldable $ NL.toArray found
   liftA1 NEL.fromFoldable $ NL.toArray found
-
-parseDetachedNode :: Parser DetachedNode
-parseDetachedNode node = do
-  node' <- toDetached node
-  pure $ Right node'
-
-queryAndDetachOne ∷ String -> Parser DetachedNode
-queryAndDetachOne selector n = queryOneAndParse selector parseDetachedNode n
-
-queryAndDetachMany ∷ String -> Parser (NonEmptyList DetachedNode)
-queryAndDetachMany selector n = queryManyAndParse selector parseDetachedNode n
-
-queryOneAndParse ∷ ∀ a. String → Parser a → Parser a
-queryOneAndParse selector parser n = do
-  selected <- queryOne selector n
-
-  case selected of
-    Nothing -> pure $ Left $ NodeNotFoundError selector
-    Just node -> parser node
-
-queryManyAndParse ∷ ∀ a. String → Parser a → Parser (NonEmptyList a)
-queryManyAndParse selector parser n = do
-  selected <- queryAll selector n
-  case selected of
-    Nothing -> pure $ Left $ NodeListNotFoundError selector
-    Just nodes -> do
-      nodes' <- sequence $ map parser nodes :: Effect (NonEmptyList((Either ParseError a)))
-      pure $ sequence nodes'
-
-detachNonEmptyTextChild :: Parser DetachedNode
-detachNonEmptyTextChild n = do
-  children <- N.childNodes n
-  childrenArr <- NL.toArray children
-  detached <- traverse parseDetachedNode childrenArr
-  
-  case A.find nonEmptyTextElement detached of
-    Nothing -> pure $ Left TextNotFoundError
-    Just c -> pure $ c
-  where 
-    nonEmptyTextElement (Right (DetachedText t)) | t /= "" = true
-    nonEmptyTextElement _ = false

+ 10 - 5
test/ArtDecoCard.purs

@@ -11,11 +11,12 @@ import Data.List.NonEmpty (NonEmptyList(..))
 import Data.List.NonEmpty as NEL
 import Data.List.NonEmpty as NEL
 import Data.Maybe (Maybe(..), isJust)
 import Data.Maybe (Maybe(..), isJust)
 import Data.NonEmpty (NonEmpty(..))
 import Data.NonEmpty (NonEmpty(..))
+import Data.Traversable (traverse)
 import Effect (Effect)
 import Effect (Effect)
-import LinkedIn (DetachedNode(..), LinkedInUIElement(..), getArtDecoCards)
+import LinkedIn (DetachedNode(..), LinkedInUIElement(..), getArtDecoCards, toDetached)
 import LinkedIn.Profile.WorkExperience (WorkExperience(..))
 import LinkedIn.Profile.WorkExperience (WorkExperience(..))
 import LinkedIn.Profile.WorkExperience as PWE
 import LinkedIn.Profile.WorkExperience as PWE
-import LinkedIn.Types (ParseError)
+import LinkedIn.QueryRunner (QueryError, runQuery)
 import LinkedIn.UIElements.Types (Duration(..), TimeSpan(..))
 import LinkedIn.UIElements.Types (Duration(..), TimeSpan(..))
 import Node.JsDom (jsDomFromFile)
 import Node.JsDom (jsDomFromFile)
 import Partial.Unsafe (unsafePartial)
 import Partial.Unsafe (unsafePartial)
@@ -90,10 +91,14 @@ testArtDecoCards = do
           })
           })
       }
       }
 
 
-parseHeadCard ∷ Partial => Maybe (NonEmptyList LinkedInUIElement) → Effect (Either ParseError (ArtDecoCardElement DetachedNode))
+parseHeadCard ∷ Partial => Maybe (NonEmptyList LinkedInUIElement) → Effect (Either QueryError (ArtDecoCardElement DetachedNode))
 parseHeadCard (Just l) = do
 parseHeadCard (Just l) = do
-  parsed <- (\(LinkedInUIElement _ n) -> parseArtDecoCard n) $ NEL.head l
-  pure $ parsed
+  queried <- (\(LinkedInUIElement _ n) -> runQuery $ queryArtDecoCard n) $ NEL.head l
+  case queried of
+    Left l -> pure $ Left l
+    Right q -> do
+      parsed <- traverse toDetached q
+      pure $ Right parsed
 
 
 testArtDecoCard :: Effect Unit
 testArtDecoCard :: Effect Unit
 testArtDecoCard = do
 testArtDecoCard = do