[Haskell-cafe] Hackage upload log

Michael Snoyman michael at snoyman.com
Fri Apr 11 11:32:16 UTC 2014


On Fri, Apr 11, 2014 at 9:02 AM, Michael Snoyman <michael at snoyman.com>wrote:

> There used to be a log of Hackage uploads available at [1], but "it's just
> not here" anymore. Has that content moved to a different URL? Or is there
> some new way to get that information? I'd like to know the upload dates of
> every package. I could definitely screenscrape fro the date on the package
> listing pages, but I was hoping for something a bit more elegant.
>
> [1] http://hackage.haskell.org/packages/archive/log
>

Just in case anyone else needs something like this, I ended up hacking
together a quick screen scraper, though it would be nice if this was
available via an API:

{-# LANGUAGE OverloadedStrings #-}
import Text.XML.Cursor
import Text.HTML.DOM (sinkDoc)
import Network.HTTP.Client.Conduit
import Data.Conduit
import Control.Monad.IO.Class
import qualified Data.Text as T
import Data.Time
import System.Locale

main = withManager $ do
    withResponse ("http://hackage.haskell.org/package/conduit-1.1.0") $
\res -> do
        doc <- responseBody res $$ sinkDoc
        let uploadDate = fromDocument doc $// element "th" >=> hasContent
"Upload date" >=> followingSibling &/ content
        liftIO $ print (parseTime defaultTimeLocale "%c" $ T.unpack $
T.concat uploadDate :: Maybe UTCTime)

hasContent t c =
    if T.concat (c $// content) == t
        then [c]
        else []
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20140411/4540a45e/attachment.html>


More information about the Haskell-Cafe mailing list