├── .gitignore ├── Cabal2Arch └── Util.hs ├── LICENSE ├── Main.hs ├── README.md ├── Setup.lhs ├── cabal2arch.cabal └── data ├── ghc-provides.txt ├── library-providers.txt └── platform-provides.txt /.gitignore: -------------------------------------------------------------------------------- 1 | dist/ 2 | *~ 3 | .*.swp 4 | -------------------------------------------------------------------------------- /Cabal2Arch/Util.hs: -------------------------------------------------------------------------------- 1 | -- | 2 | -- Module : Cabal2Arch.Util: utility functions for cabal2arch 3 | -- Copyright : (c) Don Stewart, 2008 .. 2010 4 | -- License : BSD3 5 | -- 6 | -- Maintainer: Arch Haskell Team 7 | -- Stability : provisional 8 | 9 | module Cabal2Arch.Util where 10 | 11 | import Data.List 12 | 13 | import Control.Monad 14 | import Control.Concurrent 15 | import qualified Control.Exception as CE 16 | 17 | import System.Directory 18 | import System.Environment 19 | import System.Exit 20 | import System.FilePath 21 | import System.IO 22 | import System.Process hiding(cwd) 23 | 24 | import Control.Monad.Trans 25 | import Control.Monad.Error 26 | import Distribution.ArchLinux.SystemProvides 27 | 28 | import Paths_cabal2arch 29 | 30 | type IOErr a = ErrorT String IO a 31 | 32 | ------------------------------------------------------------------------ 33 | -- Read a file from a URL 34 | -- 35 | getFromURL :: String -> IOErr String 36 | getFromURL url = do 37 | res <- liftIO (myReadProcess "curl" ["-f", url] "") 38 | case res of 39 | Left _ -> throwError ("Unable to retrieve " ++ url) 40 | Right s -> liftIO (return s) 41 | 42 | -- Read from a file 43 | getFromFile :: String -> IOErr String 44 | getFromFile path = do 45 | b <- liftIO (doesFileExist path) 46 | if not b 47 | then throwError ("File " ++ path ++ " does not exist!") 48 | else liftIO (readFile path) 49 | 50 | getDefaultSystemProvides :: ErrorT String IO SystemProvides 51 | getDefaultSystemProvides = getSystemProvidesFromPath =<< (liftIO $ getDataFileName "data") 52 | -- getSystemProvidesFromPath "http://andromeda.kiwilight.com/~remy.oudompheng/arch-haskell/default" 53 | 54 | getSystemProvidesFromPath :: String -> IOErr SystemProvides 55 | getSystemProvidesFromPath dir 56 | | null dir = getDefaultSystemProvides 57 | | "http://" `isPrefixOf` dir || "ftp://" `isPrefixOf` dir = do 58 | fc <- getFromURL (dir "ghc-provides.txt") 59 | fp <- getFromURL (dir "platform-provides.txt") 60 | ft <- getFromURL (dir "library-providers.txt") 61 | return (parseSystemProvides fc fp ft) 62 | | otherwise = do 63 | fc <- getFromFile (dir "ghc-provides.txt") 64 | fp <- getFromFile (dir "platform-provides.txt") 65 | ft <- getFromFile (dir "library-providers.txt") 66 | return (parseSystemProvides fc fp ft) 67 | 68 | ------------------------------------------------------------------------ 69 | -- Some extras 70 | -- 71 | 72 | die :: String -> IO a 73 | die s = do 74 | hPutStrLn stderr $ "cabal2pkg:\n" ++ s 75 | exitWith (ExitFailure 1) 76 | 77 | -- Safe wrapper for getEnv 78 | getEnvMaybe :: String -> IO (Maybe String) 79 | getEnvMaybe _name = CE.handle ((const :: a -> CE.SomeException -> a) $ return Nothing) (Just `fmap` getEnv _name) 80 | 81 | ------------------------------------------------------------------------ 82 | 83 | -- 84 | -- Strict process reading 85 | -- 86 | myReadProcess :: FilePath -- ^ command to run 87 | -> [String] -- ^ any arguments 88 | -> String -- ^ standard input 89 | -> IO (Either (ExitCode,String,String) String) -- ^ either the stdout, or an exitcode and any output 90 | 91 | myReadProcess cmd _args input = CE.handle (return . handler) $ do 92 | (inh,outh,errh,pid) <- runInteractiveProcess cmd _args Nothing Nothing 93 | 94 | output <- hGetContents outh 95 | outMVar <- newEmptyMVar 96 | _ <- forkIO $ (CE.evaluate (length output) >> putMVar outMVar ()) 97 | 98 | errput <- hGetContents errh 99 | errMVar <- newEmptyMVar 100 | _ <- forkIO $ (CE.evaluate (length errput) >> putMVar errMVar ()) 101 | 102 | when (not (null input)) $ hPutStr inh input 103 | takeMVar outMVar 104 | takeMVar errMVar 105 | ex <- CE.catch (waitForProcess pid) ((const :: a -> CE.SomeException -> a) $ return ExitSuccess) 106 | hClose outh 107 | hClose inh -- done with stdin 108 | hClose errh -- ignore stderr 109 | 110 | return $ case ex of 111 | ExitSuccess -> Right output 112 | ExitFailure _ -> Left (ex, errput, output) 113 | 114 | where 115 | handler (ExitFailure e) = Left (ExitFailure e,"","") 116 | handler e = Left (ExitFailure 1, show e, "") 117 | -------------------------------------------------------------------------------- /LICENSE: -------------------------------------------------------------------------------- 1 | Copyright (c) 2008 Don Stewart 2 | 3 | All rights reserved. 4 | 5 | Redistribution and use in source and binary forms, with or without 6 | modification, are permitted provided that the following conditions 7 | are met: 8 | 9 | 1. Redistributions of source code must retain the above copyright 10 | notice, this list of conditions and the following disclaimer. 11 | 12 | 2. Redistributions in binary form must reproduce the above copyright 13 | notice, this list of conditions and the following disclaimer in the 14 | documentation and/or other materials provided with the distribution. 15 | 16 | 3. Neither the name of the author nor the names of his contributors 17 | may be used to endorse or promote products derived from this software 18 | without specific prior written permission. 19 | 20 | THIS SOFTWARE IS PROVIDED BY THE AUTHORS ``AS IS'' AND ANY EXPRESS OR 21 | IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED 22 | WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE 23 | DISCLAIMED. IN NO EVENT SHALL THE AUTHORS OR CONTRIBUTORS BE LIABLE FOR 24 | ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL 25 | DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS 26 | OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) 27 | HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, 28 | STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN 29 | ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE 30 | POSSIBILITY OF SUCH DAMAGE. 31 | -------------------------------------------------------------------------------- /Main.hs: -------------------------------------------------------------------------------- 1 | {-# LANGUAGE DeriveDataTypeable #-} 2 | 3 | -- | 4 | -- Module : cabal2arch: convert cabal packages to Arch Linux PKGBUILD format 5 | -- Copyright : (c) Don Stewart, 2008 .. 2010 6 | -- License : BSD3 7 | -- 8 | -- Maintainer: Don Stewart 9 | -- Stability : provisional 10 | -- Portability: 11 | -- 12 | 13 | -- TODO: if build-type: Configure, accurate C library dependecies 14 | -- require downloading the source, and running configure 15 | -- 16 | -- C libraries are dynamically linked, should be listed in depends, 17 | -- rather than makedepends 18 | 19 | import Distribution.PackageDescription.Parse 20 | import Distribution.Simple.Utils hiding (die) 21 | import Distribution.Verbosity 22 | import Distribution.Text 23 | 24 | -- from the archlinux package: 25 | import Distribution.ArchLinux.PkgBuild 26 | import Distribution.ArchLinux.CabalTranslation 27 | 28 | import Control.Monad 29 | import Control.Monad.Error 30 | import qualified Control.Exception as CE 31 | 32 | import Data.List 33 | 34 | import Text.PrettyPrint 35 | 36 | import Paths_cabal2arch 37 | import Data.Version (showVersion) 38 | 39 | import System.Directory 40 | import System.Exit 41 | import System.FilePath 42 | import System.IO 43 | import System.Process hiding(cwd) 44 | 45 | import System.Console.CmdArgs 46 | import Cabal2Arch.Util 47 | 48 | data CmdLnArgs 49 | = CmdLnConvertOne { argCabalFile :: String, argCreateTar :: Bool, argDataFiles :: String } 50 | deriving (Data, Typeable) 51 | 52 | cmdLnConvertOne :: CmdLnArgs 53 | cmdLnConvertOne = CmdLnConvertOne 54 | { argCabalFile = "" &= argPos 0 &= typ "FILE|DIR|URL" 55 | , argCreateTar = False &= name "tar" &= explicit &= help "Create a tar-ball for the source package." 56 | , argDataFiles = "" &= name "sysinfo" &= typDir &= explicit &= help "Use custom system information files." 57 | } &= auto &= name "conv" &= help "Convert a single CABAL file." 58 | 59 | cmdLnArgs :: CmdLnArgs 60 | cmdLnArgs = modes [cmdLnConvertOne] 61 | &= program "cabal2arch" 62 | &= summary ("cabal2arch, v. " ++ showVersion version ++ ": Convert .cabal file to ArchLinux source package") 63 | 64 | main :: IO () 65 | main = cmdArgs cmdLnArgs >>= subCmd 66 | 67 | subCmd :: CmdLnArgs -> IO () 68 | subCmd (CmdLnConvertOne cabalLoc createTar dataFiles) = 69 | CE.bracket 70 | -- We do all our work in a temp directory 71 | (do _cwd <- getCurrentDirectory 72 | etmp <- myReadProcess "mktemp" ["-d"] [] 73 | case etmp of 74 | Left _ -> die "Unable to create temp directory" 75 | Right d -> do 76 | let dir = makeValid (init d) -- drop newline 77 | setCurrentDirectory dir 78 | return (dir, _cwd)) 79 | 80 | -- Always remember to clean up 81 | (\(d, _cwd) -> do 82 | setCurrentDirectory _cwd 83 | removeDirectoryRecursive d) 84 | 85 | -- Now, get to work: 86 | $ \(tmp, _cwd) -> do 87 | 88 | -- myArgs <- cmdArgs cmdLnArgs 89 | email <- do 90 | r <- getEnvMaybe "ARCH_HASKELL" 91 | case r of 92 | Nothing -> do 93 | hPutStrLn stderr "Warning: ARCH_HASKELL environment variable not set. Set this to the maintainer contact you wish to use. \n E.g. 'Arch Haskell Team '" 94 | return [] 95 | Just s -> return s 96 | 97 | cabalfile <- findCabalFile cabalLoc _cwd tmp 98 | hPutStrLn stderr $ "Using " ++ cabalfile 99 | 100 | cabalsrc <- readPackageDescription normal cabalfile 101 | 102 | -- Create a package description with all configurations resolved. 103 | maybeSysProvides <- runErrorT $ getSystemProvidesFromPath dataFiles 104 | sysProvides <- case maybeSysProvides of 105 | Left s -> die s 106 | Right sp -> return sp 107 | let finalcabal = preprocessCabal cabalsrc sysProvides 108 | finalcabal' <- case finalcabal of 109 | Nothing -> die "Aborting..." 110 | Just f -> return f 111 | let (pkgbuild', hooks) = cabal2pkg finalcabal' sysProvides 112 | 113 | apkgbuild' <- getMD5 pkgbuild' 114 | let apkgbuild = apkgbuild' { pkgBuiltWith = Just version } 115 | pkgbuild = pkgBody apkgbuild 116 | doc = pkg2doc email apkgbuild 117 | dir = arch_pkgname pkgbuild 118 | 119 | setCurrentDirectory _cwd 120 | createDirectoryIfMissing False dir 121 | setCurrentDirectory dir 122 | 123 | writeFile "PKGBUILD" (render doc ++ "\n") 124 | 125 | -- print pkgname.install 126 | case hooks of 127 | Nothing -> return () 128 | Just i -> writeFile (install_hook_name (arch_pkgname pkgbuild)) i 129 | 130 | setCurrentDirectory _cwd 131 | 132 | _ <- system $ "rm -rf " ++ dir "{pkg,src,*.tar.gz}" 133 | when createTar $ do 134 | tarred <- myReadProcess "tar" ["-zcvvf",(dir <.> "tar.gz"), dir] [] 135 | case tarred of 136 | Left (_,s,_) -> do 137 | hPutStrLn stderr s 138 | die "Unable to tar package" 139 | Right _ -> putStrLn ("Created " ++ (_cwd dir <.> "tar.gz")) 140 | 141 | -- If the user created a .cabal2arch.log file, append log results there. 142 | mh <- getEnvMaybe "HOME" 143 | case mh of 144 | Nothing -> return () 145 | Just home -> do 146 | b <- doesFileExist $ home ".cabal2arch.log" 147 | if not b 148 | then return () 149 | else do 150 | 151 | -- Log to build file. 152 | appendFile (home ".cabal2arch.log") $ (show $ (,,) 153 | (arch_pkgname pkgbuild ++ "-" ++ (display $ arch_pkgver pkgbuild)) 154 | (arch_pkgdesc pkgbuild) 155 | (arch_url pkgbuild)) ++ "\n" 156 | 157 | ------------------------------------------------------------------------ 158 | 159 | -- | Given an abstract pkgbuild, run "makepkg -g" to compute md5 160 | -- of source files (possibly cached locally), and modify the PkgBuild 161 | -- accordingly. 162 | -- 163 | getMD5 :: AnnotatedPkgBuild -> IO AnnotatedPkgBuild 164 | getMD5 pkg = do 165 | putStrLn "Feeding the PKGBUILD to `makepkg -g`..." 166 | eres <- readProcessWithExitCode "makepkg" ["-g"] $ display pkg 167 | case eres of 168 | (ExitFailure _,_,err) -> do 169 | hPutStrLn stderr err 170 | hPutStrLn stderr $ "makepkg encountered an error while calculating MD5." 171 | return pkg 172 | (ExitSuccess,out,err) -> do 173 | -- s should be "md5sums=(' ... ')" 174 | hPutStrLn stderr err 175 | if "md5sums=('" `isPrefixOf` out 176 | then 177 | let md5sum = takeWhile (\x -> x `elem` "0123456789abcdef") $ drop 10 out 178 | in return pkg { pkgBody = (pkgBody pkg) { arch_md5sum = ArchList [md5sum] } } 179 | else do 180 | hPutStrLn stderr $ "Incorrect output from makepkg." 181 | return pkg 182 | 183 | -- Return the path to a .cabal file. 184 | -- If not arguments are specified, use ".", 185 | -- if the argument looks like a url, download that 186 | -- otherwise, assume its a directory 187 | -- 188 | findCabalFile :: String -> FilePath -> FilePath -> IO FilePath 189 | findCabalFile file _cwd tmp = do 190 | let epath 191 | | null file 192 | = Right _cwd 193 | | "http://" `isPrefixOf` file 194 | = Left file 195 | | ".cabal" `isSuffixOf` file 196 | = Right (makeValid (joinPath [_cwd,file])) 197 | | otherwise -- a directory path 198 | = Right file 199 | 200 | -- download url to .cabal 201 | case epath of 202 | Left url -> do 203 | eres <- myReadProcess "wget" [url] [] 204 | case eres of 205 | Left (_,s,_) -> do 206 | hPutStrLn stderr s 207 | die $ "Couldn't download .cabal file: " ++ show url 208 | Right _ -> findPackageDesc tmp -- tmp dir 209 | 210 | -- it might be a .cabal file 211 | Right f | ".cabal" `isSuffixOf` f -> do 212 | b <- doesFileExist f 213 | if not b 214 | then die $ ".cabal file doesn't exist: " ++ show f 215 | else return f 216 | 217 | -- or assume it is a dir to a file: 218 | Right dir -> do 219 | b <- doesDirectoryExist dir 220 | if not b 221 | then die $ "directory doesn't exist: " ++ show dir 222 | else findPackageDesc dir 223 | 224 | -------------------------------------------------------------------------------- /README.md: -------------------------------------------------------------------------------- 1 | *This tool is no longer maintained* 2 | 3 | Nowadays we use [cblrepo](https://github.com/magthe/cblrepo) to maintain the haskell packages in HABS. 4 | 5 | Please let us know if you would have use of `cabal2arch` and want to take over maintainership. 6 | 7 | cabal2arch 8 | ========== 9 | 10 | cabal2arch is a tool used to convert CABAL ([Common Architecture for 11 | Building Applications and Libraries][1]) files into [ArchLinux][2] 12 | source packages. 13 | 14 | Usage 15 | ----- 16 | 17 | As its only argument, cabal2arch expects a file path, directory path, or 18 | URL to the Cabal description of the package that should be converted. 19 | For example: 20 | 21 | % cabal2arch puremd5.cabal 22 | % cabal2arch http://hackage.haskell.org/packages/archive/pureMD5/2.1.0.1/pureMD5.cabal 23 | 24 | Build and install 25 | ----------------- 26 | 27 | Run the well-known triple: 28 | 29 | % runhaskell Setup.lhs configure 30 | % runhaskell Setup.lhs build 31 | % runhaskell Setup.lhs install 32 | 33 | [1]: http://www.haskell.org/ghc/docs/latest/html/Cabal/ 34 | [2]: http://www.archlinux.org/ 35 | -------------------------------------------------------------------------------- /Setup.lhs: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env runhaskell 2 | > import Distribution.Simple 3 | > main = defaultMain 4 | -------------------------------------------------------------------------------- /cabal2arch.cabal: -------------------------------------------------------------------------------- 1 | name: cabal2arch 2 | version: 1.2 3 | homepage: http://github.com/archhaskell/ 4 | synopsis: Create Arch Linux packages from Cabal packages. 5 | description: Create Arch Linux packages from Cabal packages. 6 | category: Distribution 7 | license: BSD3 8 | license-file: LICENSE 9 | author: Don Stewart , 10 | Matthew William Cox , 11 | Adam Vogt , 12 | Asgaroth , 13 | Rémy Oudompheng , 14 | Magnus Therning , 15 | Peter Simons 16 | maintainer: ArchHaskell Team 17 | cabal-version: >= 1.6 18 | build-type: Simple 19 | data-files: data/*.txt 20 | 21 | source-repository head 22 | type: git 23 | location: git://github.com/archhaskell/cabal2arch.git 24 | 25 | executable cabal2arch 26 | main-is: Main.hs 27 | ghc-options: -Wall 28 | 29 | build-depends: 30 | base >= 4 && <= 6, 31 | pretty, 32 | process, 33 | directory, 34 | containers, 35 | bytestring, 36 | Cabal > 1.8, 37 | filepath, 38 | mtl, 39 | archlinux >= 1 && < 2, 40 | cmdargs 41 | 42 | other-modules: 43 | Cabal2Arch.Util 44 | -------------------------------------------------------------------------------- /data/ghc-provides.txt: -------------------------------------------------------------------------------- 1 | # 2 | # GHC core packages and their versions. 3 | # 4 | # http://haskell.org/haskellwiki/Libraries_released_with_GHC 5 | # 6 | 7 | base ==4.3.1.0 8 | bin-package-db ==0.0.0.0 9 | ffi ==1.0 10 | ghc ==7.0.3 11 | ghc-binary ==0.5.0.2 12 | ghc-prim ==0.2.0.0 13 | integer-gmp ==0.2.0.3 14 | rts ==1.0 15 | -------------------------------------------------------------------------------- /data/library-providers.txt: -------------------------------------------------------------------------------- 1 | # 2 | # This file lists external library dependencies and the ArchLinux packages 3 | # providing them. 4 | # 5 | 6 | Imlib2 imlib2 7 | SDL sdl 8 | adns adns 9 | alut freealut 10 | asound alsa-lib 11 | bz2 bzip2 12 | cairo cairo 13 | cblas blas 14 | crack cracklib 15 | crypt glibc 16 | crypto openssl 17 | csound64 csound5 18 | curl curl 19 | curses ncurses 20 | cv opencv 21 | db_cxx db 22 | doublefann fann 23 | ev libev 24 | event libevent 25 | exif libexif 26 | ffi libffi 27 | fftw3 fftw 28 | freetype freetype2 29 | gcc_s gcc-libs 30 | gconf gconf 31 | gcrypt libgcrypt 32 | gdk gtk 33 | gdk-x11-2.0 gtk2 34 | gio glib2 35 | gl mesa 36 | glib glib2 37 | glu mesa 38 | glut freeglut 39 | gmodule glib2 40 | gnome-vfs-module 41 | gnutls gnutls 42 | gnutls-extra gnutls 43 | gobject glib2 44 | gstreamer gstreamer0.10 45 | gstreamer-audio gstreamer0.10-base 46 | gstreamer-base gstreamer0.10 47 | gstreamer-controller gstreamer0.10 48 | gstreamer-dataprotocol gstreamer0.10 49 | gstreamer-net gstreamer0.10 50 | gstreamer-plugins-base gstreamer0.10-base 51 | gthread glib 52 | gtk+ gtk2 53 | gtk-x11-2.0 gtk2 54 | gtksourceview gtksourceview2 55 | highgui opencv 56 | icudata icu 57 | icui18n icu 58 | icuuc icu 59 | idn libidn 60 | il devil 61 | jpeg libjpeg 62 | ldap libldap 63 | libgsasl gsasl 64 | libxml libxml2 65 | m glibc 66 | mtp libmtp 67 | ncurses ncurses 68 | ncursesw ncurses 69 | netsnmp net-snmp 70 | odbc unixodbc 71 | ogg libogg 72 | ogremain 73 | panel ncurses 74 | pango pango 75 | pangocairo pango 76 | pcap libpcap 77 | pcre pcre 78 | png libpng 79 | pq postgresql 80 | pthread glibc 81 | sndfile libsndfile 82 | sqlite3 sqlite3 83 | ssl openssl 84 | stdc++ gcc-libs 85 | theora libtheora 86 | tiff libtiff 87 | uuid e2fsprogs 88 | vte vte 89 | webkit libwebkit 90 | wmflite libwmf 91 | wx wxgtk 92 | x11 libx11 93 | xdamage libxdamage 94 | xenctrl xen 95 | xine xine-lib 96 | xml2 libxml2 97 | xrandr libxrandr 98 | xslt libxslt 99 | xss libxss 100 | z zlib 101 | zmq zeromq 102 | -------------------------------------------------------------------------------- /data/platform-provides.txt: -------------------------------------------------------------------------------- 1 | # Packages that are not part of GHC, but are required by Haskell Platform. 2 | 3 | # HP 2011.2.0.0 packages provided by GHC 7.0.3: 4 | array ==0.3.0.2 5 | bytestring ==0.9.1.10 6 | Cabal ==1.10.1.0 7 | containers ==0.4.0.0 8 | directory ==1.1.0.0 9 | extensible-exceptions ==0.1.1.2 10 | filepath ==1.2.0.0 11 | haskell2010 ==1.0.0.0 12 | haskell98 ==1.1.0.1 13 | hpc ==0.5.0.6 14 | old-locale ==1.0.0.2 15 | old-time ==1.0.0.6 16 | pretty ==1.0.1.2 17 | process ==1.0.1.5 18 | random ==1.0.0.3 19 | template-haskell ==2.5.0.0 20 | time ==1.2.0.3 21 | unix ==2.4.2.0 22 | 23 | # HP 2011.2.0.0 packages not provided by GHC 7.0.2: 24 | cgi ==3001.1.7.4 25 | fgl ==5.4.2.3 26 | GLUT ==2.1.2.1 27 | haskell-src ==1.0.1.4 28 | html ==1.0.1.2 29 | HUnit ==1.2.2.3 30 | network ==2.3.0.2 31 | OpenGL ==2.2.3.0 32 | parallel ==3.1.0.1 33 | parsec ==3.1.1 34 | QuickCheck ==2.4.0.1 35 | regex-base ==0.93.2 36 | regex-compat ==0.93.1 37 | regex-posix ==0.94.4 38 | stm ==2.2.0.1 39 | syb ==0.3 40 | xhtml ==3000.2.0.1 41 | zlib ==0.5.3.1 42 | HTTP ==4000.1.1 43 | deepseq ==1.1.0.2 44 | 45 | # HP proposals: 46 | text ==0.11.0.5 47 | transformers ==0.2.2.0 48 | mtl ==2.0.1.0 49 | 50 | # Build tools: 51 | cabal-install ==0.10.2 52 | alex ==2.3.5 53 | happy ==1.18.6 54 | hscolour ==1.17 55 | haddock ==2.9.2 56 | --------------------------------------------------------------------------------