module Text.Feed.Translate
( translateItemTo
, withAtomEntry
, withRSSItem
, withRSS1Item
) where
import Text.Feed.Types as Feed
import Text.Feed.Constructor
import Text.RSS.Syntax as RSS
import qualified Text.RSS1.Syntax as RSS1
import Text.Atom.Feed as Atom
import Data.Maybe ( fromMaybe )
withAtomEntry :: (Atom.Entry -> Atom.Entry) -> Item -> Item
withAtomEntry f it =
case it of
Feed.AtomItem e -> Feed.AtomItem (f e)
_ -> it
withRSSItem :: (RSS.RSSItem -> RSS.RSSItem) -> Item -> Item
withRSSItem f it =
case it of
Feed.RSSItem e -> Feed.RSSItem (f e)
_ -> it
withRSS1Item :: (RSS1.Item -> RSS1.Item) -> Item -> Item
withRSS1Item f it =
case it of
Feed.RSS1Item e -> Feed.RSS1Item (f e)
_ -> it
translateItemTo :: FeedKind -> Item -> Item
translateItemTo fk it =
case fk of
AtomKind -> toAtomItem it
RSSKind v -> toRSSItem v it
RDFKind v -> toRDFItem v it
toRSSItem :: Maybe String -> Item -> Item
toRSSItem = error "toRSSItem: unimplemented"
toRDFItem :: Maybe String -> Item -> Item
toRDFItem = error "toRDFItem: unimplemented"
toAtomItem :: Item -> Item
toAtomItem it =
case it of
AtomItem{} -> it
RSS1Item{} -> error "toAtomItem: unimplemented (from RSS1 item rep.)"
XMLItem{} -> error "toAtomItem: unimplemented (from shallow XML rep.)"
Feed.RSSItem ri -> foldl (\ oi f -> f oi) outIt pipeline_rss_atom
where
outIt =
(flip withAtomEntry) (newItem AtomKind)
(\ e -> e{ Atom.entryOther = RSS.rssItemOther ri
, Atom.entryAttrs = RSS.rssItemAttrs ri
})
pipeline_rss_atom =
[ mb withItemTitle (rssItemTitle ri)
, mb withItemLink (rssItemLink ri)
, mb withItemDescription (rssItemDescription ri)
, mb withItemAuthor (rssItemAuthor ri)
, ls withItemCategories (rssItemCategories ri)
, mb withItemId' (rssItemGuid ri)
, mb withItemCommentLink (rssItemComments ri)
, mb withItemEnclosure' (rssItemEnclosure ri)
, mb withItemPubDate (rssItemPubDate ri)
]
withItemEnclosure' e =
withItemEnclosure (rssEnclosureURL e)
(Just $ rssEnclosureType e)
(rssEnclosureLength e)
withItemId' g = withItemId (fromMaybe True (rssGuidPermanentURL g)) (rssGuidValue g)
mb _ Nothing = id
mb f (Just v) = f v
ls _ [] = id
ls f xs = f (map (\ c -> (rssCategoryValue c, rssCategoryDomain c)) xs)