module Text.Feed.Import
( parseFeedFromFile
, parseFeedString
, parseFeedSource
, FeedSource
, readRSS2
, readRSS1
, readAtom
) where
import Prelude ()
import Prelude.Compat
import Control.Exception
import Data.ByteString.Lazy (ByteString)
import Data.Text.Lazy (Text, pack)
import Data.XML.Types as XML
import Text.Atom.Feed.Import as Atom
import Text.Feed.Types
import Text.RSS.Import as RSS
import Text.RSS1.Import as RSS1
import Control.Monad
import qualified Text.XML as C
#if MIN_VERSION_utf8_string(1,0,0)
import Codec.Binary.UTF8.String (decodeString)
import System.IO (IOMode(..), hGetContents, openBinaryFile)
utf8readFile :: FilePath -> IO String
utf8readFile fp = fmap decodeString (hGetContents =<< openBinaryFile fp ReadMode)
#else
import System.IO.UTF8 as UTF8 (readFile)
utf8readFile :: FilePath -> IO String
utf8readFile = UTF8.readFile
#endif
class FeedSource s where
parseFeedSourceXML :: s -> Either SomeException C.Document
instance FeedSource ByteString where
parseFeedSourceXML = C.parseLBS C.def
instance FeedSource Text where
parseFeedSourceXML = C.parseText C.def
instance FeedSource String where
parseFeedSourceXML = parseFeedSourceXML . pack
parseFeedFromFile :: FilePath -> IO Feed
parseFeedFromFile fp = do
ls <- utf8readFile fp
case parseFeedString ls of
Nothing -> fail ("parseFeedFromFile: not a well-formed XML content in: " ++ fp)
Just f -> return f
parseFeedWithParser :: FeedSource s => (s -> Either e C.Document) -> s -> Maybe Feed
parseFeedWithParser parser str =
case parser str of
Left _ -> Nothing
Right d ->
readAtom e `mplus` readRSS2 e `mplus` readRSS1 e `mplus` Just (XMLFeed e)
where
e = C.toXMLElement $ C.documentRoot d
parseFeedString :: String -> Maybe Feed
parseFeedString = parseFeedSource
parseFeedSource :: FeedSource s => s -> Maybe Feed
parseFeedSource = parseFeedWithParser parseFeedSourceXML
readRSS2 :: XML.Element -> Maybe Feed
readRSS2 e = RSSFeed <$> RSS.elementToRSS e
readRSS1 :: XML.Element -> Maybe Feed
readRSS1 e = RSS1Feed <$> RSS1.elementToFeed e
readAtom :: XML.Element -> Maybe Feed
readAtom e = AtomFeed <$> Atom.elementFeed e