)
import Network.Curl.Download (openURI)
import System.Directory (doesFileExist, getTemporaryDirectory)
-import System.IO (hClose, hPutStrLn, stderr)
+import System.IO (hClose, hPutStrLn, stderr, stdout)
import System.IO.Temp (openBinaryTempFile, openTempFile)
import LWN.URI (filename)
-- And we don't want to use a DNS cache anyway.
CurlDNSCacheTimeout 0,
+ -- Follow redirects.
+ CurlFollowLocation True,
+
-- Give it a little time...
CurlTimeout 45,
- -- And let us know when things go wrong.
+ -- For debugging.
CurlVerbose True ]
return out_path
get_page :: Maybe FilePath -> URLString -> IO (Maybe String)
-get_page cookie_jar url =
+get_page cookie_file url =
withCurlDo $ do
+ hPutStrLn stdout ("Getting page: " ++ url ++ "...")
+
-- Create a curl instance.
curl <- initialize
-- Perform the request, and get back a CurlResponse object.
-- The cast is needed to specify how we would like our headers
-- and body returned (Strings).
+ putStrLn "Curl options:"
+ print curl_opts
+
resp <- do_curl_ curl url curl_opts :: IO CurlResponse
-- Pull out the response code as a CurlCode.
return Nothing
where
get_opts =
- case cookie_jar of
+ case cookie_file of
Nothing -> []
- Just cookies -> [ CurlCookieJar cookies ]
+ Just cookies -> [ CurlCookieFile cookies ]
curl_opts = default_curl_opts ++ get_opts
log_in :: FilePath -> String -> String -> IO Bool
log_in cookie_jar username password =
withCurlDo $ do
+ hPutStrLn stdout ("Logging " ++ username ++ " in...")
+
-- Create a curl instance.
curl <- initialize
-{-# LANGUAGE ScopedTypeVariables, RecordWildCards, DoAndIfThenElse #-}
+{-# LANGUAGE DoAndIfThenElse #-}
module Main
where
import Configuration (Cfg(..), get_cfg, use_account)
import LWN.HTTP (get_page, log_in, make_cookie_jar)
import LWN.Page (epublish, parse)
-import LWN.URI (is_lwn_url, make_absolute_url, make_https)
+import LWN.URI (add_trailing_slash, is_lwn_url, make_absolute_url, make_https)
import Misc (contains)
hPutStrLn stderr "Failed to log in."
html <- get_page (Just cj) my_article
+ print $ fromJust $ html
return $
case html of
Nothing -> Nothing
Just h -> Just $ my_read h
else do
html <- get_page Nothing my_article
+ putStrLn "Not logged in."
+ print $ fromJust $ html
return $
case html of
Nothing -> Nothing
real_article_path :: String -> IO String
real_article_path s = do
is_file <- doesFileExist s
- return $ if is_file then s else check_cases
+ return $ if is_file then s else add_trailing_slash check_cases
where
abs_current =
case make_absolute_url "current" of
cfg <- get_cfg
output_handle <- get_output_handle (output cfg)
+ when (use_account cfg) $ do
+ putStrLn "Using account."
+
maybe_html <- get_xml_from_article cfg
case maybe_html of
test_current_article_path :: Assertion
test_current_article_path = do
- let expected = "https://lwn.net/current"
+ let expected = "https://lwn.net/current/"
actual <- real_article_path "current"
assertEqual "Current article path constructed" expected actual
test_numbered_article_path :: Assertion
test_numbered_article_path = do
- let expected = "https://lwn.net/Articles/69"
+ let expected = "https://lwn.net/Articles/69/"
actual <- real_article_path "69" -- I'm twelve
assertEqual "Numbered article path constructed" expected actual