-------------------------------------------------------------------- -- | -- Module : -- Copyright : (c) Galois, Inc. 2008 -- License : All rights reserved -- -- Maintainer: Don Stewart -- Stability : provisional -- Portability: -- -------------------------------------------------------------------- module Text.OPML.Reader ( {- readOPML, -} parseOPMLString ) where import Text.OPML.Syntax import Text.OPML.Import import Text.XML.Light {- import Web.HTTP.Header import Web.DAV.Utils ( splitURL ) import Web.DAV.Backend.CurlPkg as Curl import Web.DAV.Backend.Interface import Web.DAV.Types as WebClient -} -- import Data.Maybe ( fromMaybe ) -- | Parse a string into OPML. parseOPMLString :: String -> Maybe OPML parseOPMLString str = case parseXMLDoc str of Nothing -> Nothing Just e -> elementToOPML e {- -- remove dependence on webdav readOPML :: {-URL-}String -> IO (Maybe OPML) readOPML opmlURL = do (st,_,body) <- readIn opmlURL case st of 200 -> case parseOPMLString body of Nothing -> fail ("readOPML: failed to parse OPML from " ++ opmlURL) Just fd -> return (Just fd) _ -> return Nothing where readIn f = do catch (readFile f >>= \ ls -> return (200,[],ls)) (\ _ -> readURL f []) readURL :: {-URL-}String -> [HttpHeader] -> IO (Int,[HttpHeader], String) readURL url hs = do let (base,path) = splitURL url webH <- primOpen (Curl.factory defaultConfig{cfgOptions=cOpts}) base hs st <- WebClient.webGet webH path [] Nothing case st of WebOK rhs v -> return (200,rhs,v) WebFailed rhs m -> return (404,rhs,fromMaybe "" m) WebStatus rhs v a -> return (v,rhs,a) where cOpts = cAuthOpts cAuthOpts = [ CurlHttpAuth [HttpAuthAny] -- ToDo: allow cookie file location to be passed in. , CurlCookieFile "cookies" , CurlCookieJar "cookies" , CurlFollowLocation True ] -}