Skip to content

Commit

Permalink
Put a header in the dist/setup-config file and check it on loading
Browse files Browse the repository at this point in the history
This should fix ticket #120 in future which is the problem where you do
something like "sudo runghc Setup install" and you accidentally end up
using a different version of the compiler or of the Cabal lib and you get
an unhelpful error message:
> Setup.hs: error reading ./.setup-config; run "setup configure" command?
Well now you'll get a helpful error message:
> setup: You need to re-run the 'configure' command. The version of Cabal
> being used has changed (was Cabal-1.3.6, now Cabal-1.3.7).
If the compiler version being used has changed too we get the extra helpful:
> setup: You need to re-run the 'configure' command. The version of Cabal
> being used has changed (was Cabal-1.3.6, now Cabal-1.3.7). Additionally
> the compiler is different (was ghc-6.8, now ghc-6.9) which is probably
> the cause of the problem.
Of course this does not help for older versions of Cabal but there's not a
lot we can do about that.
  • Loading branch information
dcoutts committed Mar 3, 2008
1 parent 1ff75da commit f94785e
Show file tree
Hide file tree
Showing 2 changed files with 86 additions and 13 deletions.
91 changes: 78 additions & 13 deletions Distribution/Simple/Configure.hs
Original file line number Diff line number Diff line change
Expand Up @@ -55,10 +55,10 @@ module Distribution.Simple.Configure (configure,
where

import Distribution.Simple.Compiler
( CompilerFlavor(..), Compiler(..), compilerVersion, showCompilerId
( CompilerFlavor(..), Compiler(compilerFlavor), compilerVersion, showCompilerId
, unsupportedExtensions, PackageDB(..) )
import Distribution.Package
( PackageIdentifier(..), showPackageId, Package(..) )
( PackageIdentifier(..), showPackageId, parsePackageId, Package(..) )
import Distribution.InstalledPackageInfo
( InstalledPackageInfo, emptyInstalledPackageInfo )
import qualified Distribution.InstalledPackageInfo as InstalledPackageInfo
Expand All @@ -76,6 +76,8 @@ import Distribution.PackageDescription.Check
( PackageCheck(..), checkPackage, checkPackageFiles )
import Distribution.ParseUtils
( showDependency )
import Distribution.Compat.ReadP
( readP_to_S )
import Distribution.Simple.Program
( Program(..), ProgramLocation(..), ConfiguredProgram(..)
, ProgramConfiguration, defaultProgramConfiguration
Expand All @@ -94,7 +96,7 @@ import Distribution.Simple.BuildPaths
( distPref )
import Distribution.Simple.Utils
( die, warn, info, setupMessage, createDirectoryIfMissingVerbose
, intercalate, comparing )
, intercalate, comparing, cabalVersion, cabalBootstrapping )
import Distribution.Simple.Register
( removeInstalledConfig )
import Distribution.System
Expand Down Expand Up @@ -129,7 +131,7 @@ import System.Exit
import System.FilePath
( (</>) )
import qualified System.Info
( arch )
( arch, compilerName, compilerVersion )
import System.IO
( hPutStrLn, stderr )
import Text.PrettyPrint.HughesPJ
Expand All @@ -139,14 +141,42 @@ import Prelude hiding (catch)

tryGetConfigStateFile :: (Read a) => FilePath -> IO (Either String a)
tryGetConfigStateFile filename = do
e <- doesFileExist filename
let dieMsg = "error reading " ++ filename ++
"; run \"setup configure\" command?\n"
if (not e) then return $ Left dieMsg else do
str <- readFile filename
case reads str of
[(bi,_)] -> return $ Right bi
_ -> return $ Left dieMsg
exists <- doesFileExist filename
if not exists
then return (Left missing)
else do
str <- readFile filename
return $ case lines str of
[headder, rest] -> case checkHeader headder of
Just msg -> Left msg
Nothing -> case reads rest of
[(bi,_)] -> Right bi
_ -> Left cantParse
_ -> Left cantParse
where
checkHeader :: String -> Maybe String
checkHeader header = case parseHeader header of
Just (cabalId, compilerId)
| cabalId
== currentCabalId -> Nothing
| otherwise -> Just (badVersion cabalId compilerId)
Nothing -> Just cantParse

missing = "Run the 'configure' command first."
cantParse = "Saved package config file seems to be corrupt. "
++ "Try re-running the 'configure' command."
badVersion cabalId compilerId
= "You need to re-run the 'configure' command. "
++ "The version of Cabal being used has changed (was "
++ showPackageId cabalId ++ ", now "
++ showPackageId currentCabalId ++ ")."
++ badcompiler compilerId
badcompiler compilerId | compilerId == currentCompilerId = ""
| otherwise
= " Additionally the compiler is different (was "
++ showPackageId compilerId ++ ", now "
++ showPackageId currentCompilerId
++ ") which is probably the cause of the problem."

-- internal function
tryGetPersistBuildConfig :: IO (Either String LocalBuildInfo)
Expand All @@ -171,7 +201,42 @@ maybeGetPersistBuildConfig = do
writePersistBuildConfig :: LocalBuildInfo -> IO ()
writePersistBuildConfig lbi = do
createDirectoryIfMissing False distPref
writeFile localBuildInfoFile (show lbi)
writeFile localBuildInfoFile $ showHeader pkgid
++ '\n' : show lbi
where
pkgid = packageId (localPkgDescr lbi)

showHeader :: PackageIdentifier -> String
showHeader pkgid =
"Saved package config for " ++ showPackageId pkgid
++ " written by " ++ showPackageId currentCabalId
++ " using " ++ showPackageId currentCompilerId
where

currentCabalId :: PackageIdentifier
currentCabalId = PackageIdentifier "Cabal" currentVersion
where currentVersion | cabalBootstrapping = Version [0] []
| otherwise = cabalVersion

currentCompilerId :: PackageIdentifier
currentCompilerId = PackageIdentifier System.Info.compilerName
System.Info.compilerVersion

parseHeader :: String -> Maybe (PackageIdentifier, PackageIdentifier)
parseHeader header = case words header of
["Saved", "package", "config", "for", pkgid,
"written", "by", cabalid, "using", compilerid]
-> case (readPackageId pkgid,
readPackageId cabalid,
readPackageId compilerid) of
(Just _,
Just cabalid',
Just compilerid') -> Just (cabalid', compilerid')
_ -> Nothing
_ -> Nothing
where readPackageId str = case readP_to_S parsePackageId str of
[] -> Nothing
ok -> Just (fst (last ok))

-- |Check that localBuildInfoFile is up-to-date with respect to the
-- .cabal file.
Expand Down
8 changes: 8 additions & 0 deletions Distribution/Simple/Utils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -46,6 +46,7 @@ OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -}

module Distribution.Simple.Utils (
cabalVersion,
cabalBootstrapping,

-- * logging and errors
die,
Expand Down Expand Up @@ -162,6 +163,13 @@ cabalVersion = Version [CABAL_VERSION] []
cabalVersion = error "Cabal was not bootstrapped correctly"
#endif

cabalBootstrapping :: Bool
#ifdef CABAL_VERSION
cabalBootstrapping = False
#else
cabalBootstrapping = True
#endif

-- ------------------------------------------------------------------------------- Utils for setup

dieWithLocation :: FilePath -> (Maybe Int) -> String -> IO a
Expand Down

0 comments on commit f94785e

Please sign in to comment.