]> gitweb.michael.orlitzky.com - dead/halcyon.git/blobdiff - src/Twitter/Http.hs
Rewrite everything to use the JSON API with OAuth authentication.
[dead/halcyon.git] / src / Twitter / Http.hs
index 4c7c6086d9cad0fc22939f4612ed2acddf1d0978..112c2ea2fa293f75aa16382ab7770b07c9607c2f 100644 (file)
@@ -1,92 +1,98 @@
 module Twitter.Http
 where
 
-import Network.Curl
-import System.IO (hPutStrLn, stderr)
+import qualified Data.ByteString.Lazy as B
+import qualified Data.ByteString.Char8 as BC
+import qualified Data.Conduit as C
+import Data.Conduit.Binary (sinkLbs)
+import Network.HTTP.Conduit
+import Web.Authenticate.OAuth (
+  OAuth(..),
+  Credential,
+  newCredential,
+  newOAuth,
+  signOAuth)
 
 -- |The API URL of username's timeline.
 --
 -- See,
 --
---   <http://dev.twitter.com/doc/get/statuses/user_timeline>
+--   <https://dev.twitter.com/docs/api/1.1/get/statuses/user_timeline>
 --
 user_timeline_url :: String -> String
 user_timeline_url username =
-    concat [ "http://api.twitter.com/1/statuses/user_timeline.xml",
-             "?screen_name=" ++ username,
-             "&include_rts=true",
-             "&count=10" ]
+  concat [ "https://api.twitter.com/",
+           "1.1/",
+           "statuses/",
+           "user_timeline.json?",
+           "screen_name=",
+           username,
+           "&include_rts=true&",
+           "count=10" ]
 
 status_url :: Integer -> String
 status_url status_id =
-    concat [ "http://api.twitter.com/1/statuses/show/",
-             (show status_id),
-             ".xml" ]
-
--- |Given username's last status id, constructs the API URL for
--- username's new statuses. Essentially, 'user_timeline_url' with a
--- "since_id" parameter tacked on.
+  concat [ "https://api.twitter.com/",
+           "1.1/",
+           "statuses/",
+           "show.json?id=",
+           (show status_id) ]
+
+-- | Given username's last status id, constructs the API URL for
+--   username's new statuses. Essentially, 'user_timeline_url' with a
+--   "since_id" parameter tacked on.
 user_new_statuses_url :: String -> Integer -> String
 user_new_statuses_url username last_status_id =
-    concat [ user_timeline_url username,
-             "&since_id=" ++ (show last_status_id) ]
+  concat [ user_timeline_url username,
+           "&since_id=" ++ (show last_status_id) ]
 
 
-get_status :: Integer -> IO (Maybe String)
+get_status :: Integer -> IO B.ByteString
 get_status status_id = do
-    let uri = (status_url status_id)
-    status <- (http_get uri)
-    return status
+  let uri = (status_url status_id)
+  status <- (http_get uri)
+  return status
 
 
--- |Return's username's timeline, or 'Nothing' if there was an error.
-get_user_timeline :: String -> IO (Maybe String)
+-- | Return's username's timeline.
+get_user_timeline :: String -> IO B.ByteString
 get_user_timeline username = do
   let uri = (user_timeline_url username)
   timeline <- (http_get uri)
   return timeline
 
 
--- | Returns the XML representing all of username's statuses that are
+-- | Returns the JSON representing all of username's statuses that are
 --   newer than last_status_id.
-get_user_new_statuses :: String -> Integer -> IO (Maybe String)
+get_user_new_statuses :: String -> Integer -> IO B.ByteString
 get_user_new_statuses username last_status_id = do
   let uri = (user_new_statuses_url username last_status_id)
   new_statuses <- (http_get uri)
   return new_statuses
 
 
--- | Options that will be passed to every curl request.
-curl_options :: [CurlOption]
-curl_options =
-  [ CurlTimeout 45,
-    -- The Global cache is not thread-friendly.
-    CurlDNSUseGlobalCache False,
-     -- And we don't want to use a DNS cache anyway.
-    CurlDNSCacheTimeout 0 ]
-
-
--- | Uses the CURL API to retrieve uri. Returns 'Nothing' if there was
---   an error.
-http_get :: String -> IO (Maybe String)
-http_get uri =
-  withCurlDo $ do
-  -- 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).
-  resp <- do_curl_ curl uri curl_options :: IO CurlResponse
-
-  -- Pull out the response code as a CurlCode.
-  let code = respCurlCode resp
-
-  case code of
-    CurlOK -> return $ Just (respBody resp)
-    error_code -> do
-      hPutStrLn stderr ("HTTP Error: " ++ (show error_code))
-      -- If an error occurred, we want to dump as much information as
-      -- possible. If this becomes a problem, we can use respGetInfo to
-      -- query the response object for more information
-      return Nothing
+-- | Retrieve a URL, or crash.
+http_get :: String -> IO B.ByteString
+http_get url = do
+  manager <- newManager def
+  request <- parseUrl url
+
+  C.runResourceT $ do
+    signed_request <- signOAuth oauth credential request
+    response <- http signed_request manager
+    responseBody response C.$$+- sinkLbs
+
+  where
+    consumer_key = BC.pack ""
+    consumer_secret = BC.pack ""
+    access_token = BC.pack ""
+    access_secret = BC.pack ""
+
+    oauth :: OAuth
+    oauth = newOAuth {
+              oauthConsumerKey = consumer_key,
+              oauthConsumerSecret = consumer_secret
+            }
+
+    credential :: Credential
+    credential = newCredential access_token access_secret