Browse Source

Factor out the conversion to UI elements

jherve 1 year ago
parent
commit
ba95b6ed53

+ 15 - 11
src/LinkedIn/Jobs/JobOffer.purs

@@ -2,11 +2,11 @@ module LinkedIn.Jobs.JobOffer where
 
 
 import Prelude
 import Prelude
 
 
-import Data.Either (Either, note)
-import Data.Foldable (findMap)
+import Data.Either (Either(..), note)
 import Data.Generic.Rep (class Generic)
 import Data.Generic.Rep (class Generic)
 import Data.Maybe (Maybe(..))
 import Data.Maybe (Maybe(..))
 import Data.Show.Generic (genericShow)
 import Data.Show.Generic (genericShow)
+import Data.Traversable (traverse)
 import LinkedIn.DetachedNode (DetachedNode)
 import LinkedIn.DetachedNode (DetachedNode)
 import LinkedIn.JobsUnifiedTopCard (JobsUnifiedTopCardElement, toHeader, toPrimaryDescriptionLink, toPrimaryDescriptionText)
 import LinkedIn.JobsUnifiedTopCard (JobsUnifiedTopCardElement, toHeader, toPrimaryDescriptionLink, toPrimaryDescriptionText)
 import LinkedIn.Profile.Utils (toUIElement)
 import LinkedIn.Profile.Utils (toUIElement)
@@ -25,17 +25,21 @@ instance Show JobOffer where
 
 
 
 
 fromUI ∷ JobsUnifiedTopCardElement DetachedNode → Either String JobOffer
 fromUI ∷ JobsUnifiedTopCardElement DetachedNode → Either String JobOffer
-fromUI card = ado
-    title <- note "No title found" $ findMap extractTitle header
-    companyName <- note "No company found" $ findMap extractCompany link
-    companyLink <- note "No company link found" $ findMap extractCompanyLink link
+fromUI card = fromUI' =<< case traverse toUIElement card of
+  Left _ -> Left "error on conversion to UI element"
+  Right ui -> Right ui
+
+fromUI' ∷ JobsUnifiedTopCardElement UIElement → Either String JobOffer
+fromUI' card = ado
+    title <- note "No title found" $ extractTitle header
+    companyName <- note "No company found" $ extractCompany link
+    companyLink <- note "No company link found" $ extractCompanyLink link
   in
   in
-    JobOffer { title, companyName, companyLink, location: findMap extractLocation primaryDescText }
+    JobOffer { title, companyName, companyLink, location: extractLocation primaryDescText }
   where
   where
-    asUI = toUIElement <$> card
-    header = toHeader asUI
-    link = toPrimaryDescriptionLink asUI
-    primaryDescText = toPrimaryDescriptionText asUI
+    header = toHeader card
+    link = toPrimaryDescriptionLink card
+    primaryDescText = toPrimaryDescriptionText card
 
 
 extractTitle :: UIElement -> Maybe String
 extractTitle :: UIElement -> Maybe String
 extractTitle = case _ of
 extractTitle = case _ of

+ 16 - 11
src/LinkedIn/Profile/Project.purs

@@ -2,14 +2,15 @@ module LinkedIn.Profile.Project where
 
 
 import Prelude
 import Prelude
 
 
-import Data.Either (Either, note)
-import Data.Foldable (findMap)
+import Data.Either (Either(..), note)
 import Data.Generic.Rep (class Generic)
 import Data.Generic.Rep (class Generic)
+import Data.List as L
 import Data.Maybe (Maybe(..))
 import Data.Maybe (Maybe(..))
 import Data.Show.Generic (genericShow)
 import Data.Show.Generic (genericShow)
+import Data.Traversable (traverse)
 import LinkedIn.ArtDecoCard (ArtDecoCardElement, toCenterContent, toHeaderBold, toHeaderNormal)
 import LinkedIn.ArtDecoCard (ArtDecoCardElement, toCenterContent, toHeaderBold, toHeaderNormal)
 import LinkedIn.DetachedNode (DetachedNode)
 import LinkedIn.DetachedNode (DetachedNode)
