Skip to content
GitLab
Projects
Groups
Snippets
/
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
Menu
Open sidebar
Glasgow Haskell Compiler
Packages
Cabal
Commits
c13850d1
Commit
c13850d1
authored
Apr 07, 2014
by
Daniel Trstenjak
Browse files
Merge remote-tracking branch 'cabal/master'
Conflicts: Cabal/Distribution/ParseUtils.hs
parents
77ccb23c
34179398
Changes
67
Hide whitespace changes
Inline
Side-by-side
.travis.yml
View file @
c13850d1
...
...
@@ -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
...
...
Cabal/Cabal.cabal
View file @
c13850d1
...
...
@@ -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
...
...
Cabal/
tests/
Distribution/Compat/CreatePipe.hs
c
→
Cabal/Distribution/Compat/CreatePipe.hs
View file @
c13850d1
{-# LANGUAGE CPP, ForeignFunctionInterface #-}
module Distribution.Compat.CreatePipe (createPipe) where
module
Distribution.Compat.CreatePipe
(
createPipe
,
tee
)
where
import System.IO (Handle)
import
Control.Concurrent
(
forkIO
)
import
Control.Monad
(
forM_
,
when
)
import
System.IO
(
Handle
,
hClose
,
hGetContents
,
hPutStr
)
#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 */
-- 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
(
..
))
...
...
@@ -19,37 +17,59 @@ 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
)
#if !(defined(_MSC_VER) || defined(__MINGW32__) || defined(_WIN32))
createPipe = do
(readfd, writefd) <- Posix.createPipe
readh <- fdToHandle readfd
writeh <- fdToHandle writefd
return (readh, writeh)
#else
-- 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 (
#const
_O_BINARY)
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
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
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
Cabal/Distribution/Compiler.hs
View file @
c13850d1
...
...
@@ -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
(
..
),
...
...
Cabal/Distribution/License.hs
View file @
c13850d1
...
...
@@ -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
,
...
...
Cabal/Distribution/Make.hs
View file @
c13850d1
...
...
@@ -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
(
..
),
...
...
Cabal/Distribution/ModuleName.hs
View file @
c13850d1
...
...
@@ -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
,
...
...
Cabal/Distribution/Package.hs
View file @
c13850d1
...
...
@@ -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
(
..
),
...
...
Cabal/Distribution/PackageDescription.hs
View file @
c13850d1
...
...
@@ -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
(
..
),
...
...
Cabal/Distribution/PackageDescription/Check.hs
View file @
c13850d1
...
...
@@ -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
(
..
),
...
...
Cabal/Distribution/PackageDescription/Configuration.hs
View file @
c13850d1
...
...
@@ -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
,
...
...
Cabal/Distribution/PackageDescription/Parse.hs
View file @
c13850d1
...
...
@@ -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
...
...
Cabal/Distribution/PackageDescription/PrettyPrint.hs
View file @
c13850d1
...
...
@@ -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
,
...
...
Cabal/Distribution/ParseUtils.hs
View file @
c13850d1
...
...
@@ -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