Browse Source

Start adding Profile.WorkExperience data

jherve 1 year ago
parent
commit
c2f4e093b4
2 changed files with 57 additions and 0 deletions
  1. 5 0
      src/Content.purs
  2. 52 0
      src/LinkedIn/Profile/WorkExperience.purs

+ 5 - 0
src/Content.purs

@@ -4,6 +4,7 @@ import LinkedIn
 import Prelude
 
 import Browser.DOM (getBrowserDom)
+import Data.Either (Either(..))
 import Data.List.NonEmpty (NonEmptyList)
 import Data.List.NonEmpty as NEL
 import Data.Maybe (Maybe(..))
@@ -11,6 +12,7 @@ import Effect (Effect)
 import Effect.Class.Console (logShow)
 import Effect.Console (log)
 import LinkedIn.ArtDecoCard (parseArtDecoCard)
+import LinkedIn.Profile.WorkExperience (fromUI)
 import Yoga.Tree (Tree, showTree)
 
 main :: Effect Unit
@@ -33,6 +35,9 @@ main = do
     Just l -> do
       parsed <- (\(LinkedInUIElement _ n) -> parseArtDecoCard n) $ NEL.head l
       logShow parsed
+      case parsed of
+        Left l -> logShow l
+        Right p -> logShow $ fromUI p
 
 
 maybeShowTree ∷ Maybe (NonEmptyList LinkedInUIElement) → Effect String

+ 52 - 0
src/LinkedIn/Profile/WorkExperience.purs

@@ -0,0 +1,52 @@
+module LinkedIn.Profile.WorkExperience where
+
+import LinkedIn.UIElements.Parser
+import Prelude
+
+import Data.Either (Either(..), note)
+import Data.Generic.Rep (class Generic)
+import Data.List.NonEmpty as NEL
+import Data.Maybe (Maybe(..), fromMaybe)
+import Data.Show.Generic (genericShow)
+import Debug (trace, traceM)
+import LinkedIn (DetachedNode(..))
+import LinkedIn.ArtDecoCard (ArtDecoCardElement(..), ArtDecoCenter(..), ArtDecoCenterContent(..), ArtDecoCenterHeader(..), ArtDecoPvsEntity(..), ArtDecoPvsEntitySubComponent(..))
+import Parsing (runParser)
+
+data WorkExperience = WorkExperience {
+  position :: String,
+  company :: Maybe String,
+  timeSpan :: Maybe String,
+  description :: Maybe String
+}
+
+derive instance Generic WorkExperience _
+instance Show WorkExperience where
+  show = genericShow
+
+fromUI :: ArtDecoCardElement -> Either String WorkExperience
+fromUI (ArtDecoCardElement {
+  pvs_entity: ArtDecoPvsEntity {
+    center: ArtDecoCenter {
+      header: ArtDecoCenterHeader {
+        bold: bold,
+        normal,
+        light
+      },
+      content: ArtDecoCenterContent subComponents
+    }
+  }
+}) = note "Oops" wep where
+  subC = map (\(ArtDecoPvsEntitySubComponent c) -> c) subComponents
+  desc = NEL.head subC
+
+  wep = ado
+    p <- toContent bold
+    c <- toContent <$> normal
+  in WorkExperience {position: p, company: c, timeSpan: Nothing, description: toContent desc}
+
+toContent ∷ DetachedNode → Maybe String
+toContent (DetachedElement {content}) = Just content
+toContent _ = Nothing
+
+toUIElement el = runParser uiElementP el