hasktags - small patch

Claus Reinke claus.reinke at talk21.com
Fri Feb 23 12:41:57 EST 2007


[cc-ed to libraries, as they seem to be more appropriate for cabal topics]

> Some time ago I've tweaked cabal to start ghci with package options
> given in the .cabal file.
> 
> Perhaps it might be useful for someone:

yes, i'd like to see something like this in cabal. cf also 
http://www.mail-archive.com/glasgow-haskell-users@haskell.org/msg11101.html

claus
 
> module Main where
> import Distribution.Simple
> import Distribution.Simple.Configure 
> import Distribution.Simple.LocalBuildInfo
> import System
> import System.Process
> import System.Exit
> import Monad
> 
> main= do
>  args <- getArgs -- check args to launch ghci
>  when (length args > 0) $ do
>    when ((args!!0) == "ghci") $ do
> lbi <- getPersistBuildConfig
> let packageArgs = (concat.concat) [ [" -package ", showPackageId pkg] | pkg <- packageDeps lbi ]
> system("ghci " ++ packageArgs)
> exitWith ExitSuccess
>  defaultMain -- fallback to defaultMain
> 
> Then you can use ./setup ghci to start ghci
> It is incomplete but should work for default packages..
> 
> Marc
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users at haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


More information about the Glasgow-haskell-users mailing list