Forráskód Böngészése

Turn toXXX functions into simple, generic accessors

jherve 1 éve
szülő
commit
ed69a745e4

+ 10 - 12
src/LinkedIn/ArtDeco.purs

@@ -121,24 +121,22 @@ parseArtDecoPvsEntity n = do
     c <- center
   in ArtDecoPvsEntity {side: unit, center: c}
 
-toHeaderBold ∷ ArtDecoPvsEntity DetachedNodeEither ParseError UIElement
+toHeaderBold ∷ forall a. ArtDecoPvsEntity a → a
 toHeaderBold (ArtDecoPvsEntity {
-    center: ArtDecoCenter { header: ArtDecoCenterHeader { bold }
-  }
-}) = toUIElement bold
+  center: ArtDecoCenter { header: ArtDecoCenterHeader { bold }}
+}) = bold
 
-toHeaderNormal ∷ ArtDecoPvsEntity DetachedNode → Maybe (Either ParseError UIElement)
+toHeaderNormal ∷ forall a. ArtDecoPvsEntity a → Maybe (a)
 toHeaderNormal (ArtDecoPvsEntity {
   center: ArtDecoCenter { header: ArtDecoCenterHeader { normal }}
-}) = toUIElement <$> normal
+}) = normal
 
-toHeaderLight ∷ ArtDecoPvsEntity DetachedNode → Maybe (NonEmptyList (Either ParseError UIElement))
+toHeaderLight ∷ forall a. ArtDecoPvsEntity a → Maybe (NonEmptyList a)
 toHeaderLight (ArtDecoPvsEntity {
-  center: ArtDecoCenter { header: ArtDecoCenterHeader { light } }
-}) = (map toUIElement) <$> light
+  center: ArtDecoCenter { header: ArtDecoCenterHeader { light }}
+}) = light
 
-toCenterContent ∷ ArtDecoPvsEntity DetachedNode → List (Either ParseError UIElement)
+toCenterContent ∷ forall a. ArtDecoPvsEntity a → List a
 toCenterContent (ArtDecoPvsEntity {
   center: ArtDecoCenter { content: ArtDecoCenterContent subComponents }
-}) = map toUIElement subC
-  where subC = NEL.catMaybes $ map (\(ArtDecoPvsEntitySubComponent c) -> c) subComponents :: List (DetachedNode)
+}) = NEL.catMaybes $ map (\(ArtDecoPvsEntitySubComponent c) -> c) subComponents

+ 4 - 7
src/LinkedIn/ArtDecoCard.purs

@@ -2,7 +2,6 @@ module LinkedIn.ArtDecoCard where
 
 import Prelude
 
-import Data.Either (Either)
 import Data.Generic.Rep (class Generic)
 import Data.List (List)
 import Data.List.Types (NonEmptyList)
@@ -12,9 +11,7 @@ import LinkedIn (DetachedNode)
 import LinkedIn.ArtDeco (ArtDecoPvsEntity, parseArtDecoPvsEntity)
 import LinkedIn.ArtDeco as AD
 import LinkedIn.Types (Parser)
-import LinkedIn.UIElements.Types (UIElement)
 import LinkedIn.Utils (queryOneAndParse)
-import Parsing (ParseError)
 
 
 data ArtDecoCardElement a = ArtDecoCardElement {
@@ -37,16 +34,16 @@ parseArtDecoCard n = do
     p <- pvs
   in ArtDecoCardElement {pvs_entity: p}
 
-toCenterContent ∷ ArtDecoCardElement DetachedNode → List (Either ParseError UIElement)
+toCenterContent ∷ forall a. ArtDecoCardElement a → List a
 toCenterContent = toPvsEntity >>> AD.toCenterContent
 
-toHeaderBold ∷ ArtDecoCardElement DetachedNodeEither ParseError UIElement
+toHeaderBold ∷ forall a. ArtDecoCardElement a → a
 toHeaderBold = toPvsEntity >>> AD.toHeaderBold
 
-toHeaderLight ∷ ArtDecoCardElement DetachedNode → Maybe (NonEmptyList (Either ParseError UIElement))
+toHeaderLight ∷ forall a.  ArtDecoCardElement a → Maybe (NonEmptyList a)
 toHeaderLight = toPvsEntity >>> AD.toHeaderLight
 
-toHeaderNormal ∷ ArtDecoCardElement DetachedNode → Maybe (Either ParseError UIElement)
+toHeaderNormal ∷ forall a. ArtDecoCardElement a → Maybe a
 toHeaderNormal = toPvsEntity >>> AD.toHeaderNormal
 
 toPvsEntity ∷ forall a. ArtDecoCardElement a → ArtDecoPvsEntity a

+ 4 - 7
src/LinkedIn/ArtDecoTab.purs

@@ -2,7 +2,6 @@ module LinkedIn.ArtDecoTab where
 
 import Prelude
 
-import Data.Either (Either)
 import Data.Generic.Rep (class Generic)
 import Data.List (List)
 import Data.List.Types (NonEmptyList)
@@ -12,9 +11,7 @@ import LinkedIn (DetachedNode)
 import LinkedIn.ArtDeco (ArtDecoPvsEntity, parseArtDecoPvsEntity)
 import LinkedIn.ArtDeco as AD
 import LinkedIn.Types (Parser)
-import LinkedIn.UIElements.Types (UIElement)
 import LinkedIn.Utils (queryOneAndParse)
-import Parsing (ParseError)
 
 
 data ArtDecoTabElement a = ArtDecoTabElement {
@@ -37,16 +34,16 @@ parseArtDecoTab n = do
     p <- pvs
   in ArtDecoTabElement {pvs_entity: p}
 
-toCenterContent ∷ ArtDecoTabElement DetachedNode → List (Either ParseError UIElement)
+toCenterContent ∷ forall a. ArtDecoTabElement a → List a
 toCenterContent = toPvsEntity >>> AD.toCenterContent
 
-toHeaderBold ∷ ArtDecoTabElement DetachedNodeEither ParseError UIElement
+toHeaderBold ∷ forall a. ArtDecoTabElement a → a
 toHeaderBold = toPvsEntity >>> AD.toHeaderBold
 
-toHeaderLight ∷ ArtDecoTabElement DetachedNode → Maybe (NonEmptyList (Either ParseError UIElement))
+toHeaderLight ∷ forall a. ArtDecoTabElement a → Maybe (NonEmptyList a)
 toHeaderLight = toPvsEntity >>> AD.toHeaderLight
 
-toHeaderNormal ∷ ArtDecoTabElement DetachedNode → Maybe (Either ParseError UIElement)
+toHeaderNormal ∷ forall a. ArtDecoTabElement a → Maybe a
 toHeaderNormal = toPvsEntity >>> AD.toHeaderNormal
 
 toPvsEntity ∷ forall a. ArtDecoTabElement a → ArtDecoPvsEntity a

+ 5 - 4
src/LinkedIn/Profile/Project.purs

@@ -9,7 +9,7 @@ import Data.Maybe (Maybe(..))
 import Data.Show.Generic (genericShow)
 import LinkedIn (DetachedNode)
 import LinkedIn.ArtDecoCard (ArtDecoCardElement, toCenterContent, toHeaderBold, toHeaderNormal)
-import LinkedIn.Profile.Utils (maybeExtractFromMaybe, maybeGetInList)
+import LinkedIn.Profile.Utils (maybeExtractFromMaybe, maybeGetInList, toUIElement)
 import LinkedIn.UIElements.Types (TimeSpan, UIElement(..))
 
 data Project = Project {
@@ -32,9 +32,10 @@ fromUI card = ado
     description: maybeGetInList extractDescription content 0
   }
   where
-    normal = toHeaderNormal card
-    content = toCenterContent card
-    bold = toHeaderBold card
+    asUI = toUIElement <$> card
+    normal = toHeaderNormal asUI
+    content = toCenterContent asUI
+    bold = toHeaderBold asUI
 
 extractName :: UIElement -> Maybe String
 extractName = case _ of

+ 3 - 1
src/LinkedIn/Profile/Skill.purs

@@ -9,6 +9,7 @@ import Data.Maybe (Maybe(..))
 import Data.Show.Generic (genericShow)
 import LinkedIn (DetachedNode)
 import LinkedIn.ArtDecoTab (ArtDecoTabElement, toHeaderBold)
+import LinkedIn.Profile.Utils (toUIElement)
 import LinkedIn.UIElements.Types (UIElement(..))
 
 data Skill = Skill {
@@ -25,7 +26,8 @@ fromUI (tab) = ado
   in
     Skill { name }
   where
-    bold = toHeaderBold tab
+    asUI = toUIElement <$> tab
+    bold = toHeaderBold asUI
 
 extractName :: UIElement -> Maybe String
 extractName = case _ of

+ 6 - 5
src/LinkedIn/Profile/WorkExperience.purs

@@ -9,7 +9,7 @@ import Data.Maybe (Maybe(..))
 import Data.Show.Generic (genericShow)
 import LinkedIn (DetachedNode)
 import LinkedIn.ArtDecoCard (ArtDecoCardElement, toCenterContent, toHeaderBold, toHeaderLight, toHeaderNormal)
-import LinkedIn.Profile.Utils (maybeExtractFromMaybe, maybeFindInMaybeNEL, maybeGetInList)
+import LinkedIn.Profile.Utils (maybeExtractFromMaybe, maybeFindInMaybeNEL, maybeGetInList, toUIElement)
 import LinkedIn.UIElements.Types (Duration, TimeSpan, UIElement(..))
 
 data WorkExperience = WorkExperience {
@@ -39,10 +39,11 @@ fromUI (card) = ado
     description: maybeGetInList extractDescription content 0
   }
   where
-    normal = toHeaderNormal card
-    light = toHeaderLight card
-    content = toCenterContent card
-    bold = toHeaderBold card
+    asUI = toUIElement <$> card
+    normal = toHeaderNormal asUI
+    light = toHeaderLight asUI
+    content = toCenterContent asUI
+    bold = toHeaderBold asUI
 
 extractPosition :: UIElement -> Maybe String
 extractPosition = case _ of