Fri Jan 30 14:02:28 EET 2009  Gleb Alexeyev <[email protected]>
  * #262 iterative tests for foreign dependencies
  Optimize for succesful case. First try all libs and includes in one command, 
  proceed with further tests only if the first test fails. The same goes for 
libs 
  and headers: look for an offending one only when overall test fails.
  
New patches:

[#262 iterative tests for foreign dependencies
Gleb Alexeyev <[email protected]>**20090130120228
 Optimize for succesful case. First try all libs and includes in one command, 
 proceed with further tests only if the first test fails. The same goes for libs 
 and headers: look for an offending one only when overall test fails.
 
] {
hunk ./Distribution/Simple/Configure.hs 128
-    ( nub, partition, isPrefixOf, maximumBy )
+    ( nub, partition, isPrefixOf, maximumBy, inits )
hunk ./Distribution/Simple/Configure.hs 663
-  missingHdrs <- findMissing PD.includes headerExists
-  missingLibs <- findMissing PD.extraLibs libExists
-  explainErrors missingHdrs missingLibs
+  ifBuildsWith allHeaders (commonCppArgs ++ makeLdArgs allLibs) -- I'm feeling lucky
+           (return ())
+           (do missingLibs <- findMissingLibs
+               missingHdr  <- findOffendingHdr 
+               explainErrors missingHdr missingLibs)
hunk ./Distribution/Simple/Configure.hs 669
-        findMissing field p = filterM (\v -> not `fmap` p v) (collectField field)
+        allHeaders = collectField PD.includes
+        allLibs    = collectField PD.extraLibs
hunk ./Distribution/Simple/Configure.hs 672
-        headerExists hdr = compilesAndLinks cppArgs $
-                           "#include \""  ++ hdr ++ "\"\n" ++
-                           "int main(int argc, char** argv) { return 0; }\n"
-            where cppArgs = [ "-I" ++ dir | dir <- collectField PD.includeDirs ]
+        ifBuildsWith headers args success failure = do
+            ok <- builds (makeProgram headers) args
+            if ok then success else failure
hunk ./Distribution/Simple/Configure.hs 676
-        libExists lib = compilesAndLinks ldArgs "int main(int argc, char** argv) { return 0; }\n"
-            where ldArgs = ("-l"++lib):[ "-L" ++ dir | dir <- collectField PD.extraLibDirs ]
+        -- NOTE: if some package-local header has errors,
+        -- we will report that this header is missing. 
+        -- Maybe additional tests for local headers are needed 
+        -- for better diagnostics
+        findOffendingHdr =
+            ifBuildsWith allHeaders cppArgs
+                         (return Nothing)
+                         (go . tail . inits $ allHeaders)
+            where
+              go [] = return Nothing       -- cannot happen
+              go (hdrs:hdrsInits) = do
+                    ifBuildsWith hdrs cppArgs
+                                 (go hdrsInits)
+                                 (return . Just . last $ hdrs) 
hunk ./Distribution/Simple/Configure.hs 691
-        bi = allBuildInfo pkg
+              cppArgs = "-c":commonCppArgs -- don't try to link
+
+        findMissingLibs = ifBuildsWith [] (makeLdArgs allLibs)
+                                       (return [])
+                                       (filterM (fmap not . libExists) allLibs)
+                       
+        libExists lib = builds (makeProgram []) (makeLdArgs [lib])
+
+        commonCppArgs = [ "-I" ++ dir | dir <- collectField PD.includeDirs ]
+        commonLdArgs  = [ "-L" ++ dir | dir <- collectField PD.extraLibDirs ]
+        
+        makeLdArgs libs = [ "-l"++lib | lib <- libs ] ++ commonLdArgs
+
+        makeProgram hdrs = unlines $
+                           [ "#include \""  ++ hdr ++ "\"" | hdr <- hdrs ] ++
+                           ["int main(int argc, char** argv) { return 0; }"]
+        
hunk ./Distribution/Simple/Configure.hs 709
+            where bi = allBuildInfo pkg
hunk ./Distribution/Simple/Configure.hs 711
-        compilesAndLinks args program = do
+        builds program args = do
hunk ./Distribution/Simple/Configure.hs 725
-        explainErrors hdrs libs = do
-            mapM_ (warn verbosity) $ map ("Required C header not found: " ++) hdrs
+        explainErrors hdr libs = do
+            case hdr of
+              Just h -> warn verbosity $ "Required C header not found: " ++ h
+              _      -> return ()
}

Context:

