[Haskell-cafe] ANNOUNCE: cabal-query 0.1

Max Desyatov explicitcall at googlemail.com
Sun Aug 9 12:34:05 EDT 2009


This package was written to assist you at finding a set of packages,
which satisfy your needs. At the moment it doesn't have a standalone
executable, but you can do the queries from your Haskell code.

It uses Data.Generics.PlateData, so

 * when Cabal package format changes, we don't have to rewrite anything
 * all queries are statically typed
 * as a disadvantage, we may suffer some performance loss when doing
   very complex queries, anyway most of processing goes while we read
   package descriptions, not querying them

Example of enduser querying code:

> module Main where

> import qualified Data.ByteString.Lazy as B
> import System.Environment
> import Distribution.Query
> import Distribution.Compiler
> import Distribution.License
> import Distribution.ModuleName hiding (main)
> import Distribution.Package
> import Distribution.PackageDescription
> import Distribution.Version
> import Distribution.Text
> import Language.Haskell.Extension

> main = (head `fmap` getArgs) >>=
>         B.readFile >>=
>         mapM_ (putStrLn . show . (x -> (display $ package x, display $ license x))) .
>         queryIndex (Not (Id (== GPL)) :& Not (Id (== BSD3)))

This queries an index file, which is commonly located at
~/.cabal/packages/hackage.haskell.org/00-index.tar in POSIX systems.

You can query any field of PackageDescription no matter how deep it
is. You don't need to provide any type signature for comparison
functions, which are wrapped in Id, as long as you use data constructors
for which type can be inferred.

In the future versions I want to add some query expressions parser, for
invoking cabal-query from command-line.  I suppose this will look like:

cabal-query -q 'license == BSD3 & stability == stable &
testedWith == GHC & repoType == (git | darcs)' <path_to_cabal-files_or_index-file>


More information about the Haskell-Cafe mailing list