浏览代码

Much more precise code to extract WorkExperience

jherve 1 年之前
父节点
当前提交
cf14586c68
共有 2 个文件被更改,包括 60 次插入25 次删除
  1. 3 3
      src/Content.purs
  2. 57 22
      src/LinkedIn/Profile/WorkExperience.purs

+ 3 - 3
src/Content.purs

@@ -30,15 +30,15 @@ main = do
   maybeShowPruned "no tabs found" artDecoTabs >>= log
   maybeShowPruned "no top card found" jobsUnifiedTopCard >>= log
 
-  case artDecoCards of 
+  case artDecoCards of
     Nothing -> log "nothing"
     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
-
+        Right p -> do
+          logShow $ fromUI p
 
 maybeShowTree ∷ Maybe (NonEmptyList LinkedInUIElement) → Effect String
 maybeShowTree Nothing = pure "nope"

+ 57 - 22
src/LinkedIn/Profile/WorkExperience.purs

@@ -3,20 +3,22 @@ module LinkedIn.Profile.WorkExperience where
 import LinkedIn.UIElements.Parser
 import Prelude
 
-import Data.Either (Either(..), note)
+import Data.Either (Either(..), hush, note)
 import Data.Generic.Rep (class Generic)
+import Data.List.NonEmpty (NonEmptyList)
 import Data.List.NonEmpty as NEL
 import Data.Maybe (Maybe(..))
 import Data.Show.Generic (genericShow)
 import LinkedIn (DetachedNode(..))
 import LinkedIn.ArtDecoCard (ArtDecoCardElement(..), ArtDecoCenter(..), ArtDecoCenterContent(..), ArtDecoCenterHeader(..), ArtDecoPvsEntity(..), ArtDecoPvsEntitySubComponent(..))
-import LinkedIn.UIElements.Types (UIElement(..))
+import LinkedIn.UIElements.Types (Duration, TimeSpan, UIElement(..))
 import Parsing (ParseError, runParser)
 
 data WorkExperience = WorkExperience {
   position :: String,
   company :: Maybe String,
-  timeSpan :: Maybe String,
+  timeSpan :: Maybe TimeSpan,
+  duration :: Maybe Duration,
   description :: Maybe String
 }
 
@@ -36,27 +38,60 @@ fromUI (ArtDecoCardElement {
       content: ArtDecoCenterContent subComponents
     }
   }
-}) = note "Oops" wep where
-  subC = map (\(ArtDecoPvsEntitySubComponent c) -> c) subComponents
-  desc = NEL.head subC
-
-  wep = ado
-    p <- toText bold
-  in WorkExperience {
-    position: p,
-    company: normal >>= toText,
-    timeSpan: Nothing,
-    description: toText desc
-  }
+}) = ado
+    position <- extractPosition bold'
+  in
+    WorkExperience {
+    position,
+    company: hush $ extractCompany normal',
+    timeSpan: hush $ extractTimeSpan light',
+    duration: hush $ extractDuration light',
+    description: hush $ extractDescription content'
+  } where
+  bold' = toUIElement bold
+
+  content' :: NonEmptyList (Either ParseError UIElement)
+  content' = map (\(ArtDecoPvsEntitySubComponent c) -> toUIElement c) subComponents
+
+  normal' :: Maybe (Either ParseError UIElement)
+  normal' = toUIElement <$> normal
+
+  light' :: Maybe (NonEmptyList (Either ParseError UIElement))
+  light' = (map toUIElement) <$> light
+
+extractPosition ∷ Either ParseError UIElement → Either String String
+extractPosition bold = case bold of
+  Right (UIPlainText str) -> Right str
+  _ -> Left "No position"
+
+extractCompany ∷ Maybe (Either ParseError UIElement) → Either String String
+extractCompany normal = case normal of
+  Just (Right (UIPlainText str)) -> Right str
+  Just (Right (UIDotSeparated (UIPlainText str) _)) -> Right str
+  _ -> Left "No company"
+
+extractTimeSpan ∷ Maybe (NonEmptyList (Either ParseError UIElement)) → Either String TimeSpan
+extractTimeSpan light = case light of
+  Just l -> note "No timespan" $ NEL.findMap getTimeSpan l
+  Nothing -> Left "No timespan"
+  where
+    getTimeSpan (Right (UIDotSeparated (UITimeSpan s) _)) = Just s
+    getTimeSpan _ = Nothing
+
+extractDuration ∷ Maybe (NonEmptyList (Either ParseError UIElement)) → Either String Duration
+extractDuration light = case light of
+  Just l -> note "No duration" $ NEL.findMap getDuration l
+  Nothing -> Left "No duration"
+  where
+    getDuration (Right (UIDotSeparated _ (UIDuration d))) = Just d
+    getDuration _ = Nothing
+
+extractDescription ∷ NonEmptyList (Either ParseError UIElement) → Either String String
+extractDescription  content = case NEL.head content of
+    Right (UIPlainText d) -> Right d
+    _ -> Left "No description"
 
 toUIElement ∷ DetachedNode → Either ParseError UIElement
 toUIElement (DetachedElement {content}) = runParser content uiElementP
 toUIElement (DetachedComment str) = runParser str uiElementP
 toUIElement (DetachedText str) = runParser str uiElementP
-
-toText ∷ DetachedNode → Maybe String
-toText el = case toUIElement el of
-  Right (UIPlainText str) -> Just str
-  Right (UIDotSeparated (UIPlainText str) _) -> Just str
-  Right (UIDotSeparated _ (UIPlainText str)) -> Just str
-  _ -> Nothing