diff --git a/Cabal/Cabal.cabal b/Cabal/Cabal.cabal index f1b5111750e2f9bbf5224baf594a1ec02e26eff6..c3f13290575f0ce946cda3cecb6e97ea28079c34 100644 --- a/Cabal/Cabal.cabal +++ b/Cabal/Cabal.cabal @@ -432,8 +432,36 @@ library Distribution.Compat.Binary.Class Distribution.Compat.Binary.Generic - default-language: Haskell98 - default-extensions: Rank2Types, FlexibleContexts + default-language: Haskell2010 + other-extensions: + BangPatterns + CPP + DefaultSignatures + DeriveDataTypeable + DeriveFoldable + DeriveFunctor + DeriveGeneric + DeriveTraversable + ExistentialQuantification + FlexibleContexts + FlexibleInstances + GeneralizedNewtypeDeriving + ImplicitParams + KindSignatures + NondecreasingIndentation + OverloadedStrings + RankNTypes + RecordWildCards + ScopedTypeVariables + StandaloneDeriving + Trustworthy + TypeFamilies + TypeOperators + TypeSynonymInstances + UndecidableInstances + + if impl(ghc >= 7.11) + other-extensions: PatternSynonyms -- Small, fast running tests. test-suite unit-tests @@ -466,7 +494,7 @@ test-suite unit-tests QuickCheck >= 2.7 && < 2.10, Cabal ghc-options: -Wall - default-language: Haskell98 + default-language: Haskell2010 -- Large, system tests that build packages. test-suite package-tests @@ -501,4 +529,4 @@ test-suite package-tests build-depends: unix, exceptions ghc-options: -Wall -rtsopts default-extensions: CPP - default-language: Haskell98 + default-language: Haskell2010 diff --git a/Cabal/Distribution/Compat/CreatePipe.hs b/Cabal/Distribution/Compat/CreatePipe.hs index d159bb2bfb508aed081a55351eabbd86f51fef52..bfda07c4a13bafbadf7010596a6119e5e13fad22 100644 --- a/Cabal/Distribution/Compat/CreatePipe.hs +++ b/Cabal/Distribution/Compat/CreatePipe.hs @@ -1,4 +1,6 @@ -{-# LANGUAGE CPP, ForeignFunctionInterface #-} +{-# LANGUAGE CPP #-} +{-# LANGUAGE FlexibleContexts #-} + module Distribution.Compat.CreatePipe (createPipe) where import System.IO (Handle, hSetEncoding, localeEncoding) diff --git a/Cabal/Distribution/Compat/Environment.hs b/Cabal/Distribution/Compat/Environment.hs index 6f0b99d386ef349272c58f354ddd6a7ada214de4..014fad7a877f510c77f3be3e47e3e4bd3b26712c 100644 --- a/Cabal/Distribution/Compat/Environment.hs +++ b/Cabal/Distribution/Compat/Environment.hs @@ -1,5 +1,6 @@ {-# LANGUAGE CPP #-} -{-# LANGUAGE ForeignFunctionInterface #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} {-# OPTIONS_HADDOCK hide #-} module Distribution.Compat.Environment diff --git a/Cabal/Distribution/Compat/GetShortPathName.hs b/Cabal/Distribution/Compat/GetShortPathName.hs index f2a7d6a93f97b059f0f75c00b76d5383019c6bc9..eebad98f947399b37d78c90bb1329465ae8348bc 100644 --- a/Cabal/Distribution/Compat/GetShortPathName.hs +++ b/Cabal/Distribution/Compat/GetShortPathName.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE CPP, ForeignFunctionInterface #-} +{-# LANGUAGE CPP #-} ----------------------------------------------------------------------------- -- | diff --git a/Cabal/Distribution/Compat/Prelude.hs b/Cabal/Distribution/Compat/Prelude.hs index 235c4fdfa956e13c4ef8bc8027bd4ae7e2650cf8..03889d343233eae4535a6c16ed967dd224c40666 100644 --- a/Cabal/Distribution/Compat/Prelude.hs +++ b/Cabal/Distribution/Compat/Prelude.hs @@ -1,5 +1,7 @@ {-# LANGUAGE CPP #-} {-# LANGUAGE TypeOperators #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE FlexibleContexts #-} #ifdef MIN_VERSION_base #define MINVER_base_48 MIN_VERSION_base(4,8,0) diff --git a/Cabal/Distribution/Compat/Stack.hs b/Cabal/Distribution/Compat/Stack.hs index cbc2b9260a3bbefc3e582d160d57ca9ec763771f..98e8159982dc99a33635b5a1499f03efc8e7ab7b 100644 --- a/Cabal/Distribution/Compat/Stack.hs +++ b/Cabal/Distribution/Compat/Stack.hs @@ -1,5 +1,5 @@ {-# LANGUAGE CPP #-} -{-# LANGUAGE Rank2Types #-} +{-# LANGUAGE RankNTypes #-} {-# LANGUAGE ImplicitParams #-} module Distribution.Compat.Stack ( WithCallStack, diff --git a/Cabal/Distribution/Compat/Time.hs b/Cabal/Distribution/Compat/Time.hs index 6fd51e56c26cf8d433444f946ebf7cdc1c68dc22..45aaf49326f67231cef64ecb194b645cbb676031 100644 --- a/Cabal/Distribution/Compat/Time.hs +++ b/Cabal/Distribution/Compat/Time.hs @@ -1,4 +1,9 @@ -{-# LANGUAGE CPP, ForeignFunctionInterface, GeneralizedNewtypeDeriving, ScopedTypeVariables #-} +{-# LANGUAGE CPP #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE ScopedTypeVariables #-} + module Distribution.Compat.Time ( ModTime(..) -- Needed for testing , getModTime, getFileAge, getCurTime diff --git a/Cabal/Distribution/Lex.hs b/Cabal/Distribution/Lex.hs index e1970983174082ee34cfa879030134d6e1c2067c..f1fe94501a5a650b0c478e57faef95d9eef1bb86 100644 --- a/Cabal/Distribution/Lex.hs +++ b/Cabal/Distribution/Lex.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE PatternGuards #-} ----------------------------------------------------------------------------- -- | -- Module : Distribution.Lex diff --git a/Cabal/Distribution/Make.hs b/Cabal/Distribution/Make.hs index 9366a5f54d467c0d832b548dd193233014c7f496..2362da7e2f2105b4fee4d61e07871d700453f9f8 100644 --- a/Cabal/Distribution/Make.hs +++ b/Cabal/Distribution/Make.hs @@ -1,3 +1,6 @@ +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} + ----------------------------------------------------------------------------- -- | -- Module : Distribution.Make diff --git a/Cabal/Distribution/PackageDescription/Configuration.hs b/Cabal/Distribution/PackageDescription/Configuration.hs index 2baaab5db0dc960bc29ad82e92550839bf06d1dd..45589b2dd62320203f8ce3aa5f957512e672e25e 100644 --- a/Cabal/Distribution/PackageDescription/Configuration.hs +++ b/Cabal/Distribution/PackageDescription/Configuration.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE CPP #-} -- -fno-warn-deprecations for use of Map.foldWithKey {-# OPTIONS_GHC -fno-warn-deprecations #-} ----------------------------------------------------------------------------- diff --git a/Cabal/Distribution/PackageDescription/Parse.hs b/Cabal/Distribution/PackageDescription/Parse.hs index 75bdf20753eaf63418ab6f6de4decdb19f22e19b..8881834c2a2fd5993d389bb6731afb98998b9a9c 100644 --- a/Cabal/Distribution/PackageDescription/Parse.hs +++ b/Cabal/Distribution/PackageDescription/Parse.hs @@ -1,5 +1,8 @@ {-# LANGUAGE CPP #-} {-# LANGUAGE DeriveDataTypeable #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} + ----------------------------------------------------------------------------- -- | -- Module : Distribution.PackageDescription.Parse diff --git a/Cabal/Distribution/Simple.hs b/Cabal/Distribution/Simple.hs index bee886631ec32c086fab808bde05341884edd855..60fbdf1a3c21a360f67b9c9c0340fb50b9e88ece 100644 --- a/Cabal/Distribution/Simple.hs +++ b/Cabal/Distribution/Simple.hs @@ -1,3 +1,6 @@ +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} + ----------------------------------------------------------------------------- -- | -- Module : Distribution.Simple diff --git a/Cabal/Distribution/Simple/Bench.hs b/Cabal/Distribution/Simple/Bench.hs index 8a5d9b80fd3fb6a1307a6c77932b876114ef92aa..1bd565343f3328f6f9f36f51a9ffd819148c3c80 100644 --- a/Cabal/Distribution/Simple/Bench.hs +++ b/Cabal/Distribution/Simple/Bench.hs @@ -1,3 +1,6 @@ +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} + ----------------------------------------------------------------------------- -- | -- Module : Distribution.Simple.Bench diff --git a/Cabal/Distribution/Simple/Build.hs b/Cabal/Distribution/Simple/Build.hs index 78bac824238a71c3234db35d39cd1188584dc6f3..29ca2ed2c0fbed6f1bfc768dbc84295965a44d61 100644 --- a/Cabal/Distribution/Simple/Build.hs +++ b/Cabal/Distribution/Simple/Build.hs @@ -1,3 +1,6 @@ +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} + ----------------------------------------------------------------------------- -- | -- Module : Distribution.Simple.Build diff --git a/Cabal/Distribution/Simple/BuildTarget.hs b/Cabal/Distribution/Simple/BuildTarget.hs index b2dfb012f328e9a570566a37a071f0bff89d766d..328b3f43334cdf48bd36442dcae8cd33f777e4a5 100644 --- a/Cabal/Distribution/Simple/BuildTarget.hs +++ b/Cabal/Distribution/Simple/BuildTarget.hs @@ -1,4 +1,7 @@ {-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} + ----------------------------------------------------------------------------- -- | -- Module : Distribution.Client.BuildTargets diff --git a/Cabal/Distribution/Simple/Command.hs b/Cabal/Distribution/Simple/Command.hs index 725fea9dad692054e547f4787ba3edf91f3c7239..58e7883d56a358759e8284fa6308a061ef81db5b 100644 --- a/Cabal/Distribution/Simple/Command.hs +++ b/Cabal/Distribution/Simple/Command.hs @@ -1,4 +1,7 @@ {-# LANGUAGE ExistentialQuantification #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} + ----------------------------------------------------------------------------- -- | -- Module : Distribution.Simple.Command diff --git a/Cabal/Distribution/Simple/Configure.hs b/Cabal/Distribution/Simple/Configure.hs index 6a2ec8d0a4d8512d3559ae910c3a6ba610d8c018..d9c38a6fde35a501f2e9d0f37948728cf6b7a1e8 100644 --- a/Cabal/Distribution/Simple/Configure.hs +++ b/Cabal/Distribution/Simple/Configure.hs @@ -1,8 +1,9 @@ {-# LANGUAGE DeriveDataTypeable #-} +{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE RankNTypes #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE ScopedTypeVariables #-} -{-# LANGUAGE PatternGuards #-} ----------------------------------------------------------------------------- -- | diff --git a/Cabal/Distribution/Simple/GHC.hs b/Cabal/Distribution/Simple/GHC.hs index 5bc27e23e53f1f4eb050fce0e77d93aa74dcefe8..81d5e4a0650380900898873c5121308a49dce3de 100644 --- a/Cabal/Distribution/Simple/GHC.hs +++ b/Cabal/Distribution/Simple/GHC.hs @@ -1,4 +1,5 @@ -{-# LANGUAGE PatternGuards #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} ----------------------------------------------------------------------------- -- | diff --git a/Cabal/Distribution/Simple/GHC/Internal.hs b/Cabal/Distribution/Simple/GHC/Internal.hs index 5de4a8049fa6de0db05ecc076b7285b31580a714..b5fb8446700c53da2e7e02b1f8d6d01d080b7524 100644 --- a/Cabal/Distribution/Simple/GHC/Internal.hs +++ b/Cabal/Distribution/Simple/GHC/Internal.hs @@ -1,4 +1,6 @@ -{-# LANGUAGE PatternGuards #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} + ----------------------------------------------------------------------------- -- | -- Module : Distribution.Simple.GHC.Internal diff --git a/Cabal/Distribution/Simple/GHCJS.hs b/Cabal/Distribution/Simple/GHCJS.hs index f7934fcb925dbe724da1e1e377be471f13227db3..1577b244a88d30a4f387489ee47da1a2bbda1054 100644 --- a/Cabal/Distribution/Simple/GHCJS.hs +++ b/Cabal/Distribution/Simple/GHCJS.hs @@ -1,4 +1,6 @@ -{-# LANGUAGE PatternGuards #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} + module Distribution.Simple.GHCJS ( configure, getInstalledPackages, getPackageDBContents, buildLib, buildExe, diff --git a/Cabal/Distribution/Simple/Haddock.hs b/Cabal/Distribution/Simple/Haddock.hs index fac67db6f849a21724945407142d00951b5bd55f..c66346e6f9a0155004da60cadb919e23fcc77757 100644 --- a/Cabal/Distribution/Simple/Haddock.hs +++ b/Cabal/Distribution/Simple/Haddock.hs @@ -1,4 +1,6 @@ {-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} ----------------------------------------------------------------------------- -- | diff --git a/Cabal/Distribution/Simple/HaskellSuite.hs b/Cabal/Distribution/Simple/HaskellSuite.hs index 7edfd1ba4435b0aa78373f644e00993201cd7a8b..9107b6ac4790b92e7ccd7c0783b83517ded2c996 100644 --- a/Cabal/Distribution/Simple/HaskellSuite.hs +++ b/Cabal/Distribution/Simple/HaskellSuite.hs @@ -1,3 +1,6 @@ +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} + module Distribution.Simple.HaskellSuite where import Prelude () diff --git a/Cabal/Distribution/Simple/Hpc.hs b/Cabal/Distribution/Simple/Hpc.hs index 5eb52f681e594aff070a5a47cd326f95d64e4478..f1ae33390dc25349543a2b6c3c35d914e1fc4fe4 100644 --- a/Cabal/Distribution/Simple/Hpc.hs +++ b/Cabal/Distribution/Simple/Hpc.hs @@ -1,3 +1,6 @@ +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} + ----------------------------------------------------------------------------- -- | -- Module : Distribution.Simple.Hpc diff --git a/Cabal/Distribution/Simple/Install.hs b/Cabal/Distribution/Simple/Install.hs index a240c958db751acab7d468553d05ebaadaf4fbe5..77f0c9e80af3febfff1b00066fae3f85d95a761a 100644 --- a/Cabal/Distribution/Simple/Install.hs +++ b/Cabal/Distribution/Simple/Install.hs @@ -1,3 +1,6 @@ +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} + ----------------------------------------------------------------------------- -- | -- Module : Distribution.Simple.Install diff --git a/Cabal/Distribution/Simple/InstallDirs.hs b/Cabal/Distribution/Simple/InstallDirs.hs index 610dd246e30fda81936be8b03ce4c129d44cffad..e3df56e2b883d6eb15a8310428e5585369f2d763 100644 --- a/Cabal/Distribution/Simple/InstallDirs.hs +++ b/Cabal/Distribution/Simple/InstallDirs.hs @@ -1,7 +1,8 @@ {-# LANGUAGE CPP #-} -{-# LANGUAGE ForeignFunctionInterface #-} {-# LANGUAGE DeriveFunctor #-} {-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} ----------------------------------------------------------------------------- -- | diff --git a/Cabal/Distribution/Simple/JHC.hs b/Cabal/Distribution/Simple/JHC.hs index 99f7f5a9fded815ecbb00ac6bb342f9d595dbce8..aa8388da34fba48138faac89bab268f84827fc33 100644 --- a/Cabal/Distribution/Simple/JHC.hs +++ b/Cabal/Distribution/Simple/JHC.hs @@ -1,3 +1,6 @@ +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} + ----------------------------------------------------------------------------- -- | -- Module : Distribution.Simple.JHC diff --git a/Cabal/Distribution/Simple/LHC.hs b/Cabal/Distribution/Simple/LHC.hs index e3ee9c290f81a54e7e50589fd89732b22bb79ead..d709345b0a88c4f3d776815cacc4e3a23acbdf42 100644 --- a/Cabal/Distribution/Simple/LHC.hs +++ b/Cabal/Distribution/Simple/LHC.hs @@ -1,3 +1,6 @@ +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} + ----------------------------------------------------------------------------- -- | -- Module : Distribution.Simple.LHC diff --git a/Cabal/Distribution/Simple/LocalBuildInfo.hs b/Cabal/Distribution/Simple/LocalBuildInfo.hs index cb4597dc9f43b04412c98d4185ea521e6efa5076..d713d5f674075c0b83ff2e78d2fc31cccdde2f74 100644 --- a/Cabal/Distribution/Simple/LocalBuildInfo.hs +++ b/Cabal/Distribution/Simple/LocalBuildInfo.hs @@ -1,5 +1,6 @@ {-# LANGUAGE DeriveGeneric #-} -{-# LANGUAGE PatternGuards #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} ----------------------------------------------------------------------------- -- | diff --git a/Cabal/Distribution/Simple/PreProcess.hs b/Cabal/Distribution/Simple/PreProcess.hs index 1dc74f41bc3546f6e362eccd6defe2376d447ab5..2b4f9804a6e14680b8448044a752e5971130a575 100644 --- a/Cabal/Distribution/Simple/PreProcess.hs +++ b/Cabal/Distribution/Simple/PreProcess.hs @@ -1,3 +1,6 @@ +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} + ----------------------------------------------------------------------------- -- | -- Module : Distribution.Simple.PreProcess diff --git a/Cabal/Distribution/Simple/Program.hs b/Cabal/Distribution/Simple/Program.hs index 5c3eec8dea6eb675c2ffaef802011dfce170b3bc..aafa4aa9f03623388d3fcdee3ca9bc848403a5f9 100644 --- a/Cabal/Distribution/Simple/Program.hs +++ b/Cabal/Distribution/Simple/Program.hs @@ -1,3 +1,6 @@ +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} + ----------------------------------------------------------------------------- -- | -- Module : Distribution.Simple.Program diff --git a/Cabal/Distribution/Simple/Program/Ar.hs b/Cabal/Distribution/Simple/Program/Ar.hs index 21aa347a123ce9365ebea15755f2dbd717b8b5ce..11650dc2fae13493fccde34c0360796c179bd3a5 100644 --- a/Cabal/Distribution/Simple/Program/Ar.hs +++ b/Cabal/Distribution/Simple/Program/Ar.hs @@ -1,4 +1,7 @@ +{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE NondecreasingIndentation #-} ----------------------------------------------------------------------------- -- | diff --git a/Cabal/Distribution/Simple/Program/Db.hs b/Cabal/Distribution/Simple/Program/Db.hs index 388621d84773d97d5991be1990ff039088dabc5f..a7860857bc9b79381442cb59c403e312b39dd50a 100644 --- a/Cabal/Distribution/Simple/Program/Db.hs +++ b/Cabal/Distribution/Simple/Program/Db.hs @@ -1,3 +1,6 @@ +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} + ----------------------------------------------------------------------------- -- | -- Module : Distribution.Simple.Program.Db diff --git a/Cabal/Distribution/Simple/Program/Find.hs b/Cabal/Distribution/Simple/Program/Find.hs index 2f3035b5fef1554e66d0177c74cfee7c575c2ca2..d6553aa8e80e7fb0e2dc1f7fc37502a019404e9a 100644 --- a/Cabal/Distribution/Simple/Program/Find.hs +++ b/Cabal/Distribution/Simple/Program/Find.hs @@ -1,4 +1,7 @@ -{-# LANGUAGE CPP, DeriveGeneric #-} +{-# LANGUAGE CPP #-} +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} ----------------------------------------------------------------------------- -- | diff --git a/Cabal/Distribution/Simple/Program/GHC.hs b/Cabal/Distribution/Simple/Program/GHC.hs index b4d58dc7fd71004e6a6264776a53a5e802107a6a..9b73903872df1f5413cd845be5f15347a7a4e615 100644 --- a/Cabal/Distribution/Simple/Program/GHC.hs +++ b/Cabal/Distribution/Simple/Program/GHC.hs @@ -1,4 +1,6 @@ {-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} module Distribution.Simple.Program.GHC ( GhcOptions(..), diff --git a/Cabal/Distribution/Simple/Program/HcPkg.hs b/Cabal/Distribution/Simple/Program/HcPkg.hs index 5e456147924e2a048540809d17c723176bb9b5dc..24995802d8edeee916e9f3a7fae8bac48b4b24bb 100644 --- a/Cabal/Distribution/Simple/Program/HcPkg.hs +++ b/Cabal/Distribution/Simple/Program/HcPkg.hs @@ -1,3 +1,6 @@ +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} + ----------------------------------------------------------------------------- -- | -- Module : Distribution.Simple.Program.HcPkg diff --git a/Cabal/Distribution/Simple/Program/Hpc.hs b/Cabal/Distribution/Simple/Program/Hpc.hs index 38a24fcb21098ddd3bf3f3c956264273be2f6fe9..6ed401c725121a432fe5f5ac296a6a57b11a2ca1 100644 --- a/Cabal/Distribution/Simple/Program/Hpc.hs +++ b/Cabal/Distribution/Simple/Program/Hpc.hs @@ -1,3 +1,6 @@ +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} + ----------------------------------------------------------------------------- -- | -- Module : Distribution.Simple.Program.Hpc diff --git a/Cabal/Distribution/Simple/Program/Ld.hs b/Cabal/Distribution/Simple/Program/Ld.hs index 4f1922e35089fa1b37c9879c10fc73da8e5175d9..323522a7535320cf3424a287e63f4ef3278eeef7 100644 --- a/Cabal/Distribution/Simple/Program/Ld.hs +++ b/Cabal/Distribution/Simple/Program/Ld.hs @@ -1,3 +1,6 @@ +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} + ----------------------------------------------------------------------------- -- | -- Module : Distribution.Simple.Program.Ld diff --git a/Cabal/Distribution/Simple/Program/Run.hs b/Cabal/Distribution/Simple/Program/Run.hs index ab3c645a396c7f92d104abd0210307ae92be602a..55f799965acd2fe6bfba31c90ba38e9fffd140fc 100644 --- a/Cabal/Distribution/Simple/Program/Run.hs +++ b/Cabal/Distribution/Simple/Program/Run.hs @@ -1,3 +1,6 @@ +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} + ----------------------------------------------------------------------------- -- | -- Module : Distribution.Simple.Program.Run diff --git a/Cabal/Distribution/Simple/Program/Strip.hs b/Cabal/Distribution/Simple/Program/Strip.hs index 43aafe5dd8bf3de985883e6634f69d43ad5f3ee1..890321c81deb17ee2215967f878bfa4d3ff463da 100644 --- a/Cabal/Distribution/Simple/Program/Strip.hs +++ b/Cabal/Distribution/Simple/Program/Strip.hs @@ -1,3 +1,6 @@ +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} + ----------------------------------------------------------------------------- -- | -- Module : Distribution.Simple.Program.Strip diff --git a/Cabal/Distribution/Simple/Program/Types.hs b/Cabal/Distribution/Simple/Program/Types.hs index 9a196f6563a8675611fa83fe6f3285528913d458..737cc35d0030ad37fb40db44ad111db9a1594d95 100644 --- a/Cabal/Distribution/Simple/Program/Types.hs +++ b/Cabal/Distribution/Simple/Program/Types.hs @@ -1,4 +1,6 @@ {-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} ----------------------------------------------------------------------------- -- | diff --git a/Cabal/Distribution/Simple/Register.hs b/Cabal/Distribution/Simple/Register.hs index a92c5a818f95ec5f955ff5acfa634e62f58a2a99..3814ac5ceb37b595aebc0c7940af2841f03c983a 100644 --- a/Cabal/Distribution/Simple/Register.hs +++ b/Cabal/Distribution/Simple/Register.hs @@ -1,4 +1,6 @@ -{-# LANGUAGE PatternGuards #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} + ----------------------------------------------------------------------------- -- | -- Module : Distribution.Simple.Register diff --git a/Cabal/Distribution/Simple/Setup.hs b/Cabal/Distribution/Simple/Setup.hs index fb5397125a26cef0cdccbfb758eeb0e41cba9357..f5f8d528620b5ed1b9891a39e3180213f2e6151d 100644 --- a/Cabal/Distribution/Simple/Setup.hs +++ b/Cabal/Distribution/Simple/Setup.hs @@ -1,5 +1,7 @@ {-# LANGUAGE CPP #-} {-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} ----------------------------------------------------------------------------- -- | diff --git a/Cabal/Distribution/Simple/SrcDist.hs b/Cabal/Distribution/Simple/SrcDist.hs index 3b97f53afb9f3de332b18d4e3424353b127066c8..2efe08cc9687757427801fc91563a5b28998a588 100644 --- a/Cabal/Distribution/Simple/SrcDist.hs +++ b/Cabal/Distribution/Simple/SrcDist.hs @@ -1,3 +1,6 @@ +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} + ----------------------------------------------------------------------------- -- | -- Module : Distribution.Simple.SrcDist diff --git a/Cabal/Distribution/Simple/Test.hs b/Cabal/Distribution/Simple/Test.hs index 65e23c852e7869a75ba1c12c960a6269d19329a7..e460af34dc9542aea3be6928595e09ff10d5a6a4 100644 --- a/Cabal/Distribution/Simple/Test.hs +++ b/Cabal/Distribution/Simple/Test.hs @@ -1,3 +1,6 @@ +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} + ----------------------------------------------------------------------------- -- | -- Module : Distribution.Simple.Test diff --git a/Cabal/Distribution/Simple/Test/ExeV10.hs b/Cabal/Distribution/Simple/Test/ExeV10.hs index f358a8b7df9f6006625871b7411e7c8eeb68ac3e..b3509caf7cda51df6fc64af7c8d85d84e34b1e44 100644 --- a/Cabal/Distribution/Simple/Test/ExeV10.hs +++ b/Cabal/Distribution/Simple/Test/ExeV10.hs @@ -1,3 +1,6 @@ +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} + module Distribution.Simple.Test.ExeV10 ( runTest ) where diff --git a/Cabal/Distribution/Simple/Test/LibV09.hs b/Cabal/Distribution/Simple/Test/LibV09.hs index c820c6f56a311b47677227434bf2c4cb54d561ad..95b44582b518666c8edc62b42d06d6f110e40fb8 100644 --- a/Cabal/Distribution/Simple/Test/LibV09.hs +++ b/Cabal/Distribution/Simple/Test/LibV09.hs @@ -1,3 +1,6 @@ +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} + module Distribution.Simple.Test.LibV09 ( runTest -- Test stub diff --git a/Cabal/Distribution/Simple/Test/Log.hs b/Cabal/Distribution/Simple/Test/Log.hs index 0065dc369284fd7d977cabcfe5614df2b1c7ef1b..ef14020ba8466039afa1fe4534c4818493a519a0 100644 --- a/Cabal/Distribution/Simple/Test/Log.hs +++ b/Cabal/Distribution/Simple/Test/Log.hs @@ -1,3 +1,6 @@ +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} + module Distribution.Simple.Test.Log ( PackageLog(..) , TestLogs(..) diff --git a/Cabal/Distribution/Simple/UHC.hs b/Cabal/Distribution/Simple/UHC.hs index 2ad6c47cd58848700f04de95948ad4e2105ab187..7a59fef8b86fff571ff39a70a9e3500922d5cb20 100644 --- a/Cabal/Distribution/Simple/UHC.hs +++ b/Cabal/Distribution/Simple/UHC.hs @@ -1,3 +1,6 @@ +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} + ----------------------------------------------------------------------------- -- | -- Module : Distribution.Simple.UHC diff --git a/Cabal/Distribution/Simple/UserHooks.hs b/Cabal/Distribution/Simple/UserHooks.hs index b3ba6cf9b99b2d9247b35b628badb70d85fdf495..28457b66be9e93e4a1b62cd13fc6fdadcc531ef7 100644 --- a/Cabal/Distribution/Simple/UserHooks.hs +++ b/Cabal/Distribution/Simple/UserHooks.hs @@ -1,3 +1,6 @@ +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} + ----------------------------------------------------------------------------- -- | -- Module : Distribution.Simple.UserHooks diff --git a/Cabal/Distribution/Simple/Utils.hs b/Cabal/Distribution/Simple/Utils.hs index fdf704c938f6925a78ae388f931716ab8ae94203..41febe3a1c32d304f8e1a168f56f9714a2f8dc11 100644 --- a/Cabal/Distribution/Simple/Utils.hs +++ b/Cabal/Distribution/Simple/Utils.hs @@ -1,6 +1,7 @@ -{-# LANGUAGE CPP, ForeignFunctionInterface, ScopedTypeVariables #-} +{-# LANGUAGE CPP #-} +{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE FlexibleContexts #-} -{-# LANGUAGE Rank2Types #-} +{-# LANGUAGE RankNTypes #-} ----------------------------------------------------------------------------- -- | -- Module : Distribution.Simple.Utils diff --git a/Cabal/Distribution/TestSuite.hs b/Cabal/Distribution/TestSuite.hs index 411265f9f8c56a9e1da3370675432bdf33e372bd..7276bfa2c390201253ac0a9117983505204639ca 100644 --- a/Cabal/Distribution/TestSuite.hs +++ b/Cabal/Distribution/TestSuite.hs @@ -1,3 +1,6 @@ +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} + ----------------------------------------------------------------------------- -- | -- Module : Distribution.TestSuite diff --git a/Cabal/Distribution/Types/LocalBuildInfo.hs b/Cabal/Distribution/Types/LocalBuildInfo.hs index abd1757fa01af51668e66c8a40f6f90b5f157f52..60a8e99a284b5256da105e4eb3dcc42bda1fc0af 100644 --- a/Cabal/Distribution/Types/LocalBuildInfo.hs +++ b/Cabal/Distribution/Types/LocalBuildInfo.hs @@ -1,5 +1,6 @@ {-# LANGUAGE DeriveGeneric #-} -{-# LANGUAGE PatternGuards #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} module Distribution.Types.LocalBuildInfo ( -- * The type diff --git a/Cabal/Distribution/Types/PackageDescription.hs b/Cabal/Distribution/Types/PackageDescription.hs index 959154c1b21f45124c817c6bd9c6d50d2767deba..5404395525b96894630a9aeded76e51e859c12ff 100644 --- a/Cabal/Distribution/Types/PackageDescription.hs +++ b/Cabal/Distribution/Types/PackageDescription.hs @@ -1,5 +1,7 @@ {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RankNTypes #-} ----------------------------------------------------------------------------- -- |