[Misc minor comment and help message changes
Duncan Coutts <[email protected]>**20090129233455] 
[Deprecate smartCopySources and copyDirectoryRecursiveVerbose
Duncan Coutts <[email protected]>**20090129233234
 Also use simplified implementation in terms of recently added functions.
] 
[Switch copyFileVerbose to use compat copyFile
Duncan Coutts <[email protected]>**20090129233125
 All remaining uses of it do not require copying permissions
] 
[Let the setFileExecutable function work with hugs too
Duncan Coutts <[email protected]>**20090129232948] 
[Switch hugs wrapper code to use setFileExecutable
Duncan Coutts <[email protected]>**20090129232542
 instead of get/setPermissions which don't really work properly.
] 
[Switch last uses of copyFile to copyFileVerbose
Duncan Coutts <[email protected]>**20090129232429] 
[Stop using smartCopySources or copyDirectoryRecursiveVerbose
Duncan Coutts <[email protected]>**20090129231656
 Instead if copyDirectoryRecursiveVerbose use installDirectoryContents
 and for smartCopySources use findModuleFiles and installExecutableFiles
 In both cases the point is so that we use functions for installing
 files rather than functions to copy files.
] 
[Use installOrdinaryFile and installExecutableFile in various places
Duncan Coutts <[email protected]>**20090129231321
 instead of copyFileVerbose
] 
[Make the Compat.CopyFile module with with old and new ghc
Duncan Coutts <[email protected]>**20090129225423] 
[Add a bunch of utility functions for installing files
Duncan Coutts <[email protected]>**20090129180243
 We want to separate the functions that do ordinary file copies
 from the functions that install files because in the latter
 case we have to do funky things with file permissions.
] 
[Use setFileExecutable instead of copyPermissions
Duncan Coutts <[email protected]>**20090129180130
 This lets us get rid of the Compat.Permissions module
] 
[Export setFileOrdinary and setFileExecutable from Compat.CopyFile
Duncan Coutts <[email protected]>**20090129173413] 
[Pass include directories to LHC
Samuel Bronson <[email protected]>**20090127220021] 
[Add Distribution.Compat.CopyFile module
Duncan Coutts <[email protected]>**20090128181115
 This is to work around the file permissions problems with the
 standard System.Directory.copyFile function. When installing
 files we do not want to copy permissions or attributes from the
 source files. On unix we want to use specific permissions and
 on windows we want to inherit default permissions. On unix:
 copyOrdinaryFile   sets the permissions to -rw-r--r--
 copyExecutableFile sets the permissions to -rwxr-xr-x
] 
[Remove unused support for installing dynamic exe files
Duncan Coutts <[email protected]>**20090128170421
 No idea why this was ever added, they've never been built.
] 
[Check for ghc-options: -threaded in libraries
Duncan Coutts <[email protected]>**20090125161226
 It's totally unnecessary and messes up profiling in older ghc versions.
] 
[Filter ghc-options -threaded for libs too
Duncan Coutts <[email protected]>**20090125145035] 
[New changelog entries for 1.7.x
Duncan Coutts <[email protected]>**20090123175645] 
[Update changelog for 1.6.0.2
Duncan Coutts <[email protected]>**20090123175629] 
[Fix openNewBinaryFile on Windows with ghc-6.6
Duncan Coutts <[email protected]>**20090122172100
 fdToHandle calls fdGetMode which does not work with ghc-6.6 on
 windows, the workaround is not to call fdToHandle, but call
 openFd directly. Bug reported by Alistair Bayley, ticket #473.
] 
[Warn if C dependencies not found (kind of fixes #262)
[email protected]**20090126185832
 
 This is just a basic check - generate a sample program and check if it compiles and links with relevant flags. Error messages (warning messages, 
 actually) could use some improvement.
] 
[filter -threaded when profiling is on
Duncan Coutts <[email protected]>**20090122014425
 Fixes #317. Based on a patch by [email protected]
] 
[Move installDataFiles out of line to match installIncludeFiles
Duncan Coutts <[email protected]>**20090122005318] 
[Fix installIncludeFiles to create target directories properly
Duncan Coutts <[email protected]>**20090122004836
 Previously for 'install-includes: subdir/blah.h' we would not
 create the subdir in the target location.
] 
[Typo in docs for source-repository
Joachim Breitner <[email protected]>**20090121220747] 
[Make 'ghc-options: -O0' a warning rather than an error
Duncan Coutts <[email protected]>**20090118141949] 
[Improve runE parse error message
Duncan Coutts <[email protected]>**20090116133214
 Only really used in parsing config files derived from command line flags.
] 
[The Read instance for License and InstalledPackageInfo is authoritative
Duncan Coutts <[email protected]>**20090113234229
 It is ghc's optimised InstalledPackageInfo parser that needs updating.
 
 rolling back:
 
 Fri Dec 12 18:36:22 GMT 2008  Ian Lynagh <[email protected]>
   * Fix Show/Read for License
   We were ending up with things like
       InstalledPackageInfo {
           ...
           license = LGPL Nothing,
           ...
       }
   i.e. "LGPL Nothing" rather than "LGPL", which we couldn't then read.
 
     M ./Distribution/License.hs -2 +14
] 
[Swap the order of global usage messages
Duncan Coutts <[email protected]>**20090113191810
 Put the more important one first.
] 
[Enable the global command usage to be set
Duncan Coutts <[email protected]>**20090113181303
 extend it rather than overriding it.
 Also rearrange slightly the default global --help output.
] 
[On Windows, if gcc isn't where we expect it then keep looking
Ian Lynagh <[email protected]>**20090109153507] 
[Ban ghc-options: --make
Duncan Coutts <[email protected]>**20081223170621
 I dunno, some people...
] 
[Update changelog for 1.6.0.2 release
Duncan Coutts <[email protected]>**20081211142202] 
[Make the compiler PackageDB stuff more flexible
Duncan Coutts <[email protected]>**20081211141649
 We support using multiple package dbs, however the method for
 specifying them is very limited. We specify a single package db
 and that implicitly specifies any other needed dbs. For example
 the user or a specific db require the global db too. We now
 represent that stack explicitly. The user interface still uses
 the single value method and we convert internally.
] 
[Fix Show/Read for License
Ian Lynagh <[email protected]>**20081212183622
 We were ending up with things like
     InstalledPackageInfo {
         ...
         license = LGPL Nothing,
         ...
     }
 i.e. "LGPL Nothing" rather than "LGPL", which we couldn't then read.
] 
[Un-deprecate Distribution.ModuleName.simple for now
Ian Lynagh <[email protected]>**20081212164540
 Distribution/Simple/PreProcess.hs uses it, so this causes build failures
 with -Werror.
] 
[Use the first three lhc version digits
Duncan Coutts <[email protected]>**20081211224048
 Rather than two, and do it in a simpler way.
] 
[Remove obsolete test code
Duncan Coutts <[email protected]>**20081211142054] 
[Update the VersionInterval properties which now all pass
Duncan Coutts <[email protected]>**20081210145653] 
[Eliminate NoLowerBound, Versions do have a lower bound of 0.
Duncan Coutts <[email protected]>**20081210145433
 This eliminates the duplicate representation of ">= 0" vs "-any"
 and makes VersionIntervals properly canonical.
] 
[Update and extend the Version quickcheck properties
Duncan Coutts <[email protected]>**20081210143251
 One property fails. The failure reveals that the VersionInterval type
 is not quite a canonical representation of the VersionRange semantics.
 This is because the lowest Version is [0] and not -infinity, so for
 example the intervals (.., 0] and [0,0] are equivalent.
] 
[Add documentation for VersionRange functions
Duncan Coutts <[email protected]>**20081210140632
 With properties.
] 
[Export withinVersion and deprecate betweenVersionsInclusive
Duncan Coutts <[email protected]>**20081210140411] 
[Add checking of Version validity to the VersionIntervals invariant
Duncan Coutts <[email protected]>**20081210134100
 Version numbers have to be a non-empty sequence of non-negataive ints.
] 
[Fix implementation of withinIntervals
Duncan Coutts <[email protected]>**20081210000141] 
[Fix configCompilerAux to consider user-supplied program flags
Duncan Coutts <[email protected]>**20081209193320
 This fixes a bug in cabal-install
] 
[Add ModuleName.fromString and deprecate ModuleName.simple
Duncan Coutts <[email protected]>**20081209151232
 Also document the functions in the ModuleName module.
] 
[Check for absolute, outside-of-tree and dist/ paths
Duncan Coutts <[email protected]>**20081208234312] 
[Export more VersionIntervals operations
Duncan Coutts <[email protected]>**20081208222420
 and check internal invariants
] 
[Check for use of cc-options: -O
Duncan Coutts <[email protected]>**20081208182047] 
[Fake support for NamedFieldPuns in ghc-6.8
Duncan Coutts <[email protected]>**20081208180018
 Implement it in terms of the -XRecordPuns which was accidentally
 added in ghc-6.8 and deprecates in 6.10 in favor of NamedFieldPuns
 So this is for compatability so we can tell package authors always
 to use NamedFieldPuns instead.
] 
[Make getting ghc supported language extensions its own function
Duncan Coutts <[email protected]>**20081208175815] 
[Check for use of deprecated extensions
Duncan Coutts <[email protected]>**20081208175441] 
[Add a list of deprecated extenstions
Duncan Coutts <[email protected]>**20081208175337
 Along with possibly another extension that replaces it.
] 
[Change the checking of new language extensions
Duncan Coutts <[email protected]>**20081207202315
 Check for new language extensions added in Cabal-1.2 and also 1.6.
 Simplify the checking of -X ghc flags. Now always suggest using
 the extensions field, as we separately warn about new extenssons.
] 
[Tweak docs for VersionRange and VersionIntervals
Duncan Coutts <[email protected]>**20081207184749] 
[Correct and simplify checkVersion
Duncan Coutts <[email protected]>**20081205232845] 
[Make users of VersionIntervals use the new view function
Duncan Coutts <[email protected]>**20081205232707] 
[Make VersionIntervals an abstract type
Duncan Coutts <[email protected]>**20081205232041
 Provide asVersionIntervals as the view function for a VersionRange
 This will let us enforce the internal data invariant
] 
[Slight clarity improvement in compiler language extension handling
Duncan Coutts <[email protected]>**20081205210747] 
[Slightly simplify the maintenance burden of adding new language extensions
Duncan Coutts <[email protected]>**20081205210543] 
[Distributing a package with no synopsis and no description is inexcusable
Duncan Coutts <[email protected]>**20081205160719
 Previously if one or the other or both were missing we only warned.
 Now if neither are given it's an error. We still warn about either
 missing.
] 
[Add Test.Laws module for checking class laws
Duncan Coutts <[email protected]>**20081204144238
 For Functor, Monoid and Traversable.
] 
[Add QC Arbitrary instances for Version and VersionRange
Duncan Coutts <[email protected]>**20081204144204] 
[Remove accidentally added bianry file
Duncan Coutts <[email protected]>**20081203000824] 
[Fix #396 and add let .Haddock find autogen modules
Andrea Vezzosi <[email protected]>**20081201114853] 
[Add checks for new and unknown licenses
Duncan Coutts <[email protected]>**20081202172742] 
[Add MIT and versioned GPL and LGPL licenses
Duncan Coutts <[email protected]>**20081202171033
 Since Cabal-1.4 we've been able to parse versioned licenses
 and unknown licenses without the parser falling over.
] 
[Don't nub lists of dependencies
Duncan Coutts <[email protected]>**20081202162259
 It's pretty meaningless since it's only a syntactic check.
 The proper thing is to maintain a dependency set or to
 simplify dependencies before printing them.
] 
[Fix the date in the LICENSE file
Duncan Coutts <[email protected]>**20081202161457] 
[Fix the version number in the makefile
Duncan Coutts <[email protected]>**20081202161441] 
[Use VersionRange abstractly
Duncan Coutts <[email protected]>**20081202160321] 
[Do the cabal version check properly.
Duncan Coutts <[email protected]>**20081202155410
 Instead of matching on the actual expression ">= x.y" we use the
 sematic view of the version range so we can do it precisely.
 Also use foldVersionRange to simplify a couple functions.
] 
[Drop support for ghc-6.4 era OPTIONS pragmas
Duncan Coutts <[email protected]>**20081202154744
 It's still possible to build with ghc-6.4 but you have to pass
 extra flags like "ghc --make -cpp -fffi Setup.hs" We could not
 keep those OPTIONS pragmas and make it warning-free with ghc-6.10.
 See http://hackage.haskell.org/trac/ghc/ticket/2800 for details.
] 
[Almost make the VersionRange type abstract
Duncan Coutts <[email protected]>**20081202154307
 Export constructor functions and deprecate all the real constructors
 We should not be pattern matching on this type because it's just
 syntax. For meaningful questions we should be matching on the
 VersionIntervals type which represents the semantics.
] 
[Change isAnyVersion to be a semantic rather than syntactic test
Duncan Coutts <[email protected]>**20081202142123
 Also add simplify and isNoVersion.
] 
[Add VersionIntervals, a view of VersionRange
Duncan Coutts <[email protected]>**20081202141040
 as a sequence of non-overlapping intervals. This provides a canonical
 representation for the semantics of a VersionRange. This makes several
 operations easier.
] 
[Fix pretty-printing of version wildcards, was missing leading ==
Duncan Coutts <[email protected]>**20081202135949] 
[Add a fold function for the VersionRange
Duncan Coutts <[email protected]>**20081202135845
 Use it to simplify the eval / withinRange function
] 
[Improve the error on invalid file globs slightly
Duncan Coutts <[email protected]>**20081202135335] 
[Use commaSep everywhere in the Check module
Duncan Coutts <[email protected]>**20081202135208] 
[Fix message in the extra-source-files field check
Duncan Coutts <[email protected]>**20081202135000] 
[Add checks for file glob syntax
Duncan Coutts <[email protected]>**20081202133954
 It requires cabal-version: >= 1.6 to be specified
] 
[Add check for use of "build-depends: foo == 1.*" syntax
Duncan Coutts <[email protected]>**20081202131459
 It requires Cabal-1.6 or later.
] 
[Distinguish version wild cards in the VersionRange AST
Duncan Coutts <[email protected]>**20081128170513
 Rather than encoding them in existing constructors.
 This will enable us to check that uses of the new syntax
 are flagged in .cabal files with cabal-version: >= 1.6
] 
[Fix comment in LHC module
Duncan Coutts <[email protected]>**20081123100710
 Yes, LHC really does use ghc-pkg (with a different package.conf)
] 
[Use the new bug-reports and source-repository info in the .cabal file
Duncan Coutts <[email protected]>**20081123100041] 
[Simplify build-depends and base3/4 flags
Duncan Coutts <[email protected]>**20081123100003] 
[Simplify default global libdir for LHC
Duncan Coutts <[email protected]>**20081123095802
 So it uses libdir=$prefix/lib rather than libdir=/usr/local/lib
] 
[Simplify the compat exceptions stuff
Duncan Coutts <[email protected]>**20081123095737] 
[Fix warnings in the LHC module
Duncan Coutts <[email protected]>**20081122224011] 
[Distribution/Simple/GHC.hs: remove tabs for whitespace to eliminate warnings in cabal-install
[email protected]**20081122190011
 Ignore-this: 2fd54090af86e67e25e51ade42992b53
] 
[Warn about use of tabs
Duncan Coutts <[email protected]>**20081122154134] 
[Bump Cabal HEAD version to 1.7.x development series
Duncan Coutts <[email protected]>**20081122145817
 Support for LHC is the first divergence between 1.7
 and the stable 1.6.x series.
] 
[Update changelog for 1.6.0.x fixes
Duncan Coutts <[email protected]>**20081122145758] 
[LHC: Don't use --no-user-package-conf. It doesn't work with ghc-6.8.
Lemmih <[email protected]>**20081122012341
 Ignore-this: 88a837b38cf3e897cc5ed4bb22046cee
] 
[Semi-decent lhc support.
Lemmih <[email protected]>**20081121034138] 
[Make auto-generated *_paths.hs module warning-free.
Thomas Schilling <[email protected]>**20081106142734
 
 On newer GHCs using {-# OPTIONS_GHC -fffi #-} gives a warning which
 can lead to a compile failure when -Werror is activated.  We therefore
 emit this option if we know that the LANGUAGE pragma is supported 
 (ghc >= 6.6.1).
] 
[Escape ld-options with the -optl prefix when passing them to ghc
Duncan Coutts <[email protected]>**20081103151931
 Fixes ticket #389
] 
[Simplify previous pkg-config fix
Duncan Coutts <[email protected]>**20081101200309] 
[Fix bug where we'd try to configure an empty set of pkg-config packages
Duncan Coutts <[email protected]>**20081101195512
 This happened when the lib used pkg-config but the exe did not.
 It cropped up in hsSqlite3-0.0.5.
] 
[Add GHC 6.10.1's extensions to the list in Language.Haskell.Extension
Ian Lynagh <[email protected]>**20081019141408] 
[Ensure that the lib target directory is present when installing
Duncan Coutts <[email protected]>**20081017004437
 Variant on a patch from Bryan O'Sullivan
] 
[Release kind is now rc
Duncan Coutts <[email protected]>**20081011183201] 
[TAG 1.6.0.1
Duncan Coutts <[email protected]>**20081011182516] 
Patch bundle hash:
3adb5aa35f67dcc2a387e3049c8d886adec9fc9a
_______________________________________________
cabal-devel mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cabal-devel

Reply via email to