About cabal and compatibility

Robert Dockins robdockins at fastmail.fm
Sat Dec 10 19:37:37 EST 2005


On Saturday 10 December 2005 07:14 pm, you wrote:
> Robert Dockins <robdockins at fastmail.fm> writes:
> > [snip]
> >
> >> This would greatly simplify the Distribution.Simple.UserHooks
> >> structure bringing it from 34 fields to 14 fields, or so.
> >>
> >> Downsides: Making pre and post hooks would now be slightly harder, and
> >> it would break existing hooks-using code.
> >
> > I just want to mention that these kind of changes represent represent a
> > VERY big problem. I discussed that issue at some length in an email I
> > intended to send to this list very recently, but it seems to have gotten
> > lost.
>
> Are you sure they represent a very big problem in practice and not
> just in theory?  

[snip]

Well, obviously it isn't a practical problem yet.  If it was we'd have people 
screaming about it on the lists.

The thing that got me thinking about it was Happy.  Its recently been put in a  
darcs, and Simon Marlow mentioned to me that they are looking at moving to 
Cabal for the build system.

The Happy build system now does two things that aren't your standard build 
actions:

1) It creates module which contains the version string before compilation
2) After compilation it runs CPP on a number of template files with various 
different "-D" options to genreate the parser templates.

I was messing around with doing these using user hooks and I ended up needing 
to tie pretty deeply into cabal even for the simple task 1).

I have attached my initial attempts so you can see what's happening.

The user hooks change you are talking about would require a complete rework of 
my Setup.hs file.  Its only ~130 lines, but then Happy is a pretty small 
project.

> I only know of one or two packages that use the hooks.  Do you know of
> backward compatibility problems that cabal has caused?

No, this is all speculation currently.

> BTW, I just added a "cabal-version" field to cabal so that if a
> package requires a particular version of cabal, it can say so.

Well, cabal the library already has to be invoked before the package file is 
even read!  If the Setup.hs doesn't typecheck because the cabal interfaces 
have changed, you won't even get that far.  To make a "cabal-version" field 
work you'd need some kind of bootstrapping step (which would itself need a 
very stable interface).

> Further, my grand plan is that once stuff gets into hackage, we can
> try making modifications and seeing if it breaks any packages, and if
> so, offer patches to those package authors (since it's probably eaiser
> for cabal hackers to write such patches than most package authors).

That depends on the complexity of the build system.  In my experience, just 
trying to figure out what a build system is doing can be pretty difficult.  I 
can't imagine you want to undertake the maintaince of other people's build 
systems.

OTOH, if Cabal is only aiming at pretty simple projects, this may never be an 
issue.

> (snip)
>
> > I suggest that the cabal team very seriously consider using the Eternal
> > Compatibility in Theory method to manage interface change.
>
> I'll look at this.
>
> peace,
>
>   isaac
-------------- next part --------------
import Data.Version
import Control.Exception
import System.Cmd
import System.IO
import System.Exit
import System.Directory
import Distribution.Setup
import Distribution.Simple
import Distribution.Simple.Utils
import Distribution.Simple.LocalBuildInfo
import Distribution.PackageDescription


main = do
  descFile <- defaultPackageDesc
  desc <- readPackageDescription descFile
  let ver = (pkgVersion (package desc))
  defaultMainWithHooks (mkHooks desc ver)

mkHooks :: PackageDescription
        -> Version
        -> UserHooks
mkHooks desc ver = 
  defaultUserHooks
  { readDesc  = return (Just desc)
  , postConf  = doPostConf ver
  , postBuild = createTemplates
  , postClean = cleanDerivedFiles
  }


templateFiles :: [String]
templateFiles =
  [ "HappyTemplate"
  , "HappyTemplate-ghc"
  , "HappyTemplate-coerce"
  , "HappyTemplate-arrays"
  , "HappyTemplate-arrays-ghc"
  , "HappyTemplate-arrays-coerce"
  , "HappyTemplate-arrays-debug"
  , "HappyTemplate-arrays-ghc-debug"
  , "HappyTemplate-arrays-coerce-debug"
  , "GLR_Base"
  , "GLR_Lib"
  , "GLR_Lib-ghc"
  , "GLR_Lib-ghc-debug"
  ]


