{-# LANGUAGE QuasiQuotes, TypeFamilies, OverloadedStrings, MultiParamTypeClasses #-} {-# LANGUAGE TemplateHaskell #-} import Yesod import Yesod.AtomFeed import Yesod.Feed import Distribution.PackDeps import Data.Maybe import Data.List (sortBy) import Data.Ord (comparing) import Data.Time import Distribution.Package import Distribution.Text hiding (Text) import Control.Arrow import Distribution.Version (withinRange) import qualified Data.Map as Map import qualified Data.ByteString.Char8 as S8 import Data.Text (Text, pack, unpack) import Text.Hamlet (shamlet) data PD = PD Newest Reverses mkYesod "PD" [$parseRoutes| /favicon.ico FaviconR GET / RootR GET /feed FeedR GET /feed/#Text Feed2R GET /feed/#Text/#Text/#Text/#Text Feed3R GET /specific SpecificR GET /feed/specific/#Text SpecificFeedR GET /reverse ReverseListR GET /reverse/#Text ReverseR GET |] instance Yesod PD where approot _ = "" getFaviconR :: Handler () getFaviconR = sendFile "image/x-icon" "favicon.ico" mainCassius = [$cassius| body font-family: Arial,Helvetica,sans-serif width: 600px margin: 2em auto text-align: center p text-align: justify h2 border-bottom: 2px solid #999 input[type=text] width: 400px #footer margin-top: 15px border-top: 1px dashed #999 padding-top: 10px table border-collapse: collapse margin: 0 auto th, td border: 1px solid #333 form p margin-top: 1em text-align: center |] getRootR = defaultLayout $ do setTitle "Hackage dependency monitor" addCassius mainCassius [whamlet|

Hackage Dependency Monitor

Reverse Dependency List

What is this?

It can often get tedious to keep your package dependencies up-to-date. This tool is meant to alleviate a lot of the burden. It will automatically determine when an upper bound on a package prevents the usage of a newer version. For example, if foo depends on bar >= 0.1 && < 0.2, and bar 0.2 exists, this tool will flag it.

Enter a search string in the box above. It will find all packages containing that string in the package name, maintainer or author fields, and create an Atom feed for restrictive bounds. Simply add that URL to a news reader, and you're good to go!

\All of the code is available on Github \. Additionally, there is a package on Hackage \ with the code powering this site both as a library and as an executable, so you can test code which is not uploaded to the public Hackage server.