-import LinkedIn.Profile.Utils (maybeExtractFromMaybe, maybeGetInList, toUIElement)
+import LinkedIn.Profile.Utils (toUIElement)
 import LinkedIn.UIElements.Types (TimeSpan, UIElement(..), UIString(..))
 import LinkedIn.UIElements.Types (TimeSpan, UIElement(..), UIString(..))
 
 
 data Project = Project {
 data Project = Project {
@@ -23,19 +24,23 @@ instance Show Project where
   show = genericShow
   show = genericShow
 
 
 fromUI ∷ ArtDecoCardElement DetachedNode → Either String Project
 fromUI ∷ ArtDecoCardElement DetachedNode → Either String Project
-fromUI card = ado
-    name <- note "No position found" $ findMap extractName bold
+fromUI card = fromUI' =<< case traverse toUIElement card of
+  Left _ -> Left "error on conversion to UI element"
+  Right ui -> Right ui
+
+fromUI' ∷ ArtDecoCardElement UIElement → Either String Project
+fromUI' card = ado
+    name <- note "No position found" $ extractName bold
   in
   in
     Project {
     Project {
     name,
     name,
-    timeSpan: maybeExtractFromMaybe extractTimeSpan normal,
-    description: maybeGetInList extractDescription content 0
+    timeSpan: extractTimeSpan =<< normal,
+    description: extractDescription =<< L.index content 0
   }
   }
   where
   where
-    asUI = toUIElement <$> card
-    normal = toHeaderNormal asUI
-    content = toCenterContent asUI
-    bold = toHeaderBold asUI
+    normal = toHeaderNormal card
+    content = toCenterContent card
+    bold = toHeaderBold card
 
 
 extractName :: UIElement -> Maybe String
 extractName :: UIElement -> Maybe String
 extractName = case _ of
 extractName = case _ of

+ 10 - 6
src/LinkedIn/Profile/Skill.purs

@@ -2,11 +2,11 @@ module LinkedIn.Profile.Skill where
 
 
 import Prelude
 import Prelude
 
 
-import Data.Either (Either, note)
-import Data.Foldable (findMap)
+import Data.Either (Either(..), note)
 import Data.Generic.Rep (class Generic)
 import Data.Generic.Rep (class Generic)
 import Data.Maybe (Maybe(..))
 import Data.Maybe (Maybe(..))
 import Data.Show.Generic (genericShow)
 import Data.Show.Generic (genericShow)
+import Data.Traversable (traverse)
 import LinkedIn.ArtDecoTab (ArtDecoTabElement, toHeaderBold)
 import LinkedIn.ArtDecoTab (ArtDecoTabElement, toHeaderBold)
 import LinkedIn.DetachedNode (DetachedNode)
 import LinkedIn.DetachedNode (DetachedNode)
 import LinkedIn.Profile.Utils (toUIElement)
 import LinkedIn.Profile.Utils (toUIElement)
@@ -21,13 +21,17 @@ instance Show Skill where
   show = genericShow
   show = genericShow
 
 
 fromUI ∷ ArtDecoTabElement DetachedNode → Either String Skill
 fromUI ∷ ArtDecoTabElement DetachedNode → Either String Skill
-fromUI (tab) = ado
-    name <- note "No position found" $ findMap extractName bold
+fromUI tab = fromUI' =<< case traverse toUIElement tab of
+  Left _ -> Left "error on conversion to UI element"
+  Right ui -> Right ui
+
+fromUI' ∷ ArtDecoTabElement UIElement → Either String Skill
+fromUI' tab = ado
+    name <- note "No position found" $ extractName bold
   in
   in
     Skill { name }
     Skill { name }
   where
   where
-    asUI = toUIElement <$> tab
-    bold = toHeaderBold asUI
+    bold = toHeaderBold tab
 
 
 extractName :: UIElement -> Maybe String
 extractName :: UIElement -> Maybe String
 extractName = case _ of
 extractName = case _ of

+ 1 - 26
src/LinkedIn/Profile/Utils.purs

@@ -3,38 +3,13 @@ module LinkedIn.Profile.Utils where
 import Prelude
 import Prelude
 
 
 import Control.Alt ((<|>))
 import Control.Alt ((<|>))
-import Data.Either (Either(..), hush)
-import Data.Foldable (class Foldable, findMap)
-import Data.List (List)
-import Data.List as L
+import Data.Either (Either(..))
 import Data.Maybe (Maybe(..))
 import Data.Maybe (Maybe(..))
 import LinkedIn.DetachedNode (DetachedNode(..))
 import LinkedIn.DetachedNode (DetachedNode(..))
 import LinkedIn.UIElements.Parser (uiStringP)
 import LinkedIn.UIElements.Parser (uiStringP)
 import LinkedIn.UIElements.Types (UIElement(..))
 import LinkedIn.UIElements.Types (UIElement(..))
 import Parsing (ParseError(..), initialPos, runParser)
 import Parsing (ParseError(..), initialPos, runParser)
 
 
-maybeGetInList ::
-  ∀ a. (UIElement → Maybe a)
-  -> List (Either ParseError UIElement)
-  -> Int
-  -> Maybe a
-maybeGetInList extract idx list = L.index idx list >>= hush >>= extract
-
-maybeExtractFromMaybe ∷
-  ∀ a. (UIElement → Maybe a)
-  → Maybe (Either ParseError UIElement)
-  → Maybe a
-maybeExtractFromMaybe extract maybeNode = maybeNode >>= hush >>= extract
-
-maybeFindInMaybeNEL ∷
-  ∀ a f. Foldable f ⇒
-  (UIElement → Maybe a)
-  → Maybe (f (Either ParseError UIElement))
-  → Maybe a
-maybeFindInMaybeNEL extract = case _ of
-  Just nel -> findMap (hush >>> (extract =<< _)) nel
-  Nothing -> Nothing
-
 -- TODO : should certainly use another type than ParseError here
 -- TODO : should certainly use another type than ParseError here
 toUIElement ∷ DetachedNode → Either ParseError UIElement
 toUIElement ∷ DetachedNode → Either ParseError UIElement
 toUIElement (DetachedElement {content}) = wrapInUiElement content
 toUIElement (DetachedElement {content}) = wrapInUiElement content

+ 20 - 14
src/LinkedIn/Profile/WorkExperience.purs

@@ -2,14 +2,16 @@ module LinkedIn.Profile.WorkExperience where
 
 
 import Prelude
 import Prelude
 
 
-import Data.Either (Either, note)
+import Data.Either (Either(..), note)
 import Data.Foldable (findMap)
 import Data.Foldable (findMap)
 import Data.Generic.Rep (class Generic)
 import Data.Generic.Rep (class Generic)
+import Data.List as L
 import Data.Maybe (Maybe(..))
 import Data.Maybe (Maybe(..))
 import Data.Show.Generic (genericShow)
 import Data.Show.Generic (genericShow)
+import Data.Traversable (traverse)
 import LinkedIn.ArtDecoCard (ArtDecoCardElement, toCenterContent, toHeaderBold, toHeaderLight, toHeaderNormal)
 import LinkedIn.ArtDecoCard (ArtDecoCardElement, toCenterContent, toHeaderBold, toHeaderLight, toHeaderNormal)
 import LinkedIn.DetachedNode (DetachedNode)
 import LinkedIn.DetachedNode (DetachedNode)
-import LinkedIn.Profile.Utils (maybeExtractFromMaybe, maybeFindInMaybeNEL, maybeGetInList, toUIElement)
+import LinkedIn.Profile.Utils (toUIElement)
 import LinkedIn.UIElements.Types (Duration, TimeSpan, UIElement(..), UIString(..))
 import LinkedIn.UIElements.Types (Duration, TimeSpan, UIElement(..), UIString(..))
 
 
 data WorkExperience = WorkExperience {
 data WorkExperience = WorkExperience {
@@ -27,23 +29,27 @@ instance Show WorkExperience where
   show = genericShow
   show = genericShow
 
 
 fromUI ∷ ArtDecoCardElement DetachedNode → Either String WorkExperience
 fromUI ∷ ArtDecoCardElement DetachedNode → Either String WorkExperience
-fromUI (card) = ado
-    position <- note "No position found" $ findMap extractPosition bold
+fromUI card = fromUI' =<< case traverse toUIElement card of
+  Left _ -> Left "error on conversion to UI element"
+  Right ui -> Right ui
+
+fromUI' ∷ ArtDecoCardElement UIElement → Either String WorkExperience
+fromUI' card = ado
+    position <- note "No position found" $ extractPosition bold
   in
   in
     WorkExperience {
     WorkExperience {
     position,
     position,
-    company: maybeExtractFromMaybe extractCompany normal,
-    contractType: maybeExtractFromMaybe extractContractType normal,
-    timeSpan: maybeFindInMaybeNEL extractTimeSpan light,
-    duration: maybeFindInMaybeNEL extractDuration light,
-    description: maybeGetInList extractDescription content 0
+    company: extractCompany =<< normal,
+    contractType: extractContractType =<< normal,
+    timeSpan: findMap extractTimeSpan =<< light,
+    duration: findMap extractDuration =<< light,
+    description: extractDescription =<< L.index content 0
   }
   }
   where
   where
-    asUI = toUIElement <$> card
-    normal = toHeaderNormal asUI
-    light = toHeaderLight asUI
-    content = toCenterContent asUI
-    bold = toHeaderBold asUI
+    normal = toHeaderNormal card
+    light = toHeaderLight card
+    content = toCenterContent card
+    bold = toHeaderBold card
 
 
 extractPosition :: UIElement -> Maybe String
 extractPosition :: UIElement -> Maybe String
 extractPosition = case _ of
 extractPosition = case _ of