cleanDerivedFiles :: Args
                  -> Int
                  -> LocalBuildInfo
                  -> IO ExitCode
cleanDerivedFiles args _ buildInfo = do
  sequence_ $ map (delFile . (\x -> "templates/"++x++".hspp")) $ templateFiles
  sequence_ $ map (delFile . (\x -> "templates/"++x)) $ templateFiles
  removeFile "src/Version.hs"
  return ExitSuccess
 where delFile path = try (removeFile path) >> return ()


doPostConf :: Version
           -> Args 
           -> ConfigFlags
           -> LocalBuildInfo 
           -> IO ExitCode

doPostConf version args flags buildInfo = do
  case (compilerFlavor (compiler buildInfo)) of
     GHC -> do
       createVersionModule version
       return ExitSuccess

     _ -> do
       putStrLn "Currently only GHC is supported as a build platform for Happy"
       return (ExitFailure 1)


createVersionModule :: Version -> IO ()
createVersionModule version = do
  h <- openFile "src/Version.hs" WriteMode
  hPutStr h "module Version where\n"
  hPutStr h ("version = \""++(showVersion version)++"\"")
  hClose h


createTemplates :: Args
                -> Int
                -> LocalBuildInfo
                -> IO ExitCode
createTemplates args _ buildInfo = do
  putStrLn "building parser templates..."

  pwd <- getCurrentDirectory
  setCurrentDirectory (pwd++"/templates")

  defaultTemplate "HappyTemplate" []
  defaultTemplate "HappyTemplate-ghc" [ghcOpt]
  defaultTemplate "HappyTemplate-coerce" [ghcOpt,coerceOpt]
  defaultTemplate "HappyTemplate-arrays" [arrayOpt]
  defaultTemplate "HappyTemplate-arrays-ghc" [ghcOpt,arrayOpt]
  defaultTemplate "HappyTemplate-arrays-coerce" [ghcOpt,arrayOpt,coerceOpt]
  defaultTemplate "HappyTemplate-arrays-debug" [arrayOpt,debugOpt]
  defaultTemplate "HappyTemplate-arrays-ghc-debug" [arrayOpt,ghcOpt,debugOpt]
  defaultTemplate "HappyTemplate-arrays-coerce-debug" [ghcOpt,arrayOpt,coerceOpt,debugOpt]
  runCpp "GLR_Base" [] "GLR_Base.lhs"
  glrTemplate "GLR_Lib" []
  glrTemplate "GLR_Lib-ghc" [ghcOpt]
  glrTemplate "GLR_Lib-ghc-debug" [ghcOpt,debugOpt]

  setCurrentDirectory pwd
  return ExitSuccess

 where ghc = compilerPath (compiler buildInfo)
       ghcOpt    = "-DHAPPY_GHC"
       coerceOpt = "-DHAPPY_COERCE"
       arrayOpt  = "-DHAPPY_ARRAY"
       debugOpt  = "-DHAPPY_DEBUG"
       cppArgs = 
          if (compilerVersion (compiler buildInfo)) >= Version{ versionBranch = [4,11,4], versionTags = [] }
            then ["-E","-cpp","-o"]
            else ["-E","-cpp",">"]

       perlRE = "s/^#\\s+(\\d+)\\s+(\\\"[^\\\"]*\\\")/{-# LINE \\1 \\2 #-}/g;s/\\$$(Id:.*)\\$$/\\1/g"

       runCpp file args template = do
           rawSystem ghc (concat [cppArgs,[file],args,[template]])
	   rawSystem "perl" ["-pi.hspp","-e",perlRE,file]

       defaultTemplate file args = runCpp file args "GenericTemplate.hs"
       glrTemplate file args     = runCpp file args "GLR_Lib.lhs"


More information about the Libraries mailing list