Bläddra i källkod

Simplify abstraction

jherve 2 år sedan
förälder
incheckning
dfe8599132
3 ändrade filer med 39 tillägg och 48 borttagningar
  1. 1 0
      spago.dhall
  2. 12 4
      src/Content.purs
  3. 26 44
      src/LinkedIn.purs

+ 1 - 0
spago.dhall

@@ -11,6 +11,7 @@ You can edit this file as you like.
   , "node-fs"
   , "prelude"
   , "web-dom"
+  , "yoga-tree"
   ]
 , packages = ./packages.dhall
 , sources = [ "src/**/*.purs", "test/**/*.purs" ]

+ 12 - 4
src/Content.purs

@@ -1,20 +1,28 @@
 module ExampleWebExt.Content where
 
+import Data.List.NonEmpty
+import LinkedIn
 import Prelude
 
+import Browser.DOM (getBrowserDom)
+import Data.Maybe (Maybe(..))
 import Effect (Effect)
 import Effect.Class.Console (logShow)
 import Effect.Console (log)
-
-import Browser.DOM (getBrowserDom)
-import LinkedIn
+import Yoga.Tree (showTree)
 
 main :: Effect Unit
 main = do
-  dom <- fromDocument <$> getBrowserDom
+  dom <- getBrowserDom
   artDecoCards <- getArtDecoCards dom
   artDecoTabs <- getArtDecoTabs dom
 
   log "[content] starting up"
   logShow artDecoCards
   logShow artDecoTabs
+
+  case artDecoCards of 
+    Nothing -> log "no card found"
+    Just cards -> do
+      tree <- detach $ head cards
+      log "I have a tree"

+ 26 - 44
src/LinkedIn.purs

@@ -1,16 +1,18 @@
 module LinkedIn where
 
 import Prelude
+import Yoga.Tree
 
 import Data.List.NonEmpty as NEL
 import Data.List.Types (NonEmptyList)
-import Data.Maybe (Maybe(..), fromJust)
+import Data.Maybe (Maybe(..))
+import Data.Traversable (sequence)
 import Effect (Effect)
 import Partial.Unsafe (unsafePartial)
-import Web.DOM (Document, Element, Node, ParentNode)
+import Web.DOM (Document, Node)
 import Web.DOM.Document as D
-import Web.DOM.Element (tagName)
 import Web.DOM.Element as E
+import Web.DOM.Node (nodeName, nodeType)
 import Web.DOM.Node as N
 import Web.DOM.NodeList as NL
 import Web.DOM.NodeType (NodeType(..))
@@ -18,60 +20,40 @@ import Web.DOM.ParentNode (QuerySelector(..), querySelector, querySelectorAll)
 
 -- A light abstraction layer above the DOM manipulation API
 
-data LinkedInNode =
-  LinkedInDocument Document
-  | LinkedInElement Element
+fromDocument ∷ Document → Node
+fromDocument doc = D.toNode doc
 
-fromDocument ∷ Document → LinkedInNode
-fromDocument = LinkedInDocument
-
-instance Show LinkedInNode where
-  show (LinkedInDocument _) = "some document"
-  show (LinkedInElement el) = "some " <> tagName el <> " element"
-
-toParentNode' ∷ LinkedInNode → ParentNode
-toParentNode' (LinkedInDocument doc) = D.toParentNode doc
-toParentNode' (LinkedInElement el) = E.toParentNode el
-
-fromNode ∷ Partial ⇒ Node → LinkedInNode
-fromNode n = case N.nodeType n of
-  ElementNode -> LinkedInElement $ unsafePartial $ fromJust $ E.fromNode n
-
-queryOne :: String -> LinkedInNode -> Effect (Maybe LinkedInNode)
-queryOne selector node = do
-  found <- querySelector (QuerySelector selector) $ toParentNode' node
+queryOne :: String -> Document -> Effect (Maybe Node)
+queryOne selector doc = do
+  found <- querySelector (QuerySelector selector) $ D.toParentNode doc
   pure case found of
     Nothing -> Nothing
-    Just el -> Just $ LinkedInElement el
-
-queryAll :: String -> LinkedInNode -> Effect (Maybe (NonEmptyList LinkedInNode))
-queryAll selector node = do
-  found <- querySelectorAll (QuerySelector selector) $ toParentNode' node
-  nodeList <- liftA1 NEL.fromFoldable $ NL.toArray found
+    Just el -> Just $ E.toNode el
 
-  pure case nodeList of
-    Nothing -> Nothing
-    Just list -> Just $ map (unsafePartial fromNode) list
+queryAll :: String -> Document -> Effect (Maybe (NonEmptyList Node))
+queryAll selector doc = do
+  found <- querySelectorAll (QuerySelector selector) $ D.toParentNode doc
+  liftA1 NEL.fromFoldable $ NL.toArray found
 
 -- First pass of naming ; from here we know what we are looking for
 
-data LinkedInRaw =
-  ArtDecoCardRaw LinkedInNode
-  | ArtDecoTabRaw LinkedInNode
+data LinkedInUIElement =
+  ArtDecoCardRaw Node
+  | ArtDecoTabRaw Node
 
-instance Show LinkedInRaw where
-  show (ArtDecoCardRaw n) = "ArtDecoCardRaw(" <> show n <> ")"
-  show (ArtDecoTabRaw n) = "ArtDecoTabRaw(" <> show n <> ")"
+instance Show LinkedInUIElement where
+  show (ArtDecoCardRaw n) = "ArtDecoCardRaw(" <> nodeName n <> ")"
+  show (ArtDecoTabRaw n) = "ArtDecoTabRaw(" <> nodeName n <> ")"
 
-getArtDecoCards ∷ LinkedInNode → Effect (Maybe (NonEmptyList LinkedInRaw))
+getArtDecoCards ∷ Document → Effect (Maybe (NonEmptyList LinkedInUIElement))
 getArtDecoCards = queryAll' ArtDecoCardRaw "section.artdeco-card > div ~ div > div > div > ul > li"
 
-getArtDecoTabs ∷ LinkedInNode → Effect (Maybe (NonEmptyList LinkedInRaw))
+getArtDecoTabs ∷ Document → Effect (Maybe (NonEmptyList LinkedInUIElement))
 getArtDecoTabs = queryAll' ArtDecoTabRaw "div.artdeco-tabs > div > div > div > div > ul > li"
 
-queryAll' ∷ ∀ b. (LinkedInNode → b) → String → LinkedInNode → Effect (Maybe (NonEmptyList b))
-queryAll' constructor selector root = do
-  nodes <- queryAll selector root
+queryAll' ∷ ∀ b. (Node → b) → String → Document → Effect (Maybe (NonEmptyList b))
+queryAll' constructor selector doc = do
+  nodes <- queryAll selector doc
   pure case nodes of
     Nothing -> Nothing
     Just cards -> Just $ map constructor cards