diff --git a/.travis.yml b/.travis.yml index 08553f7f332b8aa32515c6f7f9c7a66a69fdb3e6..6094489713d096f4cb01c15e36ea715cff94e122 100644 --- a/.travis.yml +++ b/.travis.yml @@ -17,6 +17,7 @@ before_install: install: - sudo /opt/ghc/$GHCVER/bin/ghc-pkg recache + - /opt/ghc/$GHCVER/bin/ghc-pkg recache --user - cabal-1.18 update - cd Cabal - cabal-1.18 install --only-dependencies --enable-tests --enable-benchmarks diff --git a/Cabal/Cabal.cabal b/Cabal/Cabal.cabal index d01caf5e758574e334f9e026c80f0f738ad1721c..38e6c88bebca370e40d1a102c22aee235ac5717c 100644 --- a/Cabal/Cabal.cabal +++ b/Cabal/Cabal.cabal @@ -137,6 +137,7 @@ library ghc-options: -Wall -fno-ignore-asserts -fwarn-tabs exposed-modules: + Distribution.Compat.CreatePipe Distribution.Compat.Environment Distribution.Compat.Exception Distribution.Compat.ReadP @@ -196,6 +197,9 @@ library Distribution.Simple.Setup Distribution.Simple.SrcDist Distribution.Simple.Test + Distribution.Simple.Test.ExeV10 + Distribution.Simple.Test.LibV09 + Distribution.Simple.Test.Log Distribution.Simple.UHC Distribution.Simple.UserHooks Distribution.Simple.Utils @@ -239,7 +243,6 @@ test-suite package-tests type: exitcode-stdio-1.0 main-is: PackageTests.hs other-modules: - Distribution.Compat.CreatePipe PackageTests.BenchmarkExeV10.Check PackageTests.BenchmarkOptions.Check PackageTests.BenchmarkStanza.Check diff --git a/Cabal/Distribution/Compat/CreatePipe.hs b/Cabal/Distribution/Compat/CreatePipe.hs new file mode 100644 index 0000000000000000000000000000000000000000..bbaf14f6e59f7787e8ff8644ff94c20931e0a9eb --- /dev/null +++ b/Cabal/Distribution/Compat/CreatePipe.hs @@ -0,0 +1,75 @@ +{-# LANGUAGE CPP, ForeignFunctionInterface #-} +module Distribution.Compat.CreatePipe (createPipe, tee) where + +import Control.Concurrent (forkIO) +import Control.Monad (forM_, when) +import System.IO (Handle, hClose, hGetContents, hPutStr) + +-- The mingw32_HOST_OS CPP macro is GHC-specific +#if mingw32_HOST_OS +import Control.Exception (onException) +import Foreign.C.Error (throwErrnoIfMinus1_) +import Foreign.C.Types (CInt(..), CUInt(..)) +import Foreign.Ptr (Ptr) +import Foreign.Marshal.Array (allocaArray) +import Foreign.Storable (peek, peekElemOff) +import GHC.IO.FD (mkFD) +import GHC.IO.Device (IODeviceType(Stream)) +import GHC.IO.Handle.FD (mkHandleFromFD) +import System.IO (IOMode(ReadMode, WriteMode)) +#else +import System.Posix.IO (fdToHandle) +import qualified System.Posix.IO as Posix +#endif + +createPipe :: IO (Handle, Handle) +-- The mingw32_HOST_OS CPP macro is GHC-specific +#if mingw32_HOST_OS +createPipe = do + (readfd, writefd) <- allocaArray 2 $ \ pfds -> do + throwErrnoIfMinus1_ "_pipe" $ c__pipe pfds 2 ({- _O_BINARY -} 32768) + readfd <- peek pfds + writefd <- peekElemOff pfds 1 + return (readfd, writefd) + (do readh <- fdToHandle readfd ReadMode + writeh <- fdToHandle writefd WriteMode + return (readh, writeh)) `onException` (close readfd >> close writefd) + where + fdToHandle :: CInt -> IOMode -> IO Handle + fdToHandle fd mode = do + (fd', deviceType) <- mkFD fd mode (Just (Stream, 0, 0)) False False + mkHandleFromFD fd' deviceType "" mode False Nothing + + close :: CInt -> IO () + close = throwErrnoIfMinus1_ "_close" . c__close + +foreign import ccall "io.h _pipe" c__pipe :: + Ptr CInt -> CUInt -> CInt -> IO CInt + +foreign import ccall "io.h _close" c__close :: + CInt -> IO CInt +#else +createPipe = do + (readfd, writefd) <- Posix.createPipe + readh <- fdToHandle readfd + writeh <- fdToHandle writefd + return (readh, writeh) +#endif + +-- | Copy the contents of the input handle to the output handles, like +-- the Unix command. The input handle is processed in another thread until +-- EOF is reached; 'tee' returns immediately. The 'Bool' with each output +-- handle indicates if it should be closed when EOF is reached. +-- Synchronization can be achieved by blocking on an output handle. +tee :: Handle -- ^ input + -> [(Handle, Bool)] -- ^ output, close? + -> IO () +tee inH outHs = do + -- 'hGetContents' might cause text decoding errors on binary streams that + -- are not text. It might be better to read into a buffer with 'hGetBuf' + -- that does no text decoding, but that seems to block all threads on + -- Windows. This is much simpler. + str <- hGetContents inH + forM_ outHs $ \(h, close) -> forkIO $ do + hPutStr h str + when close $ hClose h diff --git a/Cabal/Distribution/Compiler.hs b/Cabal/Distribution/Compiler.hs index b2f07eb60487dd93af5c1bd9906d4ee2a1e9e284..16e09ef696b0d9f3eb6cee994cf438b2454bf2bd 100644 --- a/Cabal/Distribution/Compiler.hs +++ b/Cabal/Distribution/Compiler.hs @@ -3,6 +3,7 @@ -- | -- Module : Distribution.Compiler -- Copyright : Isaac Jones 2003-2004 +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Portability : portable @@ -22,36 +23,6 @@ -- moment we just have to live with this deficiency. If you're interested, see -- ticket #57. -{- All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - module Distribution.Compiler ( -- * Compiler flavor CompilerFlavor(..), diff --git a/Cabal/Distribution/License.hs b/Cabal/Distribution/License.hs index d2ed2a9e89acded832b2624295fb13e003a7c9e9..ff9a6bd0a8f7eed9c8fb4a67e25fc6a6dd57a0ee 100644 --- a/Cabal/Distribution/License.hs +++ b/Cabal/Distribution/License.hs @@ -3,6 +3,7 @@ -- | -- Module : Distribution.License -- Copyright : Isaac Jones 2003-2005 +-- License : BSD3 -- Duncan Coutts 2008 -- -- Maintainer : cabal-devel@haskell.org @@ -18,36 +19,6 @@ -- the @.cabal@ file from a short enumeration defined in this module. It -- includes 'GPL', 'AGPL', 'LGPL', 'Apache 2.0', 'MIT' and 'BSD3' licenses. -{- All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - module Distribution.License ( License(..), knownLicenses, diff --git a/Cabal/Distribution/Make.hs b/Cabal/Distribution/Make.hs index 1bab50954c3dfb5de084f977dd25935e0588caf4..7402cad7bdd7e251af7ae00a2f94f04b1a3d0382 100644 --- a/Cabal/Distribution/Make.hs +++ b/Cabal/Distribution/Make.hs @@ -2,6 +2,7 @@ -- | -- Module : Distribution.Make -- Copyright : Martin Sjögren 2004 +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Portability : portable @@ -53,36 +54,6 @@ -- $(MAKE) install prefix=$(destdir)/$(prefix) \ -- bindir=$(destdir)/$(bindir) \ -{- All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - module Distribution.Make ( module Distribution.Package, License(..), Version(..), diff --git a/Cabal/Distribution/ModuleName.hs b/Cabal/Distribution/ModuleName.hs index 45babdad2b9191910a842b19229449e747eb31d0..3f938c316565251e2cac1475fb6b1a9d98bc41a4 100644 --- a/Cabal/Distribution/ModuleName.hs +++ b/Cabal/Distribution/ModuleName.hs @@ -3,42 +3,13 @@ -- | -- Module : Distribution.ModuleName -- Copyright : Duncan Coutts 2008 +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Portability : portable -- -- Data type for Haskell module names. -{- All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - module Distribution.ModuleName ( ModuleName, fromString, diff --git a/Cabal/Distribution/Package.hs b/Cabal/Distribution/Package.hs index b561bf5f3077dc5acc1e73a91230132b82408efc..263136800b585968fcc1ad67447daa0ecb5c7a86 100644 --- a/Cabal/Distribution/Package.hs +++ b/Cabal/Distribution/Package.hs @@ -3,6 +3,7 @@ -- | -- Module : Distribution.Package -- Copyright : Isaac Jones 2003-2004 +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Portability : portable @@ -12,36 +13,6 @@ -- a 'Dependency' data type. A dependency is a package name and a version -- range, like @\"foo >= 1.2 && < 2\"@. -{- All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - module Distribution.Package ( -- * Package ids PackageName(..), diff --git a/Cabal/Distribution/PackageDescription.hs b/Cabal/Distribution/PackageDescription.hs index f21da493369f4e030edd2faf6bdbebf72d611ec8..3d873210c3748a158dd10d14758393551a9229cc 100644 --- a/Cabal/Distribution/PackageDescription.hs +++ b/Cabal/Distribution/PackageDescription.hs @@ -3,6 +3,7 @@ -- | -- Module : Distribution.PackageDescription -- Copyright : Isaac Jones 2003-2005 +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Portability : portable @@ -21,36 +22,6 @@ -- feature was introduced. It could probably do with being rationalised at some -- point to make it simpler. -{- All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - module Distribution.PackageDescription ( -- * Package descriptions PackageDescription(..), diff --git a/Cabal/Distribution/PackageDescription/Check.hs b/Cabal/Distribution/PackageDescription/Check.hs index 33a8b2f6441b7fbe357732760f7caad0b509e966..1a9f30fbf13678e6eebb399105c59843fd05c55e 100644 --- a/Cabal/Distribution/PackageDescription/Check.hs +++ b/Cabal/Distribution/PackageDescription/Check.hs @@ -2,6 +2,7 @@ -- | -- Module : Distribution.PackageDescription.Check -- Copyright : Lennart Kolmodin 2008 +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Portability : portable @@ -19,36 +20,6 @@ -- distributed to a higher standard than packages that are only ever expected -- to be used on the author's own environment. -{- All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - module Distribution.PackageDescription.Check ( -- * Package Checking PackageCheck(..), diff --git a/Cabal/Distribution/PackageDescription/Configuration.hs b/Cabal/Distribution/PackageDescription/Configuration.hs index 496d701df5d8be63282661062f81f838e79a5028..40d2c50c0ecc77511ea1dda7891ced63fdba0b56 100644 --- a/Cabal/Distribution/PackageDescription/Configuration.hs +++ b/Cabal/Distribution/PackageDescription/Configuration.hs @@ -4,6 +4,7 @@ -- | -- Module : Distribution.PackageDescription.Configuration -- Copyright : Thomas Schilling, 2007 +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Portability : portable @@ -14,36 +15,6 @@ -- 'PackageDescription's. It has code for working with the tree of conditions -- and resolving or flattening conditions. -{- All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - module Distribution.PackageDescription.Configuration ( finalizePackageDescription, flattenPackageDescription, diff --git a/Cabal/Distribution/PackageDescription/Parse.hs b/Cabal/Distribution/PackageDescription/Parse.hs index 85a686ad61cec7efeedf373d4f90156cba2756e7..0b7b6e1b013a95a56b8cb2e9d8be152f212471c8 100644 --- a/Cabal/Distribution/PackageDescription/Parse.hs +++ b/Cabal/Distribution/PackageDescription/Parse.hs @@ -2,6 +2,7 @@ -- | -- Module : Distribution.PackageDescription.Parse -- Copyright : Isaac Jones 2003-2005 +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Portability : portable @@ -11,36 +12,6 @@ -- backwards compatible with old @.cabal@ files, so there's code to translate -- into the newer structure. -{- All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - module Distribution.PackageDescription.Parse ( -- * Package descriptions readPackageDescription, @@ -1029,8 +1000,14 @@ parsePackageDescription file = do let simplFlds = [ F l n v | F l n v <- allflds ] condFlds = [ f | f@IfBlock{} <- allflds ] + sections = [ s | s@Section{} <- allflds ] let (depFlds, dataFlds) = partition isConstraint simplFlds + + mapM_ + (\(Section l n _ _) -> lift . warning $ + "Unexpected section '" ++ n ++ "' on line " ++ show l) + sections a <- parser dataFlds deps <- liftM concat . mapM (lift . parseConstraint) $ depFlds diff --git a/Cabal/Distribution/PackageDescription/PrettyPrint.hs b/Cabal/Distribution/PackageDescription/PrettyPrint.hs index 7c4008f6e66bbb4a28220290f1318c57e7781b32..8eba6898021d0ab55d664390b7c428837950ba55 100644 --- a/Cabal/Distribution/PackageDescription/PrettyPrint.hs +++ b/Cabal/Distribution/PackageDescription/PrettyPrint.hs @@ -2,7 +2,7 @@ -- -- Module : Distribution.PackageDescription.PrettyPrint -- Copyright : Jürgen Nicklisch-Franken 2010 --- License : AllRightsReserved +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Stability : provisional @@ -11,35 +11,6 @@ -- | Pretty printing for cabal files -- ----------------------------------------------------------------------------- -{- All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} module Distribution.PackageDescription.PrettyPrint ( writeGenericPackageDescription, diff --git a/Cabal/Distribution/ParseUtils.hs b/Cabal/Distribution/ParseUtils.hs index e4b039e34af719af0f6d755cadac9985fc062552..956a8492527842c2d6fb96a441bb6baf771dc977 100644 --- a/Cabal/Distribution/ParseUtils.hs +++ b/Cabal/Distribution/ParseUtils.hs @@ -2,6 +2,7 @@ -- | -- Module : Distribution.ParseUtils -- Copyright : (c) The University of Glasgow 2004 +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Portability : portable @@ -15,36 +16,6 @@ -- many of the formats we get in various @.cabal@ file fields, like module -- names, comma separated lists etc. -{- All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of the University nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - -- This module is meant to be local-only to Distribution... {-# OPTIONS_HADDOCK hide #-} @@ -62,7 +33,7 @@ module Distribution.ParseUtils ( parseSepList, parseCommaList, parseOptCommaList, showFilePath, showToken, showTestedWith, showFreeText, parseFreeText, field, simpleField, simpleNestedField, listField, spaceListField, commaListField, - optsField, liftField, boolField, parseQuoted, indentWith, + commaNewLineListField, optsField, liftField, boolField, parseQuoted, indentWith, UnrecFieldParser, warnUnrec, ignoreUnrec, ) where @@ -222,14 +193,22 @@ simpleNestedField :: String -> (a -> Doc) -> ReadP a a simpleNestedField name showF readF get set = liftField get set $ field name (showNestedField name showF) readF -commaListField :: String -> (a -> Doc) -> ReadP [a] a +commaListField' :: ([Doc] -> Doc) -> String -> (a -> Doc) -> ReadP [a] a -> (b -> [a]) -> ([a] -> b -> b) -> FieldDescr b -commaListField name showF readF get set = +commaListField' separator name showF readF get set = liftField get set' $ field name (showNestedField name showF') (parseCommaList readF) where set' xs b = set (get b ++ xs) b - showF' = vcat . punctuate comma . map showF + showF' = separator . punctuate comma . map showF + +commaListField :: String -> (a -> Doc) -> ReadP [a] a + -> (b -> [a]) -> ([a] -> b -> b) -> FieldDescr b +commaListField = commaListField' fsep + +commaNewLineListField :: String -> (a -> Doc) -> ReadP [a] a + -> (b -> [a]) -> ([a] -> b -> b) -> FieldDescr b +commaNewLineListField = commaListField' sep spaceListField :: String -> (a -> Doc) -> ReadP [a] a -> (b -> [a]) -> ([a] -> b -> b) -> FieldDescr b diff --git a/Cabal/Distribution/ReadE.hs b/Cabal/Distribution/ReadE.hs index 07b2568fe3368b2746ee81dd63ca6d2f784e44cf..b639f814c2a808cc6c7ed76f8291ff3ea4dee1b6 100644 --- a/Cabal/Distribution/ReadE.hs +++ b/Cabal/Distribution/ReadE.hs @@ -2,43 +2,13 @@ -- | -- Module : Distribution.ReadE -- Copyright : Jose Iborra 2008 +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Portability : portable -- -- Simple parsing with failure -{- Copyright (c) 2007, Jose Iborra -All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - module Distribution.ReadE ( -- * ReadE ReadE(..), succeedReadE, failReadE, diff --git a/Cabal/Distribution/Simple.hs b/Cabal/Distribution/Simple.hs index 9d8a65b927c3c5047fcb4415c5d2253ec129b4fb..80cc8ae80fef1491714961e8495022686e8c8da4 100644 --- a/Cabal/Distribution/Simple.hs +++ b/Cabal/Distribution/Simple.hs @@ -2,6 +2,7 @@ -- | -- Module : Distribution.Simple -- Copyright : Isaac Jones 2003-2005 +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Portability : portable @@ -24,36 +25,6 @@ -- presented the same compatible command line interfaces. There is still a -- "Distribution.Make" system but in practice no packages use it. -{- All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - {- Work around this warning: libraries/Cabal/Distribution/Simple.hs:78:0: diff --git a/Cabal/Distribution/Simple/Bench.hs b/Cabal/Distribution/Simple/Bench.hs index ad801ff46a88d3abe6ac2b03c138dc4c76c2fdd4..8aac02a627242c56b9c9d08a59f085379a2b40b7 100644 --- a/Cabal/Distribution/Simple/Bench.hs +++ b/Cabal/Distribution/Simple/Bench.hs @@ -2,6 +2,7 @@ -- | -- Module : Distribution.Simple.Bench -- Copyright : Johan Tibell 2011 +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Portability : portable @@ -10,36 +11,6 @@ -- package. It performs the \"@.\/setup bench@\" action. It runs -- benchmarks designated in the package description. -{- All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - module Distribution.Simple.Bench ( bench ) where diff --git a/Cabal/Distribution/Simple/Build.hs b/Cabal/Distribution/Simple/Build.hs index 627848bf72e403069d28e4dd0345cbe62c95161c..c3a65fbc5003e22a4f3c73a349494a761f7ab266 100644 --- a/Cabal/Distribution/Simple/Build.hs +++ b/Cabal/Distribution/Simple/Build.hs @@ -4,6 +4,7 @@ -- Copyright : Isaac Jones 2003-2005, -- Ross Paterson 2006, -- Duncan Coutts 2007-2008, 2012 +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Portability : portable @@ -14,37 +15,6 @@ -- running pre-processors. -- -{- Copyright (c) 2003-2005, Isaac Jones -All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - module Distribution.Simple.Build ( build, repl, startInterpreter, @@ -98,7 +68,7 @@ import Distribution.Simple.BuildPaths ( autogenModulesDir, autogenModuleName, cppHeaderName, exeExtension ) import Distribution.Simple.Register ( registerPackage, inplaceInstalledPackageInfo ) -import Distribution.Simple.Test ( stubFilePath, stubName ) +import Distribution.Simple.Test.LibV09 ( stubFilePath, stubName ) import Distribution.Simple.Utils ( createDirectoryIfMissingVerbose, rewriteFile , die, info, debug, warn, setupMessage ) diff --git a/Cabal/Distribution/Simple/BuildPaths.hs b/Cabal/Distribution/Simple/BuildPaths.hs index d7b35bac5587238cd9ec2145d666699ac466dd7f..6d3b8f464685a184e733263651d99298e3a6c127 100644 --- a/Cabal/Distribution/Simple/BuildPaths.hs +++ b/Cabal/Distribution/Simple/BuildPaths.hs @@ -3,6 +3,7 @@ -- Module : Distribution.Simple.BuildPaths -- Copyright : Isaac Jones 2003-2004, -- Duncan Coutts 2008 +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Portability : portable @@ -10,36 +11,6 @@ -- A bunch of dirs, paths and file names used for intermediate build steps. -- -{- All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - module Distribution.Simple.BuildPaths ( defaultDistPref, srcPref, hscolourPref, haddockPref, diff --git a/Cabal/Distribution/Simple/Command.hs b/Cabal/Distribution/Simple/Command.hs index a976d9d65f9a04610e361015ad8ad6394cf4626e..3f9f61dafea32628c8c7f16e9bcf101f72dad02f 100644 --- a/Cabal/Distribution/Simple/Command.hs +++ b/Cabal/Distribution/Simple/Command.hs @@ -2,6 +2,7 @@ -- | -- Module : Distribution.Simple.Command -- Copyright : Duncan Coutts 2007 +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Portability : portable @@ -14,36 +15,6 @@ -- command line completion flags. It is designed to allow other tools make -- derived commands. This feature is used heavily in @cabal-install@. -{- All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - module Distribution.Simple.Command ( -- * Command interface diff --git a/Cabal/Distribution/Simple/Compiler.hs b/Cabal/Distribution/Simple/Compiler.hs index d053da36af25e3de867e41cfdf51b3bb7cdd3510..9e159f0cde6f583544d14e03778a9c66e18e6530 100644 --- a/Cabal/Distribution/Simple/Compiler.hs +++ b/Cabal/Distribution/Simple/Compiler.hs @@ -2,6 +2,7 @@ -- | -- Module : Distribution.Simple.Compiler -- Copyright : Isaac Jones 2003-2004 +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Portability : portable @@ -17,36 +18,6 @@ -- per-user one and it lets you create arbitrary other package databases. We do -- not yet fully support this latter feature. -{- All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - module Distribution.Simple.Compiler ( -- * Haskell implementations module Distribution.Compiler, diff --git a/Cabal/Distribution/Simple/Configure.hs b/Cabal/Distribution/Simple/Configure.hs index 807451fa72d9d2ec3e9403c8c2ef705d0c70e770..649a80d42df6ea0221aa3de7adbbc3c1f563a9e6 100644 --- a/Cabal/Distribution/Simple/Configure.hs +++ b/Cabal/Distribution/Simple/Configure.hs @@ -2,6 +2,7 @@ -- | -- Module : Distribution.Simple.Configure -- Copyright : Isaac Jones 2003-2005 +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Portability : portable @@ -20,36 +21,6 @@ -- the user, the amount of information displayed depending on the verbosity -- level. -{- All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - module Distribution.Simple.Configure (configure, writePersistBuildConfig, getPersistBuildConfig, diff --git a/Cabal/Distribution/Simple/GHC.hs b/Cabal/Distribution/Simple/GHC.hs index 3cc24e9b5633af6c451844d34f00b447fdc0f6b2..93102202c061f00508dd7f9adcd20983b2cf8d11 100644 --- a/Cabal/Distribution/Simple/GHC.hs +++ b/Cabal/Distribution/Simple/GHC.hs @@ -2,6 +2,7 @@ -- | -- Module : Distribution.Simple.GHC -- Copyright : Isaac Jones 2003-2007 +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Portability : portable @@ -29,37 +30,6 @@ -- explicitly documented) and thus what search dirs are used for various kinds -- of files. -{- Copyright (c) 2003-2005, Isaac Jones -All rights reserved. - -Redistribution and use in source and binary forms, with or without -modiication, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - module Distribution.Simple.GHC ( getGhcInfo, configure, getInstalledPackages, getPackageDBContents, diff --git a/Cabal/Distribution/Simple/GHC/IPI641.hs b/Cabal/Distribution/Simple/GHC/IPI641.hs index 222af1abb180c7311b7d2456b4c40db6779326ba..c59b23ba84c2a36eecb0955bd4e5993e21845165 100644 --- a/Cabal/Distribution/Simple/GHC/IPI641.hs +++ b/Cabal/Distribution/Simple/GHC/IPI641.hs @@ -2,41 +2,12 @@ -- | -- Module : Distribution.Simple.GHC.IPI641 -- Copyright : (c) The University of Glasgow 2004 +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Portability : portable -- -{- All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of the University nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - module Distribution.Simple.GHC.IPI641 ( InstalledPackageInfo, toCurrent, diff --git a/Cabal/Distribution/Simple/GHC/IPI642.hs b/Cabal/Distribution/Simple/GHC/IPI642.hs index b1b8bb707ada9cdce660fba157fcd1db5d383cf8..a0dd0ac3537aa85148ecb670929c8bb70f421d7b 100644 --- a/Cabal/Distribution/Simple/GHC/IPI642.hs +++ b/Cabal/Distribution/Simple/GHC/IPI642.hs @@ -2,41 +2,12 @@ -- | -- Module : Distribution.Simple.GHC.IPI642 -- Copyright : (c) The University of Glasgow 2004 +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Portability : portable -- -{- All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of the University nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - module Distribution.Simple.GHC.IPI642 ( InstalledPackageInfo, toCurrent, diff --git a/Cabal/Distribution/Simple/Haddock.hs b/Cabal/Distribution/Simple/Haddock.hs index 9727a4944477a8995135283812fc218b826cb52e..f5422aa22f0d3e4092d27299adf214e2c0a09eb1 100644 --- a/Cabal/Distribution/Simple/Haddock.hs +++ b/Cabal/Distribution/Simple/Haddock.hs @@ -2,6 +2,7 @@ -- | -- Module : Distribution.Simple.Haddock -- Copyright : Isaac Jones 2003-2005 +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Portability : portable @@ -16,36 +17,6 @@ -- The @hscolour@ support allows generating html versions of the original -- source, with coloured syntax highlighting. -{- All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - module Distribution.Simple.Haddock ( haddock, hscolour, @@ -118,7 +89,7 @@ import Data.Maybe ( fromMaybe, listToMaybe ) import System.FilePath((</>), (<.>), splitFileName, splitExtension, normalise, splitPath, joinPath, isAbsolute ) -import System.IO (hClose, hPutStrLn) +import System.IO (hClose, hPutStrLn, hSetEncoding, utf8) import Distribution.Version -- ------------------------------------------------------------------------------ @@ -130,7 +101,7 @@ data HaddockArgs = HaddockArgs { argPackageName :: Flag PackageIdentifier, -- ^ package name, required. argHideModules :: (All,[ModuleName.ModuleName]), -- ^ (hide modules ?, modules to hide) argIgnoreExports :: Any, -- ^ ingore export lists in modules? - argLinkSource :: Flag (Template,Template), -- ^ (template for modules, template for symbols) + argLinkSource :: Flag (Template,Template,Template), -- ^ (template for modules, template for symbols, template for lines) argCssFile :: Flag FilePath, -- ^ optinal custom css file. argContents :: Flag String, -- ^ optional url to contents page argVerbose :: Any, @@ -305,7 +276,8 @@ fromFlags env flags = argHideModules = (maybe mempty (All . not) $ flagToMaybe (haddockInternal flags), mempty), argLinkSource = if fromFlag (haddockHscolour flags) then Flag ("src/%{MODULE/./-}.html" - ,"src/%{MODULE/./-}.html#%{NAME}") + ,"src/%{MODULE/./-}.html#%{NAME}" + ,"src/%{MODULE/./-}.html#line-%{LINE}") else NoFlag, argCssFile = haddockCss flags, argContents = fmap (fromPathTemplate . substPathTemplate env) (haddockContents flags), @@ -480,6 +452,7 @@ renderArgs verbosity tmpFileOpts version comp args k = do createDirectoryIfMissingVerbose verbosity True outputDir withTempFileEx tmpFileOpts outputDir "haddock-prolog.txt" $ \prologFileName h -> do do + when (version >= Version [2,15] []) (hSetEncoding h utf8) hPutStrLn h $ fromFlag $ argPrologue args hClose h let pflag = "--prologue=" ++ prologFileName @@ -509,8 +482,11 @@ renderPureArgs version comp args = concat else ["--package=" ++ pname]) . display . fromFlag . argPackageName $ args, (\(All b,xs) -> bool (map (("--hide=" ++). display) xs) [] b) . argHideModules $ args, bool ["--ignore-all-exports"] [] . getAny . argIgnoreExports $ args, - maybe [] (\(m,e) -> ["--source-module=" ++ m - ,"--source-entity=" ++ e]) . flagToMaybe . argLinkSource $ args, + maybe [] (\(m,e,l) -> ["--source-module=" ++ m + ,"--source-entity=" ++ e] + ++ if isVersion2_14 then ["--source-entity-line=" ++ l] + else [] + ) . flagToMaybe . argLinkSource $ args, maybe [] ((:[]).("--css="++)) . flagToMaybe . argCssFile $ args, maybe [] ((:[]).("--use-contents="++)) . flagToMaybe . argContents $ args, bool [] [verbosityFlag] . getAny . argVerbose $ args, @@ -530,8 +506,9 @@ renderPureArgs version comp args = concat map (\(i,mh) -> "--read-interface=" ++ maybe "" (++",") mh ++ i) bool a b c = if c then a else b - isVersion2 = version >= Version [2,0] [] - isVersion2_5 = version >= Version [2,5] [] + isVersion2 = version >= Version [2,0] [] + isVersion2_5 = version >= Version [2,5] [] + isVersion2_14 = version >= Version [2,14] [] verbosityFlag | isVersion2_5 = "--verbosity=1" | otherwise = "--verbose" diff --git a/Cabal/Distribution/Simple/Hpc.hs b/Cabal/Distribution/Simple/Hpc.hs index e2f1420b1671f6ff1419ca549e9a61b3f0c3b34f..57a21ed6d7ac6f13d7a557755e1efaf3d9fa3994 100644 --- a/Cabal/Distribution/Simple/Hpc.hs +++ b/Cabal/Distribution/Simple/Hpc.hs @@ -2,6 +2,7 @@ -- | -- Module : Distribution.Simple.Hpc -- Copyright : Thomas Tuegel 2011 +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Portability : portable @@ -10,36 +11,6 @@ -- a function for adding the necessary options to a PackageDescription to -- build test suites with HPC enabled. -{- All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - module Distribution.Simple.Hpc ( enableCoverage , htmlDir diff --git a/Cabal/Distribution/Simple/Hugs.hs b/Cabal/Distribution/Simple/Hugs.hs index f63bfab3524e15e356f623bad62df7a6653e8fa6..aba3a5a3cfc20ca03e51d5bda8f3608dc360c590 100644 --- a/Cabal/Distribution/Simple/Hugs.hs +++ b/Cabal/Distribution/Simple/Hugs.hs @@ -3,6 +3,7 @@ -- Module : Distribution.Simple.Hugs -- Copyright : Isaac Jones 2003-2006 -- Duncan Coutts 2009 +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Portability : portable @@ -10,37 +11,6 @@ -- This module contains most of the NHC-specific code for configuring, building -- and installing packages. -{- Copyright (c) 2003-2005, Isaac Jones -All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - module Distribution.Simple.Hugs ( configure, getInstalledPackages, diff --git a/Cabal/Distribution/Simple/Install.hs b/Cabal/Distribution/Simple/Install.hs index 0a52e16201afed85df8506ea94f56d00ba17ff26..3efcceee0fd05014806902200a987456e4f53cbe 100644 --- a/Cabal/Distribution/Simple/Install.hs +++ b/Cabal/Distribution/Simple/Install.hs @@ -2,6 +2,7 @@ -- | -- Module : Distribution.Simple.Install -- Copyright : Isaac Jones 2003-2004 +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Portability : portable @@ -11,36 +12,6 @@ -- place based on the prefix argument. It does the generic bits and then calls -- compiler-specific functions to do the rest. -{- All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - module Distribution.Simple.Install ( install, ) where diff --git a/Cabal/Distribution/Simple/InstallDirs.hs b/Cabal/Distribution/Simple/InstallDirs.hs index 32ba7b749ebb8dd18683ad6c493baf8fe5444e91..6d1de25caadb634e9f04986f5f5eaa1bd6f89c53 100644 --- a/Cabal/Distribution/Simple/InstallDirs.hs +++ b/Cabal/Distribution/Simple/InstallDirs.hs @@ -3,6 +3,7 @@ -- | -- Module : Distribution.Simple.InstallDirs -- Copyright : Isaac Jones 2003-2004 +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Portability : portable @@ -16,36 +17,6 @@ -- provides a 'PathTemplate' type and functions for substituting for these -- templates. -{- All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - module Distribution.Simple.InstallDirs ( InstallDirs(..), InstallDirTemplates, diff --git a/Cabal/Distribution/Simple/JHC.hs b/Cabal/Distribution/Simple/JHC.hs index da978be1e0bc9f6ddb57d62acb167a470ebf0640..0d3ec509925fb1ba862fbf4bb63ff4eb5f0e6102 100644 --- a/Cabal/Distribution/Simple/JHC.hs +++ b/Cabal/Distribution/Simple/JHC.hs @@ -2,6 +2,7 @@ -- | -- Module : Distribution.Simple.JHC -- Copyright : Isaac Jones 2003-2006 +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Portability : portable @@ -9,39 +10,6 @@ -- This module contains most of the JHC-specific code for configuring, building -- and installing packages. -{- -Copyright (c) 2009, Henning Thielemann -Copyright (c) 2003-2005, Isaac Jones -All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - module Distribution.Simple.JHC ( configure, getInstalledPackages, buildLib, buildExe, diff --git a/Cabal/Distribution/Simple/LHC.hs b/Cabal/Distribution/Simple/LHC.hs index ff84672f0517cd267a6648700f73f358def24a39..3006fa73c07ff05980390684b371494bc8a1b12b 100644 --- a/Cabal/Distribution/Simple/LHC.hs +++ b/Cabal/Distribution/Simple/LHC.hs @@ -2,6 +2,7 @@ -- | -- Module : Distribution.Simple.LHC -- Copyright : Isaac Jones 2003-2007 +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Portability : portable @@ -29,37 +30,6 @@ -- explicitly documented) and thus what search dirs are used for various kinds -- of files. -{- Copyright (c) 2003-2005, Isaac Jones -All rights reserved. - -Redistribution and use in source and binary forms, with or without -modiication, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - module Distribution.Simple.LHC ( configure, getInstalledPackages, buildLib, buildExe, diff --git a/Cabal/Distribution/Simple/LocalBuildInfo.hs b/Cabal/Distribution/Simple/LocalBuildInfo.hs index ed0b8f78868416e7c0511d2cf851d9b7d9ffe404..235f456808563ccd134e7edab23c4be88551a26e 100644 --- a/Cabal/Distribution/Simple/LocalBuildInfo.hs +++ b/Cabal/Distribution/Simple/LocalBuildInfo.hs @@ -2,6 +2,7 @@ -- | -- Module : Distribution.Simple.LocalBuildInfo -- Copyright : Isaac Jones 2003-2004 +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Portability : portable @@ -14,36 +15,6 @@ -- flags. It gets saved and reloaded from a file (@dist\/setup-config@). It gets -- passed in to very many subsequent build actions. -{- All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - module Distribution.Simple.LocalBuildInfo ( LocalBuildInfo(..), externalPackageDeps, diff --git a/Cabal/Distribution/Simple/NHC.hs b/Cabal/Distribution/Simple/NHC.hs index 93a6c8a322c0743013b05d6fa7239e9737bad2ab..91de219c843bda2c6eab624c98cb1f111d3acbe0 100644 --- a/Cabal/Distribution/Simple/NHC.hs +++ b/Cabal/Distribution/Simple/NHC.hs @@ -3,6 +3,7 @@ -- Module : Distribution.Simple.NHC -- Copyright : Isaac Jones 2003-2006 -- Duncan Coutts 2009 +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Portability : portable @@ -10,37 +11,6 @@ -- This module contains most of the NHC-specific code for configuring, building -- and installing packages. -{- Copyright (c) 2003-2005, Isaac Jones -All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - module Distribution.Simple.NHC ( configure, getInstalledPackages, diff --git a/Cabal/Distribution/Simple/PreProcess.hs b/Cabal/Distribution/Simple/PreProcess.hs index e2365c656a8f1b90a0d3579fdff8642332b58d5c..21175473adf0812a81978c737f473e9a9cf74eb9 100644 --- a/Cabal/Distribution/Simple/PreProcess.hs +++ b/Cabal/Distribution/Simple/PreProcess.hs @@ -2,6 +2,7 @@ -- | -- Module : Distribution.Simple.PreProcess -- Copyright : (c) 2003-2005, Isaac Jones, Malcolm Wallace +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Portability : portable @@ -16,37 +17,6 @@ -- handlers. This module is not as good as it could be, it could really do with -- a rewrite to address some of the problems we have with pre-processors. -{- Copyright (c) 2003-2005, Isaac Jones, Malcolm Wallace -All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - module Distribution.Simple.PreProcess (preprocessComponent, knownSuffixHandlers, ppSuffixes, PPSuffixHandler, PreProcessor(..), mkSimplePreProcessor, runSimplePreProcessor, @@ -88,7 +58,8 @@ import Distribution.Simple.Program , rawSystemProgramConf, rawSystemProgram , greencardProgram, cpphsProgram, hsc2hsProgram, c2hsProgram , happyProgram, alexProgram, haddockProgram, ghcProgram, gccProgram ) -import Distribution.Simple.Test ( writeSimpleTestStub, stubFilePath, stubName ) +import Distribution.Simple.Test.LibV09 + ( writeSimpleTestStub, stubFilePath, stubName ) import Distribution.System ( OS(..), buildOS, Arch(..), Platform(..) ) import Distribution.Text diff --git a/Cabal/Distribution/Simple/Register.hs b/Cabal/Distribution/Simple/Register.hs index db9acd91350ba73890e74782286729cc76988702..f2d6047b9e4b97aed3a0155ea1081ad7237128f3 100644 --- a/Cabal/Distribution/Simple/Register.hs +++ b/Cabal/Distribution/Simple/Register.hs @@ -2,6 +2,7 @@ -- | -- Module : Distribution.Simple.Register -- Copyright : Isaac Jones 2003-2004 +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Portability : portable @@ -22,37 +23,6 @@ -- mixes it all in in this module, which is rather unsatisfactory. The script -- generation and the unregister feature are not well used or tested. -{- Copyright (c) 2003-2004, Isaac Jones -All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - module Distribution.Simple.Register ( register, unregister, diff --git a/Cabal/Distribution/Simple/Setup.hs b/Cabal/Distribution/Simple/Setup.hs index 30d2f41c0cd6b36b1861c8f7fda7b454c4b40111..b9eafb7d5c5a2bfc0719fbf3bc9d7f0209abb004 100644 --- a/Cabal/Distribution/Simple/Setup.hs +++ b/Cabal/Distribution/Simple/Setup.hs @@ -3,6 +3,7 @@ -- Module : Distribution.Simple.Setup -- Copyright : Isaac Jones 2003-2004 -- Duncan Coutts 2007 +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Portability : portable @@ -26,36 +27,6 @@ -- read and written from files. This would allow us to save configure flags in -- config files. -{- All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - {-# LANGUAGE CPP #-} module Distribution.Simple.Setup ( @@ -1409,8 +1380,17 @@ defaultBuildFlags = BuildFlags { } buildCommand :: ProgramConfiguration -> CommandUI BuildFlags -buildCommand progConf = makeCommand name shortDesc longDesc - defaultBuildFlags (buildOptions progConf) +buildCommand progConf = + makeCommand name shortDesc longDesc + defaultBuildFlags + (\showOrParseArgs -> + [ optionVerbosity + buildVerbosity (\v flags -> flags { buildVerbosity = v }) + + , optionDistPref + buildDistPref (\d flags -> flags { buildDistPref = d }) showOrParseArgs + ] + ++ buildOptions progConf showOrParseArgs) where name = "build" shortDesc = "Compile all targets or specific targets." @@ -1419,7 +1399,8 @@ buildCommand progConf = makeCommand name shortDesc longDesc ++ " " ++ pname ++ " build " ++ " All the components in the package\n" ++ " " ++ pname ++ " build foo " - ++ " A component (i.e. lib, exe, test suite)\n" + ++ " A component (i.e. lib, exe, test suite)\n\n" + ++ programFlagsDescription progConf --TODO: re-enable once we have support for module/file targets -- ++ " " ++ pname ++ " build Foo.Bar " -- ++ " A module\n" @@ -1433,13 +1414,7 @@ buildCommand progConf = makeCommand name shortDesc longDesc buildOptions :: ProgramConfiguration -> ShowOrParseArgs -> [OptionField BuildFlags] buildOptions progConf showOrParseArgs = - [ optionVerbosity - buildVerbosity (\v flags -> flags { buildVerbosity = v }) - - , optionDistPref - buildDistPref (\d flags -> flags { buildDistPref = d }) showOrParseArgs - - , optionNumJobs + [ optionNumJobs buildNumJobs (\v flags -> flags { buildNumJobs = v }) ] @@ -1564,7 +1539,7 @@ replCommand progConf = CommandUI { -- * Test flags -- ------------------------------------------------------------ -data TestShowDetails = Never | Failures | Always +data TestShowDetails = Never | Failures | Always | Streaming deriving (Eq, Ord, Enum, Bounded, Show) knownTestShowDetails :: [TestShowDetails] diff --git a/Cabal/Distribution/Simple/SrcDist.hs b/Cabal/Distribution/Simple/SrcDist.hs index ad1a5cea8db073848240e918e21870c2e549335f..cdbf123618fcc78685d89657933943f9a322a420 100644 --- a/Cabal/Distribution/Simple/SrcDist.hs +++ b/Cabal/Distribution/Simple/SrcDist.hs @@ -2,6 +2,7 @@ -- | -- Module : Distribution.Simple.SrcDist -- Copyright : Simon Marlow 2004 +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Portability : portable @@ -16,37 +17,6 @@ -- it accepts the @-z@ flag. Neither of these assumptions are valid on Windows. -- The 'sdist' action now also does some distribution QA checks. -{- Copyright (c) 2003-2004, Simon Marlow -All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - -- NOTE: FIX: we don't have a great way of testing this module, since -- we can't easily look inside a tarball once its created. diff --git a/Cabal/Distribution/Simple/Test.hs b/Cabal/Distribution/Simple/Test.hs index 3fade9bd2fb174c6bef6ebbed178e19eca368a7d..523dc3ee6eaef9f832c2b76f0e7873a8a5873ab7 100644 --- a/Cabal/Distribution/Simple/Test.hs +++ b/Cabal/Distribution/Simple/Test.hs @@ -2,6 +2,7 @@ -- | -- Module : Distribution.Simple.Test -- Copyright : Thomas Tuegel 2010 +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Portability : portable @@ -10,265 +11,35 @@ -- \"@.\/setup test@\" action. It runs test suites designated in the package -- description and reports on the results. -{- All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - module Distribution.Simple.Test ( test - , stubMain - , writeSimpleTestStub - , stubFilePath - , stubName - , PackageLog(..) - , TestSuiteLog(..) - , TestLogs(..) - , suitePassed, suiteFailed, suiteError ) where -import Distribution.Compat.TempFile ( openTempFile ) -import Distribution.ModuleName ( ModuleName ) -import Distribution.Package - ( PackageId ) import qualified Distribution.PackageDescription as PD ( PackageDescription(..), BuildInfo(buildable) , TestSuite(..) , TestSuiteInterface(..), testType, hasTests ) -import Distribution.Simple.Build.PathsModule ( pkgPathEnvVar ) -import Distribution.Simple.BuildPaths ( exeExtension ) -import Distribution.Simple.Compiler ( Compiler(..), CompilerId ) -import Distribution.Simple.Hpc - ( markupPackage, markupTest, tixDir, tixFilePath ) +import Distribution.Simple.Compiler ( Compiler(..) ) +import Distribution.Simple.Hpc ( markupPackage ) import Distribution.Simple.InstallDirs - ( fromPathTemplate, initialPathTemplateEnv, PathTemplateVariable(..) - , substPathTemplate , toPathTemplate, PathTemplate ) + ( fromPathTemplate, initialPathTemplateEnv, substPathTemplate + , PathTemplate ) import qualified Distribution.Simple.LocalBuildInfo as LBI ( LocalBuildInfo(..) ) -import Distribution.Simple.Setup ( TestFlags(..), TestShowDetails(..), fromFlag ) -import Distribution.Simple.Utils ( die, notice, rawSystemIOWithEnv ) -import Distribution.TestSuite - ( OptionDescr(..), Options, Progress(..), Result(..), TestInstance(..) - , Test(..) ) +import Distribution.Simple.Setup ( TestFlags(..), fromFlag ) +import qualified Distribution.Simple.Test.ExeV10 as ExeV10 +import qualified Distribution.Simple.Test.LibV09 as LibV09 +import Distribution.Simple.Test.Log +import Distribution.Simple.Utils ( die, notice ) +import Distribution.TestSuite ( Result(..) ) import Distribution.Text -import Distribution.Verbosity ( normal, Verbosity ) -import Distribution.System ( Platform ) -import Control.Exception ( bracket ) import Control.Monad ( when, unless, filterM ) -import Data.Char ( toUpper ) -import Data.Maybe ( mapMaybe ) import System.Directory - ( createDirectoryIfMissing, doesDirectoryExist, doesFileExist - , getCurrentDirectory, getDirectoryContents, removeDirectoryRecursive - , removeFile, setCurrentDirectory ) -import Distribution.Compat.Environment ( getEnvironment ) + ( createDirectoryIfMissing, doesFileExist, getDirectoryContents + , removeFile ) import System.Exit ( ExitCode(..), exitFailure, exitWith ) -import System.FilePath ( (</>), (<.>) ) -import System.IO ( hClose, IOMode(..), openFile ) - --- | Logs all test results for a package, broken down first by test suite and --- then by test case. -data PackageLog = PackageLog - { package :: PackageId - , compiler :: CompilerId - , platform :: Platform - , testSuites :: [TestSuiteLog] - } - deriving (Read, Show, Eq) - --- | A 'PackageLog' with package and platform information specified. -localPackageLog :: PD.PackageDescription -> LBI.LocalBuildInfo -> PackageLog -localPackageLog pkg_descr lbi = PackageLog - { package = PD.package pkg_descr - , compiler = compilerId $ LBI.compiler lbi - , platform = LBI.hostPlatform lbi - , testSuites = [] - } - --- | Logs test suite results, itemized by test case. -data TestSuiteLog = TestSuiteLog - { testSuiteName :: String - , testLogs :: TestLogs - , logFile :: FilePath -- path to human-readable log file - } - deriving (Read, Show, Eq) - -data TestLogs - = TestLog - { testName :: String - , testOptionsReturned :: Options - , testResult :: Result - } - | GroupLogs String [TestLogs] - deriving (Read, Show, Eq) - --- | Count the number of pass, fail, and error test results in a 'TestLogs' --- tree. -countTestResults :: TestLogs - -> (Int, Int, Int) -- ^ Passes, fails, and errors, - -- respectively. -countTestResults = go (0, 0, 0) - where - go (p, f, e) (TestLog { testResult = r }) = - case r of - Pass -> (p + 1, f, e) - Fail _ -> (p, f + 1, e) - Error _ -> (p, f, e + 1) - go (p, f, e) (GroupLogs _ ts) = foldl go (p, f, e) ts - --- | From a 'TestSuiteLog', determine if the test suite passed. -suitePassed :: TestSuiteLog -> Bool -suitePassed l = - case countTestResults (testLogs l) of - (_, 0, 0) -> True - _ -> False - --- | From a 'TestSuiteLog', determine if the test suite failed. -suiteFailed :: TestSuiteLog -> Bool -suiteFailed l = - case countTestResults (testLogs l) of - (_, 0, _) -> False - _ -> True - --- | From a 'TestSuiteLog', determine if the test suite encountered errors. -suiteError :: TestSuiteLog -> Bool -suiteError l = - case countTestResults (testLogs l) of - (_, _, 0) -> False - _ -> True - --- | Run a test executable, logging the output and generating the appropriate --- summary messages. -testController :: TestFlags - -- ^ flags Cabal was invoked with - -> PD.PackageDescription - -- ^ description of package the test suite belongs to - -> LBI.LocalBuildInfo - -- ^ information from the configure step - -> PD.TestSuite - -- ^ TestSuite being tested - -> (FilePath -> String) - -- ^ prepare standard input for test executable - -> FilePath -- ^ executable name - -> (ExitCode -> String -> TestSuiteLog) - -- ^ generator for the TestSuiteLog - -> (TestSuiteLog -> FilePath) - -- ^ generator for final human-readable log filename - -> IO TestSuiteLog -testController flags pkg_descr lbi suite preTest cmd postTest logNamer = do - let distPref = fromFlag $ testDistPref flags - verbosity = fromFlag $ testVerbosity flags - testLogDir = distPref </> "test" - opts = map (testOption pkg_descr lbi suite) $ testOptions flags - - pwd <- getCurrentDirectory - existingEnv <- getEnvironment - let dataDirPath = pwd </> PD.dataDir pkg_descr - shellEnv = (pkgPathEnvVar pkg_descr "datadir", dataDirPath) - : ("HPCTIXFILE", (</>) pwd - $ tixFilePath distPref $ PD.testName suite) - : existingEnv - - bracket (openCabalTemp testLogDir) deleteIfExists $ \tempLog -> - bracket (openCabalTemp testLogDir) deleteIfExists $ \tempInput -> do - - -- Check that the test executable exists. - exists <- doesFileExist cmd - unless exists $ die $ "Error: Could not find test program \"" ++ cmd - ++ "\". Did you build the package first?" - - -- Remove old .tix files if appropriate. - unless (fromFlag $ testKeepTix flags) $ do - let tDir = tixDir distPref $ PD.testName suite - exists' <- doesDirectoryExist tDir - when exists' $ removeDirectoryRecursive tDir - - -- Create directory for HPC files. - createDirectoryIfMissing True $ tixDir distPref $ PD.testName suite - - -- Write summary notices indicating start of test suite - notice verbosity $ summarizeSuiteStart $ PD.testName suite - - -- Prepare standard input for test executable - appendFile tempInput $ preTest tempInput - - -- Run test executable - exit <- do - hLog <- openFile tempLog AppendMode - hIn <- openFile tempInput ReadMode - -- these handles get closed by rawSystemIOWithEnv - rawSystemIOWithEnv verbosity cmd opts Nothing (Just shellEnv) - (Just hIn) (Just hLog) (Just hLog) - - -- Generate TestSuiteLog from executable exit code and a machine- - -- readable test log - suiteLog <- fmap (postTest exit $!) $ readFile tempInput - - -- Generate final log file name - let finalLogName = testLogDir </> logNamer suiteLog - suiteLog' = suiteLog { logFile = finalLogName } - - -- Write summary notice to log file indicating start of test suite - appendFile (logFile suiteLog') $ summarizeSuiteStart $ PD.testName suite - - -- Append contents of temporary log file to the final human- - -- readable log file - readFile tempLog >>= appendFile (logFile suiteLog') - - -- Write end-of-suite summary notice to log file - appendFile (logFile suiteLog') $ summarizeSuiteFinish suiteLog' - - -- Show the contents of the human-readable log file on the terminal - -- if there is a failure and/or detailed output is requested - let details = fromFlag $ testShowDetails flags - whenPrinting = when $ (details > Never) - && (not (suitePassed suiteLog) || details == Always) - && verbosity >= normal - whenPrinting $ readFile tempLog >>= - putStr . unlines . lines - - -- Write summary notice to terminal indicating end of test suite - notice verbosity $ summarizeSuiteFinish suiteLog' - - markupTest verbosity lbi distPref - (display $ PD.package pkg_descr) suite - - return suiteLog' - where - deleteIfExists file = do - exists <- doesFileExist file - when exists $ removeFile file - - openCabalTemp testLogDir = do - (f, h) <- openTempFile testLogDir $ "cabal-test-" <.> "log" - hClose h >> return f - +import System.FilePath ( (</>) ) -- |Perform the \"@.\/setup test@\" action. test :: PD.PackageDescription -- ^information from the .cabal file @@ -277,7 +48,6 @@ test :: PD.PackageDescription -- ^information from the .cabal file -> IO () test pkg_descr lbi flags = do let verbosity = fromFlag $ testVerbosity flags - humanTemplate = fromFlag $ testHumanLog flags machineTemplate = fromFlag $ testMachineLog flags distPref = fromFlag $ testDistPref flags testLogDir = distPref </> "test" @@ -288,51 +58,25 @@ test pkg_descr lbi flags = do , PD.buildable (PD.testBuildInfo t) ] doTest :: (PD.TestSuite, Maybe TestSuiteLog) -> IO TestSuiteLog - doTest (suite, _) = do - let testLogPath = testSuiteLogPath humanTemplate pkg_descr lbi - go pre cmd post = testController flags pkg_descr lbi suite - pre cmd post testLogPath + doTest (suite, _) = case PD.testInterface suite of - PD.TestSuiteExeV10 _ _ -> do - let cmd = LBI.buildDir lbi </> PD.testName suite - </> PD.testName suite <.> exeExtension - preTest _ = "" - postTest exit _ = - let r = case exit of - ExitSuccess -> Pass - ExitFailure c -> Fail - $ "exit code: " ++ show c - in TestSuiteLog - { testSuiteName = PD.testName suite - , testLogs = TestLog - { testName = PD.testName suite - , testOptionsReturned = [] - , testResult = r - } - , logFile = "" - } - go preTest cmd postTest + PD.TestSuiteExeV10 _ _ -> + ExeV10.runTest pkg_descr lbi flags suite - PD.TestSuiteLibV09 _ _ -> do - let cmd = LBI.buildDir lbi </> stubName suite - </> stubName suite <.> exeExtension - preTest f = show ( f - , PD.testName suite - ) - postTest _ = read - go preTest cmd postTest + PD.TestSuiteLibV09 _ _ -> + LibV09.runTest pkg_descr lbi flags suite _ -> return TestSuiteLog - { testSuiteName = PD.testName suite - , testLogs = TestLog - { testName = PD.testName suite - , testOptionsReturned = [] - , testResult = Error $ - "No support for running test suite type: " - ++ show (disp $ PD.testType suite) - } - , logFile = "" - } + { testSuiteName = PD.testName suite + , testLogs = TestLog + { testName = PD.testName suite + , testOptionsReturned = [] + , testResult = + Error $ "No support for running test suite type: " + ++ show (disp $ PD.testType suite) + } + , logFile = "" + } when (not $ PD.hasTests pkg_descr) $ do notice verbosity "Package has no test suites." @@ -376,81 +120,6 @@ test pkg_descr lbi flags = do unless allOk exitFailure --- | Print a summary to the console after all test suites have been run --- indicating the number of successful test suites and cases. Returns 'True' if --- all test suites passed and 'False' otherwise. -summarizePackage :: Verbosity -> PackageLog -> IO Bool -summarizePackage verbosity packageLog = do - let counts = map (countTestResults . testLogs) $ testSuites packageLog - (passed, failed, errors) = foldl1 addTriple counts - totalCases = passed + failed + errors - passedSuites = length $ filter suitePassed $ testSuites packageLog - totalSuites = length $ testSuites packageLog - notice verbosity $ show passedSuites ++ " of " ++ show totalSuites - ++ " test suites (" ++ show passed ++ " of " - ++ show totalCases ++ " test cases) passed." - return $! passedSuites == totalSuites - where - addTriple (p1, f1, e1) (p2, f2, e2) = (p1 + p2, f1 + f2, e1 + e2) - --- | Print a summary of a single test case's result to the console, supressing --- output for certain verbosity or test filter levels. -summarizeTest :: Verbosity -> TestShowDetails -> TestLogs -> IO () -summarizeTest _ _ (GroupLogs {}) = return () -summarizeTest verbosity details t = - when shouldPrint $ notice verbosity $ "Test case " ++ testName t - ++ ": " ++ show (testResult t) - where shouldPrint = (details > Never) && (notPassed || details == Always) - notPassed = testResult t /= Pass - --- | Print a summary of the test suite's results on the console, suppressing --- output for certain verbosity or test filter levels. -summarizeSuiteFinish :: TestSuiteLog -> String -summarizeSuiteFinish testLog = unlines - [ "Test suite " ++ testSuiteName testLog ++ ": " ++ resStr - , "Test suite logged to: " ++ logFile testLog - ] - where resStr = map toUpper (resultString testLog) - -summarizeSuiteStart :: String -> String -summarizeSuiteStart n = "Test suite " ++ n ++ ": RUNNING...\n" - -resultString :: TestSuiteLog -> String -resultString l | suiteError l = "error" - | suiteFailed l = "fail" - | otherwise = "pass" - -testSuiteLogPath :: PathTemplate - -> PD.PackageDescription - -> LBI.LocalBuildInfo - -> TestSuiteLog - -> FilePath -testSuiteLogPath template pkg_descr lbi testLog = - fromPathTemplate $ substPathTemplate env template - where - env = initialPathTemplateEnv - (PD.package pkg_descr) (compilerId $ LBI.compiler lbi) - (LBI.hostPlatform lbi) - ++ [ (TestSuiteNameVar, toPathTemplate $ testSuiteName testLog) - , (TestSuiteResultVar, result) - ] - result = toPathTemplate $ resultString testLog - --- TODO: This is abusing the notion of a 'PathTemplate'. The result --- isn't neccesarily a path. -testOption :: PD.PackageDescription - -> LBI.LocalBuildInfo - -> PD.TestSuite - -> PathTemplate - -> String -testOption pkg_descr lbi suite template = - fromPathTemplate $ substPathTemplate env template - where - env = initialPathTemplateEnv - (PD.package pkg_descr) (compilerId $ LBI.compiler lbi) - (LBI.hostPlatform lbi) ++ - [(TestSuiteNameVar, toPathTemplate $ PD.testName suite)] - packageLogPath :: PathTemplate -> PD.PackageDescription -> LBI.LocalBuildInfo @@ -461,87 +130,3 @@ packageLogPath template pkg_descr lbi = env = initialPathTemplateEnv (PD.package pkg_descr) (compilerId $ LBI.compiler lbi) (LBI.hostPlatform lbi) - --- | The filename of the source file for the stub executable associated with a --- library 'TestSuite'. -stubFilePath :: PD.TestSuite -> FilePath -stubFilePath t = stubName t <.> "hs" - --- | The name of the stub executable associated with a library 'TestSuite'. -stubName :: PD.TestSuite -> FilePath -stubName t = PD.testName t ++ "Stub" - --- | Write the source file for a library 'TestSuite' stub executable. -writeSimpleTestStub :: PD.TestSuite -- ^ library 'TestSuite' for which a stub - -- is being created - -> FilePath -- ^ path to directory where stub source - -- should be located - -> IO () -writeSimpleTestStub t dir = do - createDirectoryIfMissing True dir - let filename = dir </> stubFilePath t - PD.TestSuiteLibV09 _ m = PD.testInterface t - writeFile filename $ simpleTestStub m - --- | Source code for library test suite stub executable -simpleTestStub :: ModuleName -> String -simpleTestStub m = unlines - [ "module Main ( main ) where" - , "import Distribution.Simple.Test ( stubMain )" - , "import " ++ show (disp m) ++ " ( tests )" - , "main :: IO ()" - , "main = stubMain tests" - ] - --- | Main function for test stubs. Once, it was written directly into the stub, --- but minimizing the amount of code actually in the stub maximizes the number --- of detectable errors when Cabal is compiled. -stubMain :: IO [Test] -> IO () -stubMain tests = do - (f, n) <- fmap read getContents - dir <- getCurrentDirectory - results <- tests >>= stubRunTests - setCurrentDirectory dir - stubWriteLog f n results - --- | The test runner used in library "TestSuite" stub executables. Runs a list --- of 'Test's. An executable calling this function is meant to be invoked as --- the child of a Cabal process during @.\/setup test@. A 'TestSuiteLog', --- provided by Cabal, is read from the standard input; it supplies the name of --- the test suite and the location of the machine-readable test suite log file. --- Human-readable log information is written to the standard output for capture --- by the calling Cabal process. -stubRunTests :: [Test] -> IO TestLogs -stubRunTests tests = do - logs <- mapM stubRunTests' tests - return $ GroupLogs "Default" logs - where - stubRunTests' (Test t) = do - l <- run t >>= finish - summarizeTest normal Always l - return l - where - finish (Finished result) = - return TestLog - { testName = name t - , testOptionsReturned = defaultOptions t - , testResult = result - } - finish (Progress _ next) = next >>= finish - stubRunTests' g@(Group {}) = do - logs <- mapM stubRunTests' $ groupTests g - return $ GroupLogs (groupName g) logs - stubRunTests' (ExtraOptions _ t) = stubRunTests' t - maybeDefaultOption opt = - maybe Nothing (\d -> Just (optionName opt, d)) $ optionDefault opt - defaultOptions testInst = mapMaybe maybeDefaultOption $ options testInst - --- | From a test stub, write the 'TestSuiteLog' to temporary file for the calling --- Cabal process to read. -stubWriteLog :: FilePath -> String -> TestLogs -> IO () -stubWriteLog f n logs = do - let testLog = TestSuiteLog { testSuiteName = n, testLogs = logs, logFile = f } - writeFile (logFile testLog) $ show testLog - when (suiteError testLog) $ exitWith $ ExitFailure 2 - when (suiteFailed testLog) $ exitWith $ ExitFailure 1 - exitWith ExitSuccess diff --git a/Cabal/Distribution/Simple/Test/ExeV10.hs b/Cabal/Distribution/Simple/Test/ExeV10.hs new file mode 100644 index 0000000000000000000000000000000000000000..633d636da8d681c6e42ee126c3d83baeefbd7e10 --- /dev/null +++ b/Cabal/Distribution/Simple/Test/ExeV10.hs @@ -0,0 +1,146 @@ +module Distribution.Simple.Test.ExeV10 + ( runTest + ) where + +import Distribution.Compat.CreatePipe ( createPipe, tee ) +import Distribution.Compat.Environment ( getEnvironment ) +import qualified Distribution.PackageDescription as PD +import Distribution.Simple.Build.PathsModule ( pkgPathEnvVar ) +import Distribution.Simple.BuildPaths ( exeExtension ) +import Distribution.Simple.Compiler ( Compiler(..) ) +import Distribution.Simple.Hpc ( markupTest, tixDir, tixFilePath ) +import Distribution.Simple.InstallDirs + ( fromPathTemplate, initialPathTemplateEnv, PathTemplateVariable(..) + , substPathTemplate , toPathTemplate, PathTemplate ) +import qualified Distribution.Simple.LocalBuildInfo as LBI +import Distribution.Simple.Setup ( TestFlags(..), TestShowDetails(..), fromFlag ) +import Distribution.Simple.Test.Log +import Distribution.Simple.Utils ( die, notice, rawSystemIOWithEnv ) +import Distribution.TestSuite +import Distribution.Text +import Distribution.Verbosity ( normal ) + +import Control.Monad ( when, unless ) +import System.Directory + ( createDirectoryIfMissing, doesDirectoryExist, doesFileExist + , getCurrentDirectory, removeDirectoryRecursive ) +import System.Exit ( ExitCode(..) ) +import System.FilePath ( (</>), (<.>) ) +import System.IO ( hGetContents, stdout ) + +runTest :: PD.PackageDescription + -> LBI.LocalBuildInfo + -> TestFlags + -> PD.TestSuite + -> IO TestSuiteLog +runTest pkg_descr lbi flags suite = do + pwd <- getCurrentDirectory + existingEnv <- getEnvironment + + let cmd = LBI.buildDir lbi </> PD.testName suite + </> PD.testName suite <.> exeExtension + -- Check that the test executable exists. + exists <- doesFileExist cmd + unless exists $ die $ "Error: Could not find test program \"" ++ cmd + ++ "\". Did you build the package first?" + + -- Remove old .tix files if appropriate. + unless (fromFlag $ testKeepTix flags) $ do + let tDir = tixDir distPref $ PD.testName suite + exists' <- doesDirectoryExist tDir + when exists' $ removeDirectoryRecursive tDir + + -- Create directory for HPC files. + createDirectoryIfMissing True $ tixDir distPref $ PD.testName suite + + -- Write summary notices indicating start of test suite + notice verbosity $ summarizeSuiteStart $ PD.testName suite + + -- Run test executable + (rLog, wLog) <- createPipe + let opts = map (testOption pkg_descr lbi suite) + (testOptions flags) + dataDirPath = pwd </> PD.dataDir pkg_descr + shellEnv = (pkgPathEnvVar pkg_descr "datadir", dataDirPath) + : ("HPCTIXFILE", (</>) pwd + $ tixFilePath distPref $ PD.testName suite) + : existingEnv + + (rOut, wOut) <- createPipe + let outHandles | details == Streaming = [(stdout, False)] + | otherwise = [] + tee rOut $ (wLog, True) : outHandles + exit <- rawSystemIOWithEnv verbosity cmd opts Nothing (Just shellEnv) + -- these handles are automatically closed + Nothing (Just wOut) (Just wOut) + + -- Generate TestSuiteLog from executable exit code and a machine- + -- readable test log + let suiteLog = buildLog exit + + -- Write summary notice to log file indicating start of test suite + appendFile (logFile suiteLog) $ summarizeSuiteStart $ PD.testName suite + + -- Append contents of temporary log file to the final human- + -- readable log file + logText <- hGetContents rLog + appendFile (logFile suiteLog) logText + + -- Write end-of-suite summary notice to log file + appendFile (logFile suiteLog) $ summarizeSuiteFinish suiteLog + + -- Show the contents of the human-readable log file on the terminal + -- if there is a failure and/or detailed output is requested + let + whenPrinting = when $ (details > Never) + && (not (suitePassed $ testLogs suiteLog) || details == Always) + && verbosity >= normal -- verbosity overrides show-details + && details /= Streaming -- If streaming, we already printed the log + whenPrinting $ putStr $ unlines $ lines logText + + -- Write summary notice to terminal indicating end of test suite + notice verbosity $ summarizeSuiteFinish suiteLog + + markupTest verbosity lbi distPref + (display $ PD.package pkg_descr) suite + + return suiteLog + where + distPref = fromFlag $ testDistPref flags + verbosity = fromFlag $ testVerbosity flags + details = fromFlag $ testShowDetails flags + testLogDir = distPref </> "test" + + buildLog exit = + let r = case exit of + ExitSuccess -> Pass + ExitFailure c -> Fail $ "exit code: " ++ show c + n = PD.testName suite + l = TestLog + { testName = n + , testOptionsReturned = [] + , testResult = r + } + in TestSuiteLog + { testSuiteName = n + , testLogs = l + , logFile = + testLogDir + </> testSuiteLogPath (fromFlag $ testHumanLog flags) + pkg_descr lbi n l + } + +-- TODO: This is abusing the notion of a 'PathTemplate'. The result +-- isn't neccesarily a path. +testOption :: PD.PackageDescription + -> LBI.LocalBuildInfo + -> PD.TestSuite + -> PathTemplate + -> String +testOption pkg_descr lbi suite template = + fromPathTemplate $ substPathTemplate env template + where + env = initialPathTemplateEnv + (PD.package pkg_descr) (compilerId $ LBI.compiler lbi) + (LBI.hostPlatform lbi) ++ + [(TestSuiteNameVar, toPathTemplate $ PD.testName suite)] diff --git a/Cabal/Distribution/Simple/Test/LibV09.hs b/Cabal/Distribution/Simple/Test/LibV09.hs new file mode 100644 index 0000000000000000000000000000000000000000..ddea95f31e47d7a20cbf801610d92b75471f6c71 --- /dev/null +++ b/Cabal/Distribution/Simple/Test/LibV09.hs @@ -0,0 +1,239 @@ +module Distribution.Simple.Test.LibV09 + ( runTest + -- Test stub + , simpleTestStub + , stubFilePath, stubMain, stubName, stubWriteLog + , writeSimpleTestStub + ) where + +import Distribution.Compat.CreatePipe ( createPipe ) +import Distribution.Compat.Environment ( getEnvironment ) +import Distribution.Compat.TempFile ( openTempFile ) +import Distribution.ModuleName ( ModuleName ) +import qualified Distribution.PackageDescription as PD +import Distribution.Simple.Build.PathsModule ( pkgPathEnvVar ) +import Distribution.Simple.BuildPaths ( exeExtension ) +import Distribution.Simple.Compiler ( Compiler(..) ) +import Distribution.Simple.Hpc ( markupTest, tixDir, tixFilePath ) +import Distribution.Simple.InstallDirs + ( fromPathTemplate, initialPathTemplateEnv, PathTemplateVariable(..) + , substPathTemplate , toPathTemplate, PathTemplate ) +import qualified Distribution.Simple.LocalBuildInfo as LBI +import Distribution.Simple.Setup ( TestFlags(..), TestShowDetails(..), fromFlag ) +import Distribution.Simple.Test.Log +import Distribution.Simple.Utils ( die, notice, rawSystemIOWithEnv ) +import Distribution.TestSuite +import Distribution.Text +import Distribution.Verbosity ( normal ) + +import Control.Exception ( bracket ) +import Control.Monad ( when, unless ) +import Data.Maybe ( mapMaybe ) +import System.Directory + ( createDirectoryIfMissing, doesDirectoryExist, doesFileExist + , getCurrentDirectory, removeDirectoryRecursive, removeFile + , setCurrentDirectory ) +import System.Exit ( ExitCode(..), exitWith ) +import System.FilePath ( (</>), (<.>) ) +import System.IO ( hClose, hGetContents, hPutStr ) + +runTest :: PD.PackageDescription + -> LBI.LocalBuildInfo + -> TestFlags + -> PD.TestSuite + -> IO TestSuiteLog +runTest pkg_descr lbi flags suite = do + pwd <- getCurrentDirectory + existingEnv <- getEnvironment + + let cmd = LBI.buildDir lbi </> stubName suite + </> stubName suite <.> exeExtension + -- Check that the test executable exists. + exists <- doesFileExist cmd + unless exists $ die $ "Error: Could not find test program \"" ++ cmd + ++ "\". Did you build the package first?" + + -- Remove old .tix files if appropriate. + unless (fromFlag $ testKeepTix flags) $ do + let tDir = tixDir distPref $ PD.testName suite + exists' <- doesDirectoryExist tDir + when exists' $ removeDirectoryRecursive tDir + + -- Create directory for HPC files. + createDirectoryIfMissing True $ tixDir distPref $ PD.testName suite + + -- Write summary notices indicating start of test suite + notice verbosity $ summarizeSuiteStart $ PD.testName suite + + suiteLog <- bracket openCabalTemp deleteIfExists $ \tempLog -> do + + (rIn, wIn) <- createPipe + (rOut, wOut) <- createPipe + + -- Prepare standard input for test executable + --appendFile tempInput $ show (tempInput, PD.testName suite) + hPutStr wIn $ show (tempLog, PD.testName suite) + hClose wIn + + -- Run test executable + _ <- do let opts = map (testOption pkg_descr lbi suite) $ testOptions flags + dataDirPath = pwd </> PD.dataDir pkg_descr + shellEnv = (pkgPathEnvVar pkg_descr "datadir", dataDirPath) + : ("HPCTIXFILE", (</>) pwd + $ tixFilePath distPref $ PD.testName suite) + : existingEnv + rawSystemIOWithEnv verbosity cmd opts Nothing (Just shellEnv) + -- these handles are closed automatically + (Just rIn) (Just wOut) (Just wOut) + + -- Generate final log file name + let finalLogName l = testLogDir + </> testSuiteLogPath + (fromFlag $ testHumanLog flags) pkg_descr lbi + (testSuiteName l) (testLogs l) + -- Generate TestSuiteLog from executable exit code and a machine- + -- readable test log + suiteLog <- fmap ((\l -> l { logFile = finalLogName l }) . read) + $ readFile tempLog + + -- Write summary notice to log file indicating start of test suite + appendFile (logFile suiteLog) $ summarizeSuiteStart $ PD.testName suite + + -- Append contents of temporary log file to the final human- + -- readable log file + logText <- hGetContents rOut + appendFile (logFile suiteLog) logText + + -- Write end-of-suite summary notice to log file + appendFile (logFile suiteLog) $ summarizeSuiteFinish suiteLog + + -- Show the contents of the human-readable log file on the terminal + -- if there is a failure and/or detailed output is requested + let details = fromFlag $ testShowDetails flags + whenPrinting = when $ (details > Never) + && (not (suitePassed $ testLogs suiteLog) || details == Always) + && verbosity >= normal + whenPrinting $ putStr $ unlines $ lines logText + + return suiteLog + + -- Write summary notice to terminal indicating end of test suite + notice verbosity $ summarizeSuiteFinish suiteLog + + markupTest verbosity lbi distPref + (display $ PD.package pkg_descr) suite + + return suiteLog + where + deleteIfExists file = do + exists <- doesFileExist file + when exists $ removeFile file + + testLogDir = distPref </> "test" + openCabalTemp = do + (f, h) <- openTempFile testLogDir $ "cabal-test-" <.> "log" + hClose h >> return f + + distPref = fromFlag $ testDistPref flags + verbosity = fromFlag $ testVerbosity flags + +-- TODO: This is abusing the notion of a 'PathTemplate'. The result +-- isn't neccesarily a path. +testOption :: PD.PackageDescription + -> LBI.LocalBuildInfo + -> PD.TestSuite + -> PathTemplate + -> String +testOption pkg_descr lbi suite template = + fromPathTemplate $ substPathTemplate env template + where + env = initialPathTemplateEnv + (PD.package pkg_descr) (compilerId $ LBI.compiler lbi) + (LBI.hostPlatform lbi) ++ + [(TestSuiteNameVar, toPathTemplate $ PD.testName suite)] + +-- Test stub ---------- + +-- | The name of the stub executable associated with a library 'TestSuite'. +stubName :: PD.TestSuite -> FilePath +stubName t = PD.testName t ++ "Stub" + +-- | The filename of the source file for the stub executable associated with a +-- library 'TestSuite'. +stubFilePath :: PD.TestSuite -> FilePath +stubFilePath t = stubName t <.> "hs" + +-- | Write the source file for a library 'TestSuite' stub executable. +writeSimpleTestStub :: PD.TestSuite -- ^ library 'TestSuite' for which a stub + -- is being created + -> FilePath -- ^ path to directory where stub source + -- should be located + -> IO () +writeSimpleTestStub t dir = do + createDirectoryIfMissing True dir + let filename = dir </> stubFilePath t + PD.TestSuiteLibV09 _ m = PD.testInterface t + writeFile filename $ simpleTestStub m + +-- | Source code for library test suite stub executable +simpleTestStub :: ModuleName -> String +simpleTestStub m = unlines + [ "module Main ( main ) where" + , "import Distribution.Simple.Test.LibV09 ( stubMain )" + , "import " ++ show (disp m) ++ " ( tests )" + , "main :: IO ()" + , "main = stubMain tests" + ] + +-- | Main function for test stubs. Once, it was written directly into the stub, +-- but minimizing the amount of code actually in the stub maximizes the number +-- of detectable errors when Cabal is compiled. +stubMain :: IO [Test] -> IO () +stubMain tests = do + (f, n) <- fmap read getContents + dir <- getCurrentDirectory + results <- tests >>= stubRunTests + setCurrentDirectory dir + stubWriteLog f n results + +-- | The test runner used in library "TestSuite" stub executables. Runs a list +-- of 'Test's. An executable calling this function is meant to be invoked as +-- the child of a Cabal process during @.\/setup test@. A 'TestSuiteLog', +-- provided by Cabal, is read from the standard input; it supplies the name of +-- the test suite and the location of the machine-readable test suite log file. +-- Human-readable log information is written to the standard output for capture +-- by the calling Cabal process. +stubRunTests :: [Test] -> IO TestLogs +stubRunTests tests = do + logs <- mapM stubRunTests' tests + return $ GroupLogs "Default" logs + where + stubRunTests' (Test t) = do + l <- run t >>= finish + summarizeTest normal Always l + return l + where + finish (Finished result) = + return TestLog + { testName = name t + , testOptionsReturned = defaultOptions t + , testResult = result + } + finish (Progress _ next) = next >>= finish + stubRunTests' g@(Group {}) = do + logs <- mapM stubRunTests' $ groupTests g + return $ GroupLogs (groupName g) logs + stubRunTests' (ExtraOptions _ t) = stubRunTests' t + maybeDefaultOption opt = + maybe Nothing (\d -> Just (optionName opt, d)) $ optionDefault opt + defaultOptions testInst = mapMaybe maybeDefaultOption $ options testInst + +-- | From a test stub, write the 'TestSuiteLog' to temporary file for the calling +-- Cabal process to read. +stubWriteLog :: FilePath -> String -> TestLogs -> IO () +stubWriteLog f n logs = do + let testLog = TestSuiteLog { testSuiteName = n, testLogs = logs, logFile = f } + writeFile (logFile testLog) $ show testLog + when (suiteError logs) $ exitWith $ ExitFailure 2 + when (suiteFailed logs) $ exitWith $ ExitFailure 1 + exitWith ExitSuccess diff --git a/Cabal/Distribution/Simple/Test/Log.hs b/Cabal/Distribution/Simple/Test/Log.hs new file mode 100644 index 0000000000000000000000000000000000000000..34215a60a2b999e0ac853f7140f3277b806b9211 --- /dev/null +++ b/Cabal/Distribution/Simple/Test/Log.hs @@ -0,0 +1,161 @@ +module Distribution.Simple.Test.Log + ( PackageLog(..) + , TestLogs(..) + , TestSuiteLog(..) + , countTestResults + , localPackageLog + , summarizePackage + , summarizeSuiteFinish, summarizeSuiteStart + , summarizeTest + , suiteError, suiteFailed, suitePassed + , testSuiteLogPath + ) where + +import Distribution.Package ( PackageId ) +import qualified Distribution.PackageDescription as PD +import Distribution.Simple.Compiler ( Compiler(..), CompilerId ) +import Distribution.Simple.InstallDirs + ( fromPathTemplate, initialPathTemplateEnv, PathTemplateVariable(..) + , substPathTemplate , toPathTemplate, PathTemplate ) +import qualified Distribution.Simple.LocalBuildInfo as LBI +import Distribution.Simple.Setup ( TestShowDetails(..) ) +import Distribution.Simple.Utils ( notice ) +import Distribution.System ( Platform ) +import Distribution.TestSuite ( Options, Result(..) ) +import Distribution.Verbosity ( Verbosity ) + +import Control.Monad ( when ) +import Data.Char ( toUpper ) + +-- | Logs all test results for a package, broken down first by test suite and +-- then by test case. +data PackageLog = PackageLog + { package :: PackageId + , compiler :: CompilerId + , platform :: Platform + , testSuites :: [TestSuiteLog] + } + deriving (Read, Show, Eq) + +-- | A 'PackageLog' with package and platform information specified. +localPackageLog :: PD.PackageDescription -> LBI.LocalBuildInfo -> PackageLog +localPackageLog pkg_descr lbi = PackageLog + { package = PD.package pkg_descr + , compiler = compilerId $ LBI.compiler lbi + , platform = LBI.hostPlatform lbi + , testSuites = [] + } + +-- | Logs test suite results, itemized by test case. +data TestSuiteLog = TestSuiteLog + { testSuiteName :: String + , testLogs :: TestLogs + , logFile :: FilePath -- path to human-readable log file + } + deriving (Read, Show, Eq) + +data TestLogs + = TestLog + { testName :: String + , testOptionsReturned :: Options + , testResult :: Result + } + | GroupLogs String [TestLogs] + deriving (Read, Show, Eq) + +-- | Count the number of pass, fail, and error test results in a 'TestLogs' +-- tree. +countTestResults :: TestLogs + -> (Int, Int, Int) -- ^ Passes, fails, and errors, + -- respectively. +countTestResults = go (0, 0, 0) + where + go (p, f, e) (TestLog { testResult = r }) = + case r of + Pass -> (p + 1, f, e) + Fail _ -> (p, f + 1, e) + Error _ -> (p, f, e + 1) + go (p, f, e) (GroupLogs _ ts) = foldl go (p, f, e) ts + +-- | From a 'TestSuiteLog', determine if the test suite passed. +suitePassed :: TestLogs -> Bool +suitePassed l = + case countTestResults l of + (_, 0, 0) -> True + _ -> False + +-- | From a 'TestSuiteLog', determine if the test suite failed. +suiteFailed :: TestLogs -> Bool +suiteFailed l = + case countTestResults l of + (_, 0, _) -> False + _ -> True + +-- | From a 'TestSuiteLog', determine if the test suite encountered errors. +suiteError :: TestLogs -> Bool +suiteError l = + case countTestResults l of + (_, _, 0) -> False + _ -> True + +resultString :: TestLogs -> String +resultString l | suiteError l = "error" + | suiteFailed l = "fail" + | otherwise = "pass" + +testSuiteLogPath :: PathTemplate + -> PD.PackageDescription + -> LBI.LocalBuildInfo + -> String -- ^ test suite name + -> TestLogs -- ^ test suite results + -> FilePath +testSuiteLogPath template pkg_descr lbi name result = + fromPathTemplate $ substPathTemplate env template + where + env = initialPathTemplateEnv + (PD.package pkg_descr) (compilerId $ LBI.compiler lbi) + (LBI.hostPlatform lbi) + ++ [ (TestSuiteNameVar, toPathTemplate name) + , (TestSuiteResultVar, toPathTemplate $ resultString result) + ] + +-- | Print a summary to the console after all test suites have been run +-- indicating the number of successful test suites and cases. Returns 'True' if +-- all test suites passed and 'False' otherwise. +summarizePackage :: Verbosity -> PackageLog -> IO Bool +summarizePackage verbosity packageLog = do + let counts = map (countTestResults . testLogs) $ testSuites packageLog + (passed, failed, errors) = foldl1 addTriple counts + totalCases = passed + failed + errors + passedSuites = length + $ filter (suitePassed . testLogs) + $ testSuites packageLog + totalSuites = length $ testSuites packageLog + notice verbosity $ show passedSuites ++ " of " ++ show totalSuites + ++ " test suites (" ++ show passed ++ " of " + ++ show totalCases ++ " test cases) passed." + return $! passedSuites == totalSuites + where + addTriple (p1, f1, e1) (p2, f2, e2) = (p1 + p2, f1 + f2, e1 + e2) + +-- | Print a summary of a single test case's result to the console, supressing +-- output for certain verbosity or test filter levels. +summarizeTest :: Verbosity -> TestShowDetails -> TestLogs -> IO () +summarizeTest _ _ (GroupLogs {}) = return () +summarizeTest verbosity details t = + when shouldPrint $ notice verbosity $ "Test case " ++ testName t + ++ ": " ++ show (testResult t) + where shouldPrint = (details > Never) && (notPassed || details == Always) + notPassed = testResult t /= Pass + +-- | Print a summary of the test suite's results on the console, suppressing +-- output for certain verbosity or test filter levels. +summarizeSuiteFinish :: TestSuiteLog -> String +summarizeSuiteFinish testLog = unlines + [ "Test suite " ++ testSuiteName testLog ++ ": " ++ resStr + , "Test suite logged to: " ++ logFile testLog + ] + where resStr = map toUpper (resultString $ testLogs testLog) + +summarizeSuiteStart :: String -> String +summarizeSuiteStart n = "Test suite " ++ n ++ ": RUNNING...\n" diff --git a/Cabal/Distribution/Simple/UHC.hs b/Cabal/Distribution/Simple/UHC.hs index 4fae18b427647ce7265b5b1f6b14a15d4f93ab35..436e1da0f3af5bb2c6baf803effd9d9c40b063b6 100644 --- a/Cabal/Distribution/Simple/UHC.hs +++ b/Cabal/Distribution/Simple/UHC.hs @@ -2,6 +2,7 @@ -- | -- Module : Distribution.Simple.UHC -- Copyright : Andres Loeh 2009 +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Portability : portable @@ -13,39 +14,6 @@ -- particular to Isaac Jones, Duncan Coutts and Henning Thielemann, for -- inspiration on how to design this module. -{- -Copyright (c) 2009, Andres Loeh -Copyright (c) 2003-2005, Isaac Jones -All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - module Distribution.Simple.UHC ( configure, getInstalledPackages, buildLib, buildExe, installLib, registerPackage diff --git a/Cabal/Distribution/Simple/UserHooks.hs b/Cabal/Distribution/Simple/UserHooks.hs index 865f0bd86711c863aca5434f0d0d35486319ce97..e680ae69d93b247b65ed18f201c410d017194096 100644 --- a/Cabal/Distribution/Simple/UserHooks.hs +++ b/Cabal/Distribution/Simple/UserHooks.hs @@ -2,6 +2,7 @@ -- | -- Module : Distribution.Simple.UserHooks -- Copyright : Isaac Jones 2003-2005 +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Portability : portable @@ -22,36 +23,6 @@ -- various phases because it would involve changing the types of the -- corresponding hook. At some point it will have to be replaced. -{- All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - module Distribution.Simple.UserHooks ( UserHooks(..), Args, emptyUserHooks, diff --git a/Cabal/Distribution/Simple/Utils.hs b/Cabal/Distribution/Simple/Utils.hs index 0c6e0f9af9807910938104f259a8c68b48861a47..247ffc08a189c39362256422f313e7211e0cbf22 100644 --- a/Cabal/Distribution/Simple/Utils.hs +++ b/Cabal/Distribution/Simple/Utils.hs @@ -3,6 +3,7 @@ -- | -- Module : Distribution.Simple.Utils -- Copyright : Isaac Jones, Simon Marlow 2003-2004 +-- License : BSD3 -- portions Copyright (c) 2007, Galois Inc. -- -- Maintainer : cabal-devel@haskell.org @@ -14,36 +15,6 @@ -- has low level functions for running programs, a bunch of wrappers for -- various directory and file functions that do extra logging. -{- All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - module Distribution.Simple.Utils ( cabalVersion, diff --git a/Cabal/Distribution/TestSuite.hs b/Cabal/Distribution/TestSuite.hs index 461f4e58dd8df3116be87d987b5e7d044eb13099..91ddfc1f3b5f192783c5a8b7473375a1204e7a3c 100644 --- a/Cabal/Distribution/TestSuite.hs +++ b/Cabal/Distribution/TestSuite.hs @@ -2,6 +2,7 @@ -- | -- Module : Distribution.TestSuite -- Copyright : Thomas Tuegel 2010 +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Portability : portable @@ -9,36 +10,6 @@ -- This module defines the detailed test suite interface which makes it -- possible to expose individual tests to Cabal or other test agents. -{- All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - module Distribution.TestSuite ( TestInstance(..) , OptionDescr(..) diff --git a/Cabal/Distribution/Verbosity.hs b/Cabal/Distribution/Verbosity.hs index 1e0d62e703cfb325286e03db9d65f99ef0e8370c..6cae83b3b717d0dc4024b873e7b229310948d4f3 100644 --- a/Cabal/Distribution/Verbosity.hs +++ b/Cabal/Distribution/Verbosity.hs @@ -2,6 +2,7 @@ -- | -- Module : Distribution.Verbosity -- Copyright : Ian Lynagh 2007 +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Portability : portable @@ -10,38 +11,7 @@ -- verbosity levels from 'silent', 'normal', 'verbose' up to 'deafening'. This -- is used for deciding what logging messages to print. --- Verbosity for Cabal functions - -{- Copyright (c) 2007, Ian Lynagh -All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} +-- Verbosity for Cabal functions. module Distribution.Verbosity ( -- * Verbosity diff --git a/Cabal/Distribution/Version.hs b/Cabal/Distribution/Version.hs index a723909094279041e7aea0700eaa84d662ffdb86..7b42aed667ea13976109faad9d9770df6d352d2d 100644 --- a/Cabal/Distribution/Version.hs +++ b/Cabal/Distribution/Version.hs @@ -4,6 +4,7 @@ -- Module : Distribution.Version -- Copyright : Isaac Jones, Simon Marlow 2003-2004 -- Duncan Coutts 2008 +-- License : BSD3 -- -- Maintainer : cabal-devel@haskell.org -- Portability : portable @@ -12,37 +13,6 @@ -- is something like @\"1.3.3\"@. It also defines the 'VersionRange' data -- types. Version ranges are like @\">= 1.2 && < 2\"@. -{- Copyright (c) 2003-2004, Isaac Jones -All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - module Distribution.Version ( -- * Package versions Version(..), diff --git a/Cabal/LICENSE b/Cabal/LICENSE index aa3f9182257c39b9211c369dda5c5b412d73f449..1193d3b8d0f336eddb8eeb3a7b875cdfc542b993 100644 --- a/Cabal/LICENSE +++ b/Cabal/LICENSE @@ -1,7 +1,8 @@ -Copyright (c) 2003-2008, Isaac Jones, Simon Marlow, Martin Sjögren, +Copyright (c) 2003-2014, Isaac Jones, Simon Marlow, Martin Sjögren, Bjorn Bringert, Krasimir Angelov, Malcolm Wallace, Ross Patterson, Ian Lynagh, - Duncan Coutts, Thomas Schilling + Duncan Coutts, Thomas Schilling, + Johan Tibell, Mikhail Glushenkov All rights reserved. Redistribution and use in source and binary forms, with or without diff --git a/Cabal/Language/Haskell/Extension.hs b/Cabal/Language/Haskell/Extension.hs index 809bce26776cd0b4380879edd8864723f85e472e..a4a5a67ce976719e785d84f34ab325f38433186e 100644 --- a/Cabal/Language/Haskell/Extension.hs +++ b/Cabal/Language/Haskell/Extension.hs @@ -3,42 +3,13 @@ -- | -- Module : Language.Haskell.Extension -- Copyright : Isaac Jones 2003-2004 +-- License : BSD3 -- -- Maintainer : libraries@haskell.org -- Portability : portable -- -- Haskell language dialects and extensions -{- All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Isaac Jones nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} - module Language.Haskell.Extension ( Language(..), knownLanguages, diff --git a/Cabal/Makefile b/Cabal/Makefile index 7d6b69e65edc3a3877365b421831bf8b7d66dc70..a359e74ad9a01e6ded64e5eed11bc864ef1bdde0 100644 --- a/Cabal/Makefile +++ b/Cabal/Makefile @@ -7,7 +7,7 @@ KIND=rc PREFIX=/usr/local HC=ghc -GHCFLAGS=-Wall +GHCFLAGS=-Wall -threaded SSH_USER=$USER all: build diff --git a/Cabal/README b/Cabal/README index e39d32a8c5dcbda87c260f50e8bd00c983c4250c..902c3748cf91cb50db95a6a1b9dddef93f7bda38 100644 --- a/Cabal/README +++ b/Cabal/README @@ -24,7 +24,7 @@ this bootstrapping problem, you can install the Cabal library directly: Installing as a user (no root or administrator access) ------------------------------------------------------ - ghc --make Setup + ghc -threaded --make Setup ./Setup configure --user ./Setup build ./Setup install @@ -43,7 +43,7 @@ configure step. Installing as root / Administrator ---------------------------------- - ghc --make Setup + ghc -threaded --make Setup ./Setup configure ./Setup build sudo ./Setup install diff --git a/Cabal/doc/developing-packages.markdown b/Cabal/doc/developing-packages.markdown index 15a59f6d71a6c8e0ded2ca065e83a41f5db22f93..fdc0e2b4605c6d57111cd6d42e87d3d693f6bf82 100644 --- a/Cabal/doc/developing-packages.markdown +++ b/Cabal/doc/developing-packages.markdown @@ -18,9 +18,7 @@ Proglet.hs It is assumed that (apart from external dependencies) all the files that make up a package live under a common project root directory. This simple example has all the project files in one directory, but most -packages will use one or more subdirectories. See section [TODO](#TODO) -for the standard practices for organising the files in your project -directory. +packages will use one or more subdirectories. To turn this into a Cabal package we need two extra files in the project's root directory: @@ -655,8 +653,8 @@ several sections. information](#build-information). * Following is an arbitrary number of executable sections - which describe an [executable program](#executable) and relevant - [build information](#build-information). + which describe an executable program and relevant [build + information](#build-information). Each section consists of a number of property descriptions in the form of field/value pairs, with a syntax roughly like mail @@ -724,8 +722,7 @@ These fields may occur in the first top-level properties section and describe the package as a whole: `name:` _package-name_ (required) -: The unique name of the [package](#packages), without the version - number. +: The unique name of the package, without the version number. `version:` _numbers_ (required) : The package version number, usually consisting of a sequence of @@ -792,8 +789,8 @@ describe the package as a whole: ~~~~~~~~~~~~~~~~ For build type `Make` (see the section on [more complex - packages](#more-complex-packages) below), the contents of - `Setup.hs` must be: + packages](installing-packages.html#more-complex-packages) below), + the contents of `Setup.hs` must be: ~~~~~~~~~~~~~~~~ import Distribution.Make @@ -866,8 +863,8 @@ describe the package as a whole: package before. For library packages, this field is used as prologue text by [`setup - haddock`](#setup-haddock), and thus may contain the same markup as - [haddock][] documentation comments. + haddock`](installing-packages.html#setup-haddock), and thus may + contain the same markup as [haddock][] documentation comments. `category:` _freeform_ : A classification category for future use by the package catalogue [Hackage]. These @@ -910,8 +907,9 @@ describe the package as a whole: `extra-source-files:` _filename list_ : A list of additional files to be included in source distributions - built with [`setup sdist`](#setup-sdist). As with `data-files` it - can use a limited form of `*` wildcards in file names. + built with [`setup sdist`](installing-packages.html#setup-sdist). As + with `data-files` it can use a limited form of `*` wildcards in file + names. `extra-doc-files:` _filename list_ : A list of additional files to be included in source distributions, @@ -921,9 +919,10 @@ describe the package as a whole: `extra-tmp-files:` _filename list_ : A list of additional files or directories to be removed by [`setup - clean`](#setup-clean). These would typically be additional files - created by additional hooks, such as the scheme described in the - section on [system-dependent parameters](#system-dependent-parameters). + clean`](installing-packages.html#setup-clean). These would typically + be additional files created by additional hooks, such as the scheme + described in the section on [system-dependent + parameters](#system-dependent-parameters). ### Library ### @@ -1536,12 +1535,12 @@ following fields. : The default value of this flag. Note that this value may be [overridden in several - ways](#controlling-flag-assignments"). The rationale for having - flags default to True is that users usually want new features as - soon as they are available. Flags representing features that are not - (yet) recommended for most users (such as experimental features or - debugging support) should therefore explicitly override the default - to False. + ways](installing-packages.html#controlling-flag-assignments"). The + rationale for having flags default to True is that users usually + want new features as soon as they are available. Flags representing + features that are not (yet) recommended for most users (such as + experimental features or debugging support) should therefore + explicitly override the default to False. `manual:` _boolean_ (default: `False`) : By default, Cabal will first try to satisfy dependencies with the @@ -1828,9 +1827,9 @@ The `get` command supports the following options: The placement on the target system of files listed in the `data-files` field varies between systems, and in some cases one can even move packages around after installation (see [prefix -independence](#prefix-independence)). To enable packages to find these -files in a portable way, Cabal generates a module called -`Paths_`_pkgname_ (with any hyphens in _pkgname_ replaced by +independence](installing-packages.html#prefix-independence)). To enable +packages to find these files in a portable way, Cabal generates a module +called `Paths_`_pkgname_ (with any hyphens in _pkgname_ replaced by underscores) during building, so that it may be imported by modules of the package. This module defines a function @@ -2097,27 +2096,27 @@ a few options: * Finally, with the `build-type` `Custom`, you can also write your own setup script from scratch. It must conform to the interface described in the section on [building and installing - packages](#building-and-installing-a-package), and you may use the - Cabal library for all or part of the work. One option is to copy - the source of `Distribution.Simple`, and alter it for your needs. - Good luck. + packages](installing-packages.html), and you may use the Cabal + library for all or part of the work. One option is to copy the + source of `Distribution.Simple`, and alter it for your needs. Good + luck. -[dist-simple]: ../libraries/Cabal/Distribution-Simple.html -[dist-make]: ../libraries/Cabal/Distribution-Make.html -[dist-license]: ../libraries/Cabal/Distribution-License.html#t:License -[extension]: ../libraries/Cabal/Language-Haskell-Extension.html#t:Extension -[BuildType]: ../libraries/Cabal/Distribution-PackageDescription.html#t:BuildType +[dist-simple]: ../release/cabal-latest/doc/API/Cabal/Distribution-Simple.html +[dist-make]: ../release/cabal-latest/doc/API/Cabal/Distribution-Make.html +[dist-license]: ../release/cabal-latest/doc/API/Cabal/Distribution-License.html#t:License +[extension]: ../release/cabal-latest/doc/API/Cabal/Language-Haskell-Extension.html#t:Extension +[BuildType]: ../release/cabal-latest/doc/API/Cabal/Distribution-PackageDescription.html#t:BuildType [data-version]: http://hackage.haskell.org/packages/archive/base/latest/doc/html/Data-Version.html [alex]: http://www.haskell.org/alex/ [autoconf]: http://www.gnu.org/software/autoconf/ [c2hs]: http://www.cse.unsw.edu.au/~chak/haskell/c2hs/ -[cpphs]: http://www.haskell.org/cpphs/ -[greencard]: http://www.haskell.org/greencard/ +[cpphs]: http://projects.haskell.org/cpphs/ +[greencard]: http://hackage.haskell.org/package/greencard [haddock]: http://www.haskell.org/haddock/ [HsColour]: http://www.cs.york.ac.uk/fp/darcs/hscolour/ [happy]: http://www.haskell.org/happy/ [Hackage]: http://hackage.haskell.org/ -[pkg-config]: http://pkg-config.freedesktop.org/ +[pkg-config]: http://www.freedesktop.org/wiki/Software/pkg-config/ [REPL]: http://en.wikipedia.org/wiki/Read%E2%80%93eval%E2%80%93print_loop diff --git a/Cabal/doc/index.markdown b/Cabal/doc/index.markdown index 87bbf8525247306ae2520c0c19ad62b32da41336..4a4a0b7b7317ef0e57bbe08ac8bb015d9340df90 100644 --- a/Cabal/doc/index.markdown +++ b/Cabal/doc/index.markdown @@ -19,7 +19,6 @@ thousands of libraries and applications in the Cabal package format. - [A tool for working with packages](#a-tool-for-working-with-packages) * [Building, installing and managing packages](installing-packages.html) * [Creating packages](developing-packages.html) - * [Cabal specification, design and implementation]() * [Reporting bugs and deficiencies](misc.html#reporting-bugs-and-deficiencies) * [Stability of Cabal interfaces](misc.html#stability-of-cabal-interfaces) diff --git a/Cabal/doc/installing-packages.markdown b/Cabal/doc/installing-packages.markdown index 3d66adab0c7839f2ce7ab6b5b696e3791faa98e9..87b3f0836fc2a7d3d1fb34d246becc150b46da88 100644 --- a/Cabal/doc/installing-packages.markdown +++ b/Cabal/doc/installing-packages.markdown @@ -267,12 +267,13 @@ infrastructure, the values supplied via these options are recorded in a private file read by later stages. If a user-supplied `configure` script is run (see the section on -[system-dependent parameters](#system-dependent-parameters) or on -[complex packages](#complex-packages)), it is passed the -`--with-hc-pkg`, `--prefix`, `--bindir`, `--libdir`, `--datadir`, `--libexecdir` -and `--sysconfdir` options. In addition the value of the `--with-compiler` -option is passed in a `--with-hc` option and all options specified with -`--configure-option=` are passed on. +[system-dependent +parameters](developing-packages.html#system-dependent-parameters) or on +[complex packages](developing-packages.html#more-complex-packages)), it +is passed the `--with-hc-pkg`, `--prefix`, `--bindir`, `--libdir`, +`--datadir`, `--libexecdir` and `--sysconfdir` options. In addition the +value of the `--with-compiler` option is passed in a `--with-hc` option +and all options specified with `--configure-option=` are passed on. ### Programs used for building ### @@ -528,8 +529,9 @@ have baked-in all absolute paths. The application need do nothing special to achieve prefix-independence. If it finds any files using `getDataFileName` and the [other functions -provided for the purpose](#accessing-data-files-from-package-code), the -files will be accessed relative to the location of the current +provided for the +purpose](developing-packages.html#accessing-data-files-from-package-code), +the files will be accessed relative to the location of the current executable. A library cannot (currently) be prefix-independent, because it will be @@ -539,8 +541,8 @@ to the library package. ### Controlling Flag Assignments ### Flag assignments (see the [resolution of conditions and -flags](#resolution-of-conditions-and-flags)) can be controlled with the -followingcommand line options. +flags](developing-packages.html#resolution-of-conditions-and-flags)) can +be controlled with the following command line options. `-f` _flagname_ or `-f` `-`_flagname_ : Force the specified flag to `true` or `false` (if preceded with a `-`). Later @@ -685,8 +687,8 @@ followingcommand line options. `--configure-option=`_str_ : An extra option to an external `configure` script, if one is used (see the section on [system-dependent - parameters](#system-dependent-parameters)). There can be several of - these options. + parameters](developing-packages.html#system-dependent-parameters)). + There can be several of these options. `--extra-include-dirs`[=_dir_] : An extra directory to search for C header files. You can use this @@ -1019,18 +1021,18 @@ This command takes the following option: the generated source package. The original package is unaffected. -[dist-simple]: ../libraries/Cabal/Distribution-Simple.html -[dist-make]: ../libraries/Cabal/Distribution-Make.html -[dist-license]: ../libraries/Cabal/Distribution-License.html#t:License -[extension]: ../libraries/Cabal/Language-Haskell-Extension.html#t:Extension -[BuildType]: ../libraries/Cabal/Distribution-PackageDescription.html#t:BuildType +[dist-simple]: ../release/cabal-latest/doc/API/Cabal/Distribution-Simple.html +[dist-make]: ../release/cabal-latest/doc/API/Cabal/Distribution-Make.html +[dist-license]: ../release/cabal-latest/doc/API/Cabal/Distribution-License.html#t:License +[extension]: ../release/cabal-latest/doc/API/Cabal/Language-Haskell-Extension.html#t:Extension +[BuildType]: ../release/cabal-latest/doc/API/Cabal/Distribution-PackageDescription.html#t:BuildType [alex]: http://www.haskell.org/alex/ [autoconf]: http://www.gnu.org/software/autoconf/ [c2hs]: http://www.cse.unsw.edu.au/~chak/haskell/c2hs/ -[cpphs]: http://www.haskell.org/cpphs/ -[greencard]: http://www.haskell.org/greencard/ +[cpphs]: http://projects.haskell.org/cpphs/ +[greencard]: http://hackage.haskell.org/package/greencard [haddock]: http://www.haskell.org/haddock/ [HsColour]: http://www.cs.york.ac.uk/fp/darcs/hscolour/ [happy]: http://www.haskell.org/happy/ [Hackage]: http://hackage.haskell.org/ -[pkg-config]: http://pkg-config.freedesktop.org/ +[pkg-config]: http://www.freedesktop.org/wiki/Software/pkg-config/ diff --git a/Cabal/doc/misc.markdown b/Cabal/doc/misc.markdown index 980bf9639203a0e6605efd3c0e666a56552785fa..8d732edcea9892f8276c4e1229f00ed80f74c576 100644 --- a/Cabal/doc/misc.markdown +++ b/Cabal/doc/misc.markdown @@ -61,7 +61,7 @@ the API are more prone to change than others. The rest of this section gives some informal advice on what level of API stability you can expect between major releases. -[PVP]: http://haskell.org/haskellwiki/Package_versioning_policy +[PVP]: http://www.haskell.org/haskellwiki/Package_versioning_policy ### Very Stable API ### @@ -92,18 +92,18 @@ file. Incompatible revisions to the format would involve bumping the name of the index file, i.e., `00-index.tar.gz`, `01-index.tar.gz` etc. -[dist-simple]: ../libraries/Cabal/Distribution-Simple.html -[dist-make]: ../libraries/Cabal/Distribution-Make.html -[dist-license]: ../libraries/Cabal/Distribution-License.html#t:License -[extension]: ../libraries/Cabal/Language-Haskell-Extension.html#t:Extension -[BuildType]: ../libraries/Cabal/Distribution-PackageDescription.html#t:BuildType +[dist-simple]: ../release/cabal-latest/doc/API/Cabal/Distribution-Simple.html +[dist-make]: ../release/cabal-latest/doc/API/Cabal/Distribution-Make.html +[dist-license]: ../release/cabal-latest/doc/API/Cabal/Distribution-License.html#t:License +[extension]: ../release/cabal-latest/doc/API/Cabal/Language-Haskell-Extension.html#t:Extension +[BuildType]: ../release/cabal-latest/doc/API/Cabal/Distribution-PackageDescription.html#t:BuildType [alex]: http://www.haskell.org/alex/ [autoconf]: http://www.gnu.org/software/autoconf/ [c2hs]: http://www.cse.unsw.edu.au/~chak/haskell/c2hs/ -[cpphs]: http://www.haskell.org/cpphs/ -[greencard]: http://www.haskell.org/greencard/ +[cpphs]: http://projects.haskell.org/cpphs/ +[greencard]: http://hackage.haskell.org/package/greencard [haddock]: http://www.haskell.org/haddock/ [HsColour]: http://www.cs.york.ac.uk/fp/darcs/hscolour/ [happy]: http://www.haskell.org/happy/ -[HackageDB]: http://hackage.haskell.org/ -[pkg-config]: http://pkg-config.freedesktop.org/ +[Hackage]: http://hackage.haskell.org/ +[pkg-config]: http://www.freedesktop.org/wiki/Software/pkg-config/ diff --git a/Cabal/tests/Distribution/Compat/CreatePipe.hsc b/Cabal/tests/Distribution/Compat/CreatePipe.hsc deleted file mode 100644 index afacbda4317e6073f855da42905408aeed99c754..0000000000000000000000000000000000000000 --- a/Cabal/tests/Distribution/Compat/CreatePipe.hsc +++ /dev/null @@ -1,55 +0,0 @@ -{-# LANGUAGE CPP, ForeignFunctionInterface #-} -module Distribution.Compat.CreatePipe (createPipe) where - -import System.IO (Handle) - -#if !(defined(_MSC_VER) || defined(__MINGW32__) || defined(_WIN32)) -import System.Posix.IO (fdToHandle) -import qualified System.Posix.IO as Posix -#else -# include <io.h> /* for _close and _pipe */ -# include <fcntl.h> /* for _O_BINARY */ -import Control.Exception (onException) -import Foreign.C.Error (throwErrnoIfMinus1_) -import Foreign.C.Types (CInt(..), CUInt(..)) -import Foreign.Ptr (Ptr) -import Foreign.Marshal.Array (allocaArray) -import Foreign.Storable (peek, peekElemOff) -import GHC.IO.FD (mkFD) -import GHC.IO.Device (IODeviceType(Stream)) -import GHC.IO.Handle.FD (mkHandleFromFD) -import System.IO (IOMode(ReadMode, WriteMode)) -#endif - -createPipe :: IO (Handle, Handle) -#if !(defined(_MSC_VER) || defined(__MINGW32__) || defined(_WIN32)) -createPipe = do - (readfd, writefd) <- Posix.createPipe - readh <- fdToHandle readfd - writeh <- fdToHandle writefd - return (readh, writeh) -#else -createPipe = do - (readfd, writefd) <- allocaArray 2 $ \ pfds -> do - throwErrnoIfMinus1_ "_pipe" $ c__pipe pfds 2 (#const _O_BINARY) - readfd <- peek pfds - writefd <- peekElemOff pfds 1 - return (readfd, writefd) - (do readh <- fdToHandle readfd ReadMode - writeh <- fdToHandle writefd WriteMode - return (readh, writeh)) `onException` (close readfd >> close writefd) - -fdToHandle :: CInt -> IOMode -> IO Handle -fdToHandle fd mode = do - (fd', deviceType) <- mkFD fd mode (Just (Stream, 0, 0)) False False - mkHandleFromFD fd' deviceType "" mode False Nothing - -close :: CInt -> IO () -close = throwErrnoIfMinus1_ "_close" . c__close - -foreign import ccall "io.h _pipe" c__pipe :: - Ptr CInt -> CUInt -> CInt -> IO CInt - -foreign import ccall "io.h _close" c__close :: - CInt -> IO CInt -#endif diff --git a/Cabal/tests/PackageTests.hs b/Cabal/tests/PackageTests.hs index 437e8c84fcc540a38262bd5f8f53a06c07d7083a..691dc1ec43a3ab6264a08604f3301246505a04cc 100644 --- a/Cabal/tests/PackageTests.hs +++ b/Cabal/tests/PackageTests.hs @@ -49,6 +49,7 @@ import System.Directory (doesFileExist, getCurrentDirectory, setCurrentDirectory) import System.Environment (getEnv) import System.FilePath ((</>)) +import System.IO (BufferMode(NoBuffering), hSetBuffering, stdout) import Test.Framework (Test, TestName, defaultMain, testGroup) import Test.Framework.Providers.HUnit (hUnitTestToTests) import qualified Test.HUnit as HUnit @@ -124,6 +125,10 @@ tests version inplaceSpec ghcPath ghcPkgPath = main :: IO () main = do + -- WORKAROUND: disable buffering on stdout to get streaming test logs + -- test providers _should_ do this themselves + hSetBuffering stdout NoBuffering + wd <- getCurrentDirectory let dbFile = wd </> "dist/package.conf.inplace" inplaceSpec = PackageSpec diff --git a/Cabal/tests/UnitTests.hs b/Cabal/tests/UnitTests.hs index 36b68ce5946f5f9a6d47ebda3505c451804567b5..3a13ee533e8f9dc16b76aae3296d75e7e4bc1f80 100644 --- a/Cabal/tests/UnitTests.hs +++ b/Cabal/tests/UnitTests.hs @@ -2,6 +2,7 @@ module Main ( main ) where +import System.IO (BufferMode(NoBuffering), hSetBuffering, stdout) import Test.Framework import qualified UnitTests.Distribution.Compat.ReadP @@ -13,4 +14,8 @@ tests = [ ] main :: IO () -main = defaultMain tests +main = do + -- WORKAROUND: disable buffering on stdout to get streaming test logs + -- test providers _should_ do this themselves + hSetBuffering stdout NoBuffering + defaultMain tests diff --git a/cabal-install/Distribution/Client/Init.hs b/cabal-install/Distribution/Client/Init.hs index 05e64083e4289ae593a72f8123f5ac925329c971..21fbbaabf99230656ab7b0c2e9e1c141dd1e7504 100644 --- a/cabal-install/Distribution/Client/Init.hs +++ b/cabal-install/Distribution/Client/Init.hs @@ -67,7 +67,7 @@ import Language.Haskell.Extension ( Language(..) ) import Distribution.Client.Init.Types ( InitFlags(..), PackageType(..), Category(..) ) import Distribution.Client.Init.Licenses - ( bsd2, bsd3, gplv2, gplv3, lgpl2, lgpl3, agplv3, apache20, mpl20 ) + ( bsd2, bsd3, gplv2, gplv3, lgpl21, lgpl3, agplv3, apache20, mit, mpl20 ) import Distribution.Client.Init.Heuristics ( guessPackageName, guessAuthorNameMail, SourceFileEntry(..), scanForModules, neededBuildPrograms ) @@ -154,7 +154,7 @@ getPackageName flags = do ?>> Just `fmap` (getCurrentDirectory >>= guessPackageName) pkgName' <- return (flagToMaybe $ packageName flags) - ?>> maybePrompt flags (promptStr "Package name" guess) + ?>> maybePrompt flags (prompt "Package name" guess) ?>> return guess return $ flags { packageName = maybeToFlag pkgName' } @@ -550,8 +550,8 @@ writeLicense flags = do Flag (GPL (Just (Version {versionBranch = [3]}))) -> Just gplv3 - Flag (LGPL (Just (Version {versionBranch = [2]}))) - -> Just lgpl2 + Flag (LGPL (Just (Version {versionBranch = [2, 1]}))) + -> Just lgpl21 Flag (LGPL (Just (Version {versionBranch = [3]}))) -> Just lgpl3 @@ -562,6 +562,9 @@ writeLicense flags = do Flag (Apache (Just (Version {versionBranch = [2, 0]}))) -> Just apache20 + Flag MIT + -> Just $ mit authors year + Flag (MPL (Version {versionBranch = [2, 0]})) -> Just mpl20 @@ -594,7 +597,7 @@ writeCabalFile flags@(InitFlags{packageName = NoFlag}) = do message flags "Error: no package name provided." return False writeCabalFile flags@(InitFlags{packageName = Flag p}) = do - let cabalFileName = p ++ ".cabal" + let cabalFileName = display p ++ ".cabal" message flags $ "Generating " ++ cabalFileName ++ "..." writeFileSafe flags cabalFileName (generateCabalFile cabalFileName flags) return True @@ -644,7 +647,7 @@ generateCabalFile fileName c = $$ text "" else empty) $$ - vcat [ fieldS "name" (packageName c) + vcat [ field "name" (packageName c) (Just "The name of the package.") True @@ -709,7 +712,9 @@ generateCabalFile fileName c = , case packageType c of Flag Executable -> - text "\nexecutable" <+> text (fromMaybe "" . flagToMaybe $ packageName c) $$ nest 2 (vcat + text "\nexecutable" <+> + text (maybe "" display . flagToMaybe $ packageName c) $$ + nest 2 (vcat [ fieldS "main-is" NoFlag (Just ".hs or .lhs file containing the Main module.") True , generateBuildInfo Executable c diff --git a/cabal-install/Distribution/Client/Init/Heuristics.hs b/cabal-install/Distribution/Client/Init/Heuristics.hs index de42bb95f1990d0262530d896ecbd73ba9ac3ffd..ae589f1d2910db91c0dca79f788123ccce83f1b3 100644 --- a/cabal-install/Distribution/Client/Init/Heuristics.hs +++ b/cabal-install/Distribution/Client/Init/Heuristics.hs @@ -24,6 +24,7 @@ import Distribution.ModuleName ( ModuleName, toFilePath ) import Distribution.Client.PackageIndex ( allPackagesByName ) +import qualified Distribution.Package as P import qualified Distribution.PackageDescription as PD ( category, packageDescription ) import Distribution.Simple.Utils @@ -34,8 +35,9 @@ import Language.Haskell.Extension ( Extension ) import Distribution.Client.Types ( packageDescription, SourcePackageDb(..) ) import Control.Applicative ( pure, (<$>), (<*>) ) +import Control.Arrow ( first ) import Control.Monad ( liftM ) -import Data.Char ( isUpper, isLower, isSpace ) +import Data.Char ( isAlphaNum, isNumber, isUpper, isLower, isSpace ) import Data.Either ( partitionEithers ) import Data.List ( isPrefixOf ) import Data.Maybe ( mapMaybe, catMaybes, maybeToList ) @@ -50,9 +52,26 @@ import System.FilePath ( takeExtension, takeBaseName, dropExtension, import Distribution.Client.Compat.Process ( readProcessWithExitCode ) import System.Exit ( ExitCode(..) ) --- |Guess the package name based on the given root directory -guessPackageName :: FilePath -> IO String -guessPackageName = liftM (last . splitDirectories) . tryCanonicalizePath +-- | Guess the package name based on the given root directory. +guessPackageName :: FilePath -> IO P.PackageName +guessPackageName = liftM (P.PackageName . repair . last . splitDirectories) + . tryCanonicalizePath + where + -- Treat each span of non-alphanumeric characters as a hyphen. Each + -- hyphenated component of a package name must contain at least one + -- alphabetic character. An arbitrary character ('x') will be prepended if + -- this is not the case for the first component, and subsequent components + -- will simply be run together. For example, "1+2_foo-3" will become + -- "x12-foo3". + repair = repair' ('x' :) id + repair' invalid valid x = case dropWhile (not . isAlphaNum) x of + "" -> repairComponent "" + x' -> let (c, r) = first repairComponent $ break (not . isAlphaNum) x' + in c ++ repairRest r + where + repairComponent c | all isNumber c = invalid c + | otherwise = valid c + repairRest = repair' id ('-' :) -- |Data type of source files found in the working directory data SourceFileEntry = SourceFileEntry diff --git a/cabal-install/Distribution/Client/Init/Licenses.hs b/cabal-install/Distribution/Client/Init/Licenses.hs index a13be33b3121a612a5f542b95c2e12ec3db14a3f..0feb95a61916dcbffa453f96dedb608708c79656 100644 --- a/cabal-install/Distribution/Client/Init/Licenses.hs +++ b/cabal-install/Distribution/Client/Init/Licenses.hs @@ -4,10 +4,11 @@ module Distribution.Client.Init.Licenses , bsd3 , gplv2 , gplv3 - , lgpl2 + , lgpl21 , lgpl3 , agplv3 , apache20 + , mit , mpl20 ) where @@ -1764,117 +1765,130 @@ agplv3 = unlines , "<http://www.gnu.org/licenses/>." ] -lgpl2 :: License -lgpl2 = unlines - [ " GNU LIBRARY GENERAL PUBLIC LICENSE" - , " Version 2, June 1991" +lgpl21 :: License +lgpl21 = unlines + [ " GNU LESSER GENERAL PUBLIC LICENSE" + , " Version 2.1, February 1999" , "" - , " Copyright (C) 1991 Free Software Foundation, Inc." + , " Copyright (C) 1991, 1999 Free Software Foundation, Inc." , " 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA" , " Everyone is permitted to copy and distribute verbatim copies" , " of this license document, but changing it is not allowed." , "" - , "[This is the first released version of the library GPL. It is" - , " numbered 2 because it goes with version 2 of the ordinary GPL.]" + , "[This is the first released version of the Lesser GPL. It also counts" + , " as the successor of the GNU Library Public License, version 2, hence" + , " the version number 2.1.]" , "" - , " Preamble" + , " Preamble" , "" , " The licenses for most software are designed to take away your" , "freedom to share and change it. By contrast, the GNU General Public" , "Licenses are intended to guarantee your freedom to share and change" , "free software--to make sure the software is free for all its users." , "" - , " This license, the Library General Public License, applies to some" - , "specially designated Free Software Foundation software, and to any" - , "other libraries whose authors decide to use it. You can use it for" - , "your libraries, too." - , "" - , " When we speak of free software, we are referring to freedom, not" - , "price. Our General Public Licenses are designed to make sure that you" - , "have the freedom to distribute copies of free software (and charge for" - , "this service if you wish), that you receive source code or can get it" - , "if you want it, that you can change the software or use pieces of it" - , "in new free programs; and that you know you can do these things." + , " This license, the Lesser General Public License, applies to some" + , "specially designated software packages--typically libraries--of the" + , "Free Software Foundation and other authors who decide to use it. You" + , "can use it too, but we suggest you first think carefully about whether" + , "this license or the ordinary General Public License is the better" + , "strategy to use in any particular case, based on the explanations below." + , "" + , " When we speak of free software, we are referring to freedom of use," + , "not price. Our General Public Licenses are designed to make sure that" + , "you have the freedom to distribute copies of free software (and charge" + , "for this service if you wish); that you receive source code or can get" + , "it if you want it; that you can change the software and use pieces of" + , "it in new free programs; and that you are informed that you can do" + , "these things." , "" , " To protect your rights, we need to make restrictions that forbid" - , "anyone to deny you these rights or to ask you to surrender the rights." - , "These restrictions translate to certain responsibilities for you if" - , "you distribute copies of the library, or if you modify it." + , "distributors to deny you these rights or to ask you to surrender these" + , "rights. These restrictions translate to certain responsibilities for" + , "you if you distribute copies of the library or if you modify it." , "" , " For example, if you distribute copies of the library, whether gratis" , "or for a fee, you must give the recipients all the rights that we gave" , "you. You must make sure that they, too, receive or can get the source" - , "code. If you link a program with the library, you must provide" - , "complete object files to the recipients so that they can relink them" - , "with the library, after making changes to the library and recompiling" + , "code. If you link other code with the library, you must provide" + , "complete object files to the recipients, so that they can relink them" + , "with the library after making changes to the library and recompiling" , "it. And you must show them these terms so they know their rights." , "" - , " Our method of protecting your rights has two steps: (1) copyright" - , "the library, and (2) offer you this license which gives you legal" + , " We protect your rights with a two-step method: (1) we copyright the" + , "library, and (2) we offer you this license, which gives you legal" , "permission to copy, distribute and/or modify the library." , "" - , " Also, for each distributor's protection, we want to make certain" - , "that everyone understands that there is no warranty for this free" - , "library. If the library is modified by someone else and passed on, we" - , "want its recipients to know that what they have is not the original" - , "version, so that any problems introduced by others will not reflect on" - , "the original authors' reputations." - , "" - , " Finally, any free program is threatened constantly by software" - , "patents. We wish to avoid the danger that companies distributing free" - , "software will individually obtain patent licenses, thus in effect" - , "transforming the program into proprietary software. To prevent this," - , "we have made it clear that any patent must be licensed for everyone's" - , "free use or not licensed at all." - , "" - , " Most GNU software, including some libraries, is covered by the ordinary" - , "GNU General Public License, which was designed for utility programs. This" - , "license, the GNU Library General Public License, applies to certain" - , "designated libraries. This license is quite different from the ordinary" - , "one; be sure to read it in full, and don't assume that anything in it is" - , "the same as in the ordinary license." - , "" - , " The reason we have a separate public license for some libraries is that" - , "they blur the distinction we usually make between modifying or adding to a" - , "program and simply using it. Linking a program with a library, without" - , "changing the library, is in some sense simply using the library, and is" - , "analogous to running a utility program or application program. However, in" - , "a textual and legal sense, the linked executable is a combined work, a" - , "derivative of the original library, and the ordinary General Public License" - , "treats it as such." - , "" - , " Because of this blurred distinction, using the ordinary General" - , "Public License for libraries did not effectively promote software" - , "sharing, because most developers did not use the libraries. We" - , "concluded that weaker conditions might promote sharing better." - , "" - , " However, unrestricted linking of non-free programs would deprive the" - , "users of those programs of all benefit from the free status of the" - , "libraries themselves. This Library General Public License is intended to" - , "permit developers of non-free programs to use free libraries, while" - , "preserving your freedom as a user of such programs to change the free" - , "libraries that are incorporated in them. (We have not seen how to achieve" - , "this as regards changes in header files, but we have achieved it as regards" - , "changes in the actual functions of the Library.) The hope is that this" - , "will lead to faster development of free libraries." + , " To protect each distributor, we want to make it very clear that" + , "there is no warranty for the free library. Also, if the library is" + , "modified by someone else and passed on, the recipients should know" + , "that what they have is not the original version, so that the original" + , "author's reputation will not be affected by problems that might be" + , "introduced by others." + , "" + , " Finally, software patents pose a constant threat to the existence of" + , "any free program. We wish to make sure that a company cannot" + , "effectively restrict the users of a free program by obtaining a" + , "restrictive license from a patent holder. Therefore, we insist that" + , "any patent license obtained for a version of the library must be" + , "consistent with the full freedom of use specified in this license." + , "" + , " Most GNU software, including some libraries, is covered by the" + , "ordinary GNU General Public License. This license, the GNU Lesser" + , "General Public License, applies to certain designated libraries, and" + , "is quite different from the ordinary General Public License. We use" + , "this license for certain libraries in order to permit linking those" + , "libraries into non-free programs." + , "" + , " When a program is linked with a library, whether statically or using" + , "a shared library, the combination of the two is legally speaking a" + , "combined work, a derivative of the original library. The ordinary" + , "General Public License therefore permits such linking only if the" + , "entire combination fits its criteria of freedom. The Lesser General" + , "Public License permits more lax criteria for linking other code with" + , "the library." + , "" + , " We call this license the \"Lesser\" General Public License because it" + , "does Less to protect the user's freedom than the ordinary General" + , "Public License. It also provides other free software developers Less" + , "of an advantage over competing non-free programs. These disadvantages" + , "are the reason we use the ordinary General Public License for many" + , "libraries. However, the Lesser license provides advantages in certain" + , "special circumstances." + , "" + , " For example, on rare occasions, there may be a special need to" + , "encourage the widest possible use of a certain library, so that it becomes" + , "a de-facto standard. To achieve this, non-free programs must be" + , "allowed to use the library. A more frequent case is that a free" + , "library does the same job as widely used non-free libraries. In this" + , "case, there is little to gain by limiting the free library to free" + , "software only, so we use the Lesser General Public License." + , "" + , " In other cases, permission to use a particular library in non-free" + , "programs enables a greater number of people to use a large body of" + , "free software. For example, permission to use the GNU C Library in" + , "non-free programs enables many more people to use the whole GNU" + , "operating system, as well as its variant, the GNU/Linux operating" + , "system." + , "" + , " Although the Lesser General Public License is Less protective of the" + , "users' freedom, it does ensure that the user of a program that is" + , "linked with the Library has the freedom and the wherewithal to run" + , "that program using a modified version of the Library." , "" , " The precise terms and conditions for copying, distribution and" , "modification follow. Pay close attention to the difference between a" , "\"work based on the library\" and a \"work that uses the library\". The" - , "former contains code derived from the library, while the latter only" - , "works together with the library." + , "former contains code derived from the library, whereas the latter must" + , "be combined with the library in order to run." , "" - , " Note that it is possible for a library to be covered by the ordinary" - , "General Public License rather than by this special one." - , "" - , " GNU LIBRARY GENERAL PUBLIC LICENSE" + , " GNU LESSER GENERAL PUBLIC LICENSE" , " TERMS AND CONDITIONS FOR COPYING, DISTRIBUTION AND MODIFICATION" , "" - , " 0. This License Agreement applies to any software library which" - , "contains a notice placed by the copyright holder or other authorized" - , "party saying it may be distributed under the terms of this Library" - , "General Public License (also called \"this License\"). Each licensee is" - , "addressed as \"you\"." + , " 0. This License Agreement applies to any software library or other" + , "program which contains a notice placed by the copyright holder or" + , "other authorized party saying it may be distributed under the terms of" + , "this Lesser General Public License (also called \"this License\")." + , "Each licensee is addressed as \"you\"." , "" , " A \"library\" means a collection of software functions and/or data" , "prepared so as to be conveniently linked with application programs" @@ -2023,7 +2037,7 @@ lgpl2 = unlines , "Any executables containing that work also fall under Section 6," , "whether or not they are linked directly with the Library itself." , "" - , " 6. As an exception to the Sections above, you may also compile or" + , " 6. As an exception to the Sections above, you may also combine or" , "link a \"work that uses the Library\" with the Library to produce a" , "work containing portions of the Library, and distribute that work" , "under terms of your choice, provided that the terms permit" @@ -2050,23 +2064,31 @@ lgpl2 = unlines , " Library will not necessarily be able to recompile the application" , " to use the modified definitions.)" , "" - , " b) Accompany the work with a written offer, valid for at" + , " b) Use a suitable shared library mechanism for linking with the" + , " Library. A suitable mechanism is one that (1) uses at run time a" + , " copy of the library already present on the user's computer system," + , " rather than copying library functions into the executable, and (2)" + , " will operate properly with a modified version of the library, if" + , " the user installs one, as long as the modified version is" + , " interface-compatible with the version that the work was made with." + , "" + , " c) Accompany the work with a written offer, valid for at" , " least three years, to give the same user the materials" , " specified in Subsection 6a, above, for a charge no more" , " than the cost of performing this distribution." , "" - , " c) If distribution of the work is made by offering access to copy" + , " d) If distribution of the work is made by offering access to copy" , " from a designated place, offer equivalent access to copy the above" , " specified materials from the same place." , "" - , " d) Verify that the user has already received a copy of these" + , " e) Verify that the user has already received a copy of these" , " materials or that you have already sent this user a copy." , "" , " For an executable, the required form of the \"work that uses the" , "Library\" must include any data and utility programs needed for" , "reproducing the executable from it. However, as a special exception," - , "the source code distributed need not include anything that is normally" - , "distributed (in either source or binary form) with the major" + , "the materials to be distributed need not include anything that is" + , "normally distributed (in either source or binary form) with the major" , "components (compiler, kernel, and so on) of the operating system on" , "which the executable runs, unless that component itself accompanies" , "the executable." @@ -2115,7 +2137,7 @@ lgpl2 = unlines , "original licensor to copy, distribute, link with or modify the Library" , "subject to these terms and conditions. You may not impose any further" , "restrictions on the recipients' exercise of the rights granted herein." - , "You are not responsible for enforcing compliance by third parties to" + , "You are not responsible for enforcing compliance by third parties with" , "this License." , "" , " 11. If, as a consequence of a court judgment or allegation of patent" @@ -2158,7 +2180,7 @@ lgpl2 = unlines , "written in the body of this License." , "" , " 13. The Free Software Foundation may publish revised and/or new" - , "versions of the Library General Public License from time to time." + , "versions of the Lesser General Public License from time to time." , "Such new versions will be similar in spirit to the present version," , "but may differ in detail to address new problems or concerns." , "" @@ -2179,7 +2201,7 @@ lgpl2 = unlines , "of all derivatives of our free software and of promoting the sharing" , "and reuse of software generally." , "" - , " NO WARRANTY" + , " NO WARRANTY" , "" , " 15. BECAUSE THE LIBRARY IS LICENSED FREE OF CHARGE, THERE IS NO" , "WARRANTY FOR THE LIBRARY, TO THE EXTENT PERMITTED BY APPLICABLE LAW." @@ -2202,7 +2224,7 @@ lgpl2 = unlines , "SUCH HOLDER OR OTHER PARTY HAS BEEN ADVISED OF THE POSSIBILITY OF SUCH" , "DAMAGES." , "" - , " END OF TERMS AND CONDITIONS" + , " END OF TERMS AND CONDITIONS" , "" , " How to Apply These Terms to Your New Libraries" , "" @@ -2221,17 +2243,17 @@ lgpl2 = unlines , " Copyright (C) <year> <name of author>" , "" , " This library is free software; you can redistribute it and/or" - , " modify it under the terms of the GNU Library General Public" + , " modify it under the terms of the GNU Lesser General Public" , " License as published by the Free Software Foundation; either" - , " version 2 of the License, or (at your option) any later version." + , " version 2.1 of the License, or (at your option) any later version." , "" , " This library is distributed in the hope that it will be useful," , " but WITHOUT ANY WARRANTY; without even the implied warranty of" , " MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU" - , " Library General Public License for more details." + , " Lesser General Public License for more details." , "" - , " You should have received a copy of the GNU Library General Public" - , " License along with this library; if not, write to the Free" + , " You should have received a copy of the GNU Lesser General Public" + , " License along with this library; if not, write to the Free Software" , " Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA" , "" , "Also add information on how to contact you by electronic and paper mail." @@ -2624,6 +2646,30 @@ apache20 = unlines , " limitations under the License." ] +mit :: String -> String -> License +mit authors year = unlines + [ "Copyright (c) " ++ year ++ " " ++ authors + , "" + , "Permission is hereby granted, free of charge, to any person obtaining" + , "a copy of this software and associated documentation files (the" + , "\"Software\"), to deal in the Software without restriction, including" + , "without limitation the rights to use, copy, modify, merge, publish," + , "distribute, sublicense, and/or sell copies of the Software, and to" + , "permit persons to whom the Software is furnished to do so, subject to" + , "the following conditions:" + , "" + , "The above copyright notice and this permission notice shall be included" + , "in all copies or substantial portions of the Software." + , "" + , "THE SOFTWARE IS PROVIDED \"AS IS\", WITHOUT WARRANTY OF ANY KIND," + , "EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF" + , "MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT." + , "IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY" + , "CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT," + , "TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE" + , "SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE." + ] + mpl20 :: License mpl20 = unlines [ "Mozilla Public License Version 2.0" diff --git a/cabal-install/Distribution/Client/Init/Types.hs b/cabal-install/Distribution/Client/Init/Types.hs index 2307286ef8fbd32d5820f460ed161520d1239252..2536736222632c8b4098fcf7a45a63eae0b998e0 100644 --- a/cabal-install/Distribution/Client/Init/Types.hs +++ b/cabal-install/Distribution/Client/Init/Types.hs @@ -41,7 +41,7 @@ data InitFlags = , noComments :: Flag Bool , minimal :: Flag Bool - , packageName :: Flag String + , packageName :: Flag P.PackageName , version :: Flag Version , cabalVersion :: Flag VersionRange , license :: Flag License diff --git a/cabal-install/Distribution/Client/Sandbox/PackageEnvironment.hs b/cabal-install/Distribution/Client/Sandbox/PackageEnvironment.hs index 02099876fc724badfa45d04150326279671ffeeb..a2bce6bc6232248d40af93f531543f56d77f476b 100644 --- a/cabal-install/Distribution/Client/Sandbox/PackageEnvironment.hs +++ b/cabal-install/Distribution/Client/Sandbox/PackageEnvironment.hs @@ -46,7 +46,7 @@ import Distribution.Simple.Setup ( Flag(..), ConfigFlags(..) , fromFlagOrDefault, toFlag, flagToMaybe ) import Distribution.Simple.Utils ( die, info, notice, warn, lowercase ) import Distribution.ParseUtils ( FieldDescr(..), ParseResult(..) - , commaListField + , commaListField, commaNewLineListField , liftField, lineNo, locatedErrorMsg , parseFilePathQ, readFields , showPWarning, simpleField @@ -390,7 +390,7 @@ pkgEnvFieldDescrs = [ pkgEnvInherit (\v pkgEnv -> pkgEnv { pkgEnvInherit = v }) -- FIXME: Should we make these fields part of ~/.cabal/config ? - , commaListField "constraints" + , commaNewLineListField "constraints" Text.disp Text.parse (configExConstraints . savedConfigureExFlags . pkgEnvSavedConfig) (\v pkgEnv -> updateConfigureExFlags pkgEnv diff --git a/cabal-install/Distribution/Client/Setup.hs b/cabal-install/Distribution/Client/Setup.hs index ceea0d927a31cda36f8ab2b19d88a5174fea1405..66bf85e3487a94489fb3ad90e0b08eea551dff12 100644 --- a/cabal-install/Distribution/Client/Setup.hs +++ b/cabal-install/Distribution/Client/Setup.hs @@ -26,6 +26,7 @@ module Distribution.Client.Setup , freezeCommand, FreezeFlags(..) , getCommand, unpackCommand, GetFlags(..) , checkCommand + , formatCommand , uploadCommand, UploadFlags(..) , reportCommand, ReportFlags(..) , runCommand @@ -635,6 +636,16 @@ checkCommand = CommandUI { commandOptions = \_ -> [] } +formatCommand :: CommandUI (Flag Verbosity) +formatCommand = CommandUI { + commandName = "format", + commandSynopsis = "Reformat the .cabal file using the standard style.", + commandDescription = Nothing, + commandUsage = \pname -> "Usage: " ++ pname ++ " format [FILE]\n", + commandDefaultFlags = toFlag normal, + commandOptions = \_ -> [] + } + runCommand :: CommandUI (BuildFlags, BuildExFlags) runCommand = CommandUI { commandName = "run", @@ -647,7 +658,7 @@ runCommand = CommandUI { commandDefaultFlags = mempty, commandOptions = \showOrParseArgs -> liftOptions fst setFst - (Cabal.buildOptions progConf showOrParseArgs) + (commandOptions parent showOrParseArgs) ++ liftOptions snd setSnd (buildExOptions showOrParseArgs) @@ -656,7 +667,7 @@ runCommand = CommandUI { setFst a (_,b) = (a,b) setSnd b (a,_) = (a,b) - progConf = defaultProgramConfiguration + parent = Cabal.buildCommand defaultProgramConfiguration -- ------------------------------------------------------------ -- * Report flags @@ -1024,10 +1035,10 @@ haddockOptions showOrParseArgs | descr <- optionDescr opt] } | opt <- commandOptions Cabal.haddockCommand showOrParseArgs , let name = optionName opt - , name `elem` ["hoogle", "html", "html-location", - "executables", "internal", "css", - "hyperlink-source", "hscolour-css", - "contents-location"] + , name `elem` ["hoogle", "html", "html-location" + ,"executables", "tests", "benchmarks", "all", "internal", "css" + ,"hyperlink-source", "hscolour-css" + ,"contents-location"] ] where fmapOptFlags :: (OptFlags -> OptFlags) -> OptDescr a -> OptDescr a @@ -1312,7 +1323,9 @@ initCommand = CommandUI { , option ['p'] ["package-name"] "Name of the Cabal package to create." IT.packageName (\v flags -> flags { IT.packageName = v }) - (reqArgFlag "PACKAGE") + (reqArg "PACKAGE" (readP_to_E ("Cannot parse package name: "++) + (toFlag `fmap` parse)) + (flagToList . fmap display)) , option [] ["version"] "Initial version of the package." diff --git a/cabal-install/Distribution/Client/SetupWrapper.hs b/cabal-install/Distribution/Client/SetupWrapper.hs index f4aec41e4c23a07e43c8c7103c7a345b327fe538..f20f1cb44692ab61fd30ff33ddf11148b427458c 100644 --- a/cabal-install/Distribution/Client/SetupWrapper.hs +++ b/cabal-install/Distribution/Client/SetupWrapper.hs @@ -463,6 +463,7 @@ externalSetupMethod verbosity options pkg bt mkargs = do , ghcOptPackages = maybe [] (\ipkgid -> [(ipkgid, cabalPkgid)]) maybeCabalLibInstalledPkgId + , ghcOptExtra = ["-threaded"] } let ghcCmdLine = renderGhcOptions compiler ghcOptions case useLoggingHandle options of diff --git a/cabal-install/Main.hs b/cabal-install/Main.hs index c943af4f175fe94cff937d2d659d9d6c47460769..713d114bd6c825de0e176277b2ed280adacaa091 100644 --- a/cabal-install/Main.hs +++ b/cabal-install/Main.hs @@ -25,6 +25,7 @@ import Distribution.Client.Setup , FreezeFlags(..), freezeCommand , GetFlags(..), getCommand, unpackCommand , checkCommand + , formatCommand , updateCommand , ListFlags(..), listCommand , InfoFlags(..), infoCommand @@ -102,6 +103,10 @@ import Distribution.Client.Utils (determineNumJobs import Distribution.PackageDescription ( Executable(..) ) +import Distribution.PackageDescription.Parse + ( readPackageDescription ) +import Distribution.PackageDescription.PrettyPrint + ( writeGenericPackageDescription ) import Distribution.Simple.Build ( startInterpreter ) import Distribution.Simple.Command @@ -117,7 +122,8 @@ import qualified Distribution.Simple.LocalBuildInfo as LBI import Distribution.Simple.Program (defaultProgramConfiguration) import qualified Distribution.Simple.Setup as Cabal import Distribution.Simple.Utils - ( cabalVersion, die, notice, info, topHandler, findPackageDesc ) + ( cabalVersion, die, notice, info, topHandler + , findPackageDesc, tryFindPackageDesc ) import Distribution.Text ( display ) import Distribution.Verbosity as Verbosity @@ -220,6 +226,8 @@ mainWorker args = topHandler $ regVerbosity regDistPref ,testCommand `commandAddAction` testAction ,benchmarkCommand `commandAddAction` benchmarkAction + ,hiddenCommand $ + formatCommand `commandAddAction` formatAction ,hiddenCommand $ upgradeCommand `commandAddAction` upgradeAction ,hiddenCommand $ @@ -672,6 +680,8 @@ testAction (testFlags, buildFlags, buildExFlags) extraArgs globalFlags = do distPref = fromFlagOrDefault (useDistPref defaultSetupScriptOptions) (testDistPref testFlags) setupOptions = defaultSetupScriptOptions { useDistPref = distPref } + buildFlags' = buildFlags { buildVerbosity = testVerbosity testFlags + , buildDistPref = testDistPref testFlags } addConfigFlags = mempty { configTests = toFlag True } checkFlags flags | fromFlagOrDefault False (configTests flags) = Nothing @@ -683,10 +693,10 @@ testAction (testFlags, buildFlags, buildExFlags) extraArgs globalFlags = do -- deps if needed. (useSandbox, config) <- reconfigure verbosity distPref addConfigFlags [] globalFlags noAddSource - (buildNumJobs buildFlags) checkFlags + (buildNumJobs buildFlags') checkFlags maybeWithSandboxDirOnSearchPath useSandbox $ - build verbosity config distPref buildFlags extraArgs + build verbosity config distPref buildFlags' extraArgs maybeWithSandboxDirOnSearchPath useSandbox $ setupWrapper verbosity setupOptions Nothing @@ -702,6 +712,9 @@ benchmarkAction (benchmarkFlags, buildFlags, buildExFlags) distPref = fromFlagOrDefault (useDistPref defaultSetupScriptOptions) (benchmarkDistPref benchmarkFlags) setupOptions = defaultSetupScriptOptions { useDistPref = distPref } + buildFlags' = buildFlags + { buildVerbosity = benchmarkVerbosity benchmarkFlags + , buildDistPref = benchmarkDistPref benchmarkFlags } addConfigFlags = mempty { configBenchmarks = toFlag True } checkFlags flags | fromFlagOrDefault False (configBenchmarks flags) = Nothing @@ -712,11 +725,11 @@ benchmarkAction (benchmarkFlags, buildFlags, buildExFlags) -- reconfigure also checks if we're in a sandbox and reinstalls add-source -- deps if needed. (useSandbox, config) <- reconfigure verbosity distPref addConfigFlags [] - globalFlags noAddSource (buildNumJobs buildFlags) + globalFlags noAddSource (buildNumJobs buildFlags') checkFlags maybeWithSandboxDirOnSearchPath useSandbox $ - build verbosity config distPref buildFlags extraArgs + build verbosity config distPref buildFlags' extraArgs maybeWithSandboxDirOnSearchPath useSandbox $ setupWrapper verbosity setupOptions Nothing @@ -857,6 +870,16 @@ checkAction verbosityFlag extraArgs _globalFlags = do allOk <- Check.check (fromFlag verbosityFlag) unless allOk exitFailure +formatAction :: Flag Verbosity -> [String] -> GlobalFlags -> IO () +formatAction verbosityFlag extraArgs _globalFlags = do + let verbosity = fromFlag verbosityFlag + path <- case extraArgs of + [] -> do cwd <- getCurrentDirectory + tryFindPackageDesc cwd + (p:_) -> return p + pkgDesc <- readPackageDescription verbosity path + -- Uses 'writeFileAtomic' under the hood. + writeGenericPackageDescription path pkgDesc sdistAction :: (SDistFlags, SDistExFlags) -> [String] -> GlobalFlags -> IO () sdistAction (sdistFlags, sdistExFlags) extraArgs _globalFlags = do diff --git a/cabal-install/bootstrap.sh b/cabal-install/bootstrap.sh index a03a77772355f635ef8078418d3fcfd16a9d64c1..fd611660a4cb7d439d75326619f2975be411fc6a 100755 --- a/cabal-install/bootstrap.sh +++ b/cabal-install/bootstrap.sh @@ -27,6 +27,10 @@ GZIP="${GZIP:-gzip}" SCOPE_OF_INSTALLATION="--user" DEFAULT_PREFIX="${HOME}/.cabal" +# Try to respect $TMPDIR but override if needed - see #1710. +[ -"$TMPDIR"- = -""- ] || echo "$TMPDIR" | grep -q ld && + export TMPDIR=/tmp/cabal-$(echo $(od -XN4 -An /dev/random)) && mkdir $TMPDIR + # Check for a C compiler. [ ! -x "$CC" ] && for ccc in gcc clang cc icc; do ${ccc} --version > /dev/null 2>&1 && CC=$ccc &&