[Haskell-cafe] cabal specify a "tested version", ghci target?

Marc Weber marco-oweber at gmx.de
Fri Aug 11 21:52:08 EDT 2006


1.)
	I know I can use
		Build-Depends:   lib == <version>, lib2 < version, lib3 >= version
	and so on.

	Do you think it would be useful to introducue some notation to indicate
	a "tested with" ?

	Reason, purpose: I think its sometimes the case that a author/ mantainer
	is quite busy with other projects and misses that some dependencies
	break things.. If you want to try out you're left with some compiler
	errors and a dependency and have to try out which version works.

	I would propose using this syntax:
		lib-1.3 >=1.1 
	to indicate that lib 1.1 is required at leeast and tested with up to
	1.3.. Cabal might then give a warning if you try to use 1.4 or greater
	"using newer version than tested" or similar..

	What do you think?
	Would this be useful?

2.)
	Is there a ghci target?
	I find it quite useful using ghci to debug test/ check types
	functions of single modules...

	My hack is using a Setup.hs file like this adding ./setup ghci 
	which runs ghci and adds all dependency as -pakcage arguments:

		module Main where
		import Distribution.Simple
		import Distribution.Simple.Configure 
		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

	Would this be useful for you, too?

Marc W.


More information about the Haskell-Cafe mailing list