Selaa lähdekoodia

Add Foldable + Traversable instances to TopCard

jherve 1 vuosi sitten
vanhempi
commit
6f6b872d00
1 muutettua tiedostoa jossa 100 lisäystä ja 1 poistoa
  1. 100 1
      src/LinkedIn/JobsUnifiedTopCard.purs

+ 100 - 1
src/LinkedIn/JobsUnifiedTopCard.purs

@@ -4,10 +4,12 @@ import Control.Alt
 import Prelude
 
 import Data.Either (Either(..), hush)
+import Data.Foldable (class Foldable, foldMap, foldlDefault, foldrDefault)
 import Data.Generic.Rep (class Generic)
 import Data.List.Types (NonEmptyList)
-import Data.Maybe (Maybe)
+import Data.Maybe (Maybe(..))
 import Data.Show.Generic (genericShow)
+import Data.Traversable (class Traversable, sequence, traverseDefault)
 import LinkedIn (DetachedNode(..))
 import LinkedIn.Types (ParseError(..), Parser)
 import LinkedIn.Utils (detachNonEmptyTextChild, parseDetachedNode, queryAndDetachMany, queryAndDetachOne, queryManyAndParse, queryOneAndParse)
@@ -49,36 +51,133 @@ instance Show a => Show (JobsUnifiedTopCardElement a) where
   show = genericShow
 derive instance Functor JobsUnifiedTopCardElement
 
+instance Foldable JobsUnifiedTopCardElement where
+  foldMap f (JobsUnifiedTopCardElement {header, primaryDescription, insights, actions}) =
+    f header
+    <> foldMap f primaryDescription
+    <> foldMap (foldMap (foldMap f)) insights
+    <> foldMap (foldMap (foldMap f)) actions
+
+  foldl = \x -> foldlDefault x
+  foldr = \x -> foldrDefault x
+
+instance Traversable JobsUnifiedTopCardElement where
+  sequence (JobsUnifiedTopCardElement {header, primaryDescription, insights, actions}) = ado
+    h <- header
+    pd <- sequence primaryDescription
+    i <- traverseMayNel insights
+    a <- traverseMayNel actions
+  in JobsUnifiedTopCardElement {header: h, primaryDescription: pd, insights: i, actions: a}
+
+  traverse = \x -> traverseDefault x
+
+traverseMayNel :: forall m t a. Traversable t => Applicative m => Maybe(NonEmptyList (t (m a))) -> m (Maybe (NonEmptyList (t a)))
+traverseMayNel (Just o) = map pure (sequence (map sequence o))
+traverseMayNel Nothing = pure Nothing
+
 derive instance Generic (TopCardPrimaryDescription a) _
 derive instance Eq a => Eq (TopCardPrimaryDescription a)
 instance Show a => Show (TopCardPrimaryDescription a) where
   show = genericShow
 derive instance Functor TopCardPrimaryDescription
 
+instance Foldable TopCardPrimaryDescription where
+  foldMap f (TopCardPrimaryDescription {link, text, tvmText}) = f link <> f text <> foldMap (foldMap f) tvmText
+
+  foldl = \x -> foldlDefault x
+  foldr = \x -> foldrDefault x
+
+instance Traversable TopCardPrimaryDescription where
+  sequence (TopCardPrimaryDescription {link, text, tvmText}) = ado
+    l <- link
+    t <- text
+    tvm <- sequence (map sequence tvmText)
+  in TopCardPrimaryDescription {link: l, text: t, tvmText: tvm}
+
+  traverse = \x -> traverseDefault x
+
 derive instance Generic (TopCardInsight a) _
 derive instance Eq a => Eq (TopCardInsight a)
 instance Show a => Show (TopCardInsight a) where
   show = genericShow
 derive instance Functor TopCardInsight
 
+instance Foldable TopCardInsight where
+  foldMap f (TopCardInsight {icon, content}) = f icon <> foldMap f content
+
+  foldl = \x -> foldlDefault x
+  foldr = \x -> foldrDefault x
+
+instance Traversable TopCardInsight where
+  sequence (TopCardInsight {icon, content}) = ado
+    i <- icon
+    c <- sequence content
+  in TopCardInsight {icon: i, content: c}
+
+  traverse = \x -> traverseDefault x
+
 derive instance Generic (TopCardInsightContent a) _
 derive instance Eq a => Eq (TopCardInsightContent a)
 instance Show a => Show (TopCardInsightContent a) where
   show = genericShow
 derive instance Functor TopCardInsightContent
 
+instance Foldable TopCardInsightContent where
+  foldMap f (TopCardInsightContentSingle a) = f a
+  foldMap f (TopCardInsightContentButton a) = f a
+  foldMap f (TopCardInsightContentSecondary {primary, secondary}) = f primary <> foldMap (foldMap f) secondary
+
+  foldl = \x -> foldlDefault x
+  foldr = \x -> foldrDefault x
+
+instance Traversable TopCardInsightContent where
+  sequence (TopCardInsightContentSingle ins) = TopCardInsightContentSingle <$> ins
+  sequence (TopCardInsightContentButton ins) = TopCardInsightContentButton <$> ins
+  sequence (TopCardInsightContentSecondary {primary, secondary}) = ado
+    p <- primary
+    s <- sequence (map sequence secondary)
+  in TopCardInsightContentSecondary {primary: p, secondary: s}
+
+  traverse = \x -> traverseDefault x
+
 derive instance Generic (TopCardSecondaryInsight a) _
 derive instance Eq a => Eq (TopCardSecondaryInsight a)
 instance Show a => Show (TopCardSecondaryInsight a) where
   show = genericShow
 derive instance Functor TopCardSecondaryInsight
 
+instance Foldable TopCardSecondaryInsight where
+  foldMap f (TopCardSecondaryInsightNested a) = f a
+  foldMap f (TopCardSecondaryInsightPlain a) = f a
+
+  foldl = \x -> foldlDefault x
+  foldr = \x -> foldrDefault x
+
+instance Traversable TopCardSecondaryInsight where
+  sequence (TopCardSecondaryInsightNested ins) = TopCardSecondaryInsightNested <$> ins
+  sequence (TopCardSecondaryInsightPlain ins) = TopCardSecondaryInsightPlain <$> ins
+
+  traverse = \x -> traverseDefault x
+
 derive instance Generic (TopCardAction a) _
 derive instance Eq a => Eq (TopCardAction a)
 instance Show a => Show (TopCardAction a) where
   show = genericShow
 derive instance Functor TopCardAction
 
+instance Foldable TopCardAction where
+  foldMap f (TopCardActionApplyButton a) = f a
+
+  foldl = \x -> foldlDefault x
+  foldr = \x -> foldrDefault x
+
+instance Traversable TopCardAction where
+  sequence (TopCardActionApplyButton app) = ado
+    a <- app
+  in TopCardActionApplyButton a
+
+  traverse = \x -> traverseDefault x
+
 parseTopCardAction :: Parser (TopCardAction DetachedNode)
 parseTopCardAction n = do
   self <- parseDetachedNode n