The other problem is that packages currently typically specify an
optimistic upwardly open range rather than a pessimistic closed range.
Cabal uses the heuristic of picking the highest version of each package
that satisfies the version constraints.

One could try to use the Ghc Api to run Ghc in typecheck-only mode,
trying the highest versions of dependencies, as given by Cabal's heuristic,
and suggesting to add upper bounds on any dependencies with which
compilation would give errors but for which lower versions are available
within the erroneously specified ranges.

You might not even need to code your own Ghc Api client - it seems that
using something like this might do for just checking buildability without generating files, running code, or displaying prompts:

ghc -ignore-dot-ghci <package and other options from .cabal> -e '"works"' Consider these example "projects" which are somewhat picky about their package versions:

   -- WhichBase.hs, needs base 3, or base 4 + syb
   import X
   import Data.Generics
   main = putStrLn x

   -- WhichGhc.hs, needs ghc < 6.9(whenever the api was changed)
   import X
   import GHC
   main = do
     newSession Nothing
     putStrLn x

   -- X.hs, just to check that we're doing import chasing
   module X where
   x = "hi"

Then we can find out whether open-ended dependencies like just "ghc" or just "base" will do:

$ /cygdrive/c/ghc/ghc-6.8.3/bin/ghc -ignore-dot-ghci -hide-all-packages -package base -package ghc -e '"works"' WhichBase.hs
   "works"

$ /cygdrive/c/ghc/ghc-6.11.20080925/bin/ghc -ignore-dot-ghci -hide-all-packages -package base -e '"works"' WhichBase.hs
   *** Exception: Could not find module `Data.Generics':
     it is a member of package base-3.0.3.0, which is hidden

$ /cygdrive/c/ghc/ghc-6.11.20080925/bin/ghc -ignore-dot-ghci -hide-all-packages -package base-3.0.3.0 -e '"works"' WhichBase.hs
   "works"

$ /cygdrive/c/ghc/ghc-6.11.20080925/bin/ghc -ignore-dot-ghci -hide-all-packages -package base -package syb -e '"works"' WhichBase.hs
   "works"


$ /cygdrive/c/ghc/ghc-6.8.3/bin/ghc -ignore-dot-ghci -hide-all-packages -package base -package ghc -e '"works"' WhichGhc.hs
   "works"

$ /cygdrive/c/ghc/ghc-6.11.20080925/bin/ghc -ignore-dot-ghci -hide-all-packages -package base -package ghc -e '"works"' WhichGhc.hs WhichGhc.hs:4:2: Not in scope: `newSession'

Does that help?
Claus

_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to