[Haskell-cafe] Parsing cabal files to calculate average number of dependencies

Gwern Branwen gwern0 at gmail.com
Sat Jul 2 01:26:44 CEST 2011


Another thing you can do along the same lines is generate a script to
download all the repos from packages which declare repos. Some ugly
code:

import Data.Maybe (fromJust)
import Distribution.PackageDescription
import Distribution.PackageDescription.Parse
import Control.Monad (unless)

main :: IO ()
main = do cbl <- getContents
          let desc = parsePackageDescription cbl
          case desc of
            ParseFailed _ -> return ()
            ParseOk _ d -> do let repos = repoPair $ extractHead $
extractRepos d
                              let cmd = concatMap shellify repos
                              unless (null cmd) $ putStrLn cmd

shellify :: (RepoType, String) -> String
shellify (rt,url) = case rt of
                       Darcs -> "darcs get " ++ url
                       Git -> "git clone " ++ url
                       SVN -> "svn clone " ++ url
                       CVS -> "cvs co " ++ url
                       Mercurial -> "hg clone " ++ url
                       _ -> ""

repoPair :: [SourceRepo] -> [(RepoType, String)]
repoPair = map (\x -> (fromJust $ repoType x, fromJust $ repoLocation x))

extractHead :: [SourceRepo] -> [SourceRepo]
extractHead rs = filter (\x -> isnothing x && ishead x) rs
                where ishead sr = case repoKind sr of
                        RepoHead -> True
                        _ -> False
                      isnothing ss = case repoType ss of
                                       Nothing -> False
                                       Just _ -> case repoLocation ss of
                                                     Nothing -> False
                                                     Just _ -> True

extractRepos :: GenericPackageDescription -> [SourceRepo]
extractRepos = sourceRepos . packageDescription

This generates results (with the same find command and setup as
previously) like:

...
git clone git://gitorious.org/maximus/mandulia.git
darcs get http://darcs.cielonegro.org/HsOpenSSL/
darcs get http://darcs.cielonegro.org/HsOpenSSL/
hg clone https://bitbucket.org/bos/text-icugit clone
https://github.com/bos/text-icu
darcs get http://code.haskell.org/Graphalyze
darcs get http://code.haskell.org/~roelvandijk/code/base-unicode-symbols
git clone git://github.com/roelvandijk/base-unicode-symbols.git
darcs get http://code.haskell.org/~basvandijk/code/regions
git clone https://github.com/skogsbaer/xmlgen
git clone git://github.com/tanakh/HongoDB.git
darcs get http://repos.mornfall.net/shellish
darcs get http://patch-tag.com/r/Saizan/syb-with-class/
git clone git://github.com/ekmett/eq.git
git clone git://github.com/ekmett/data-lens-fd.git
git clone git://github.com/ekmett/streams.git
git clone git://github.com/alanz/hjsmin.git
darcs get http://patch-tag.com/r/byorgey/diagrams-lib
...

--
gwern
http://www.gwern.net/haskell/Archiving%20GitHub



More information about the Haskell-Cafe mailing list