[commit: ghc] wip/remove-cabal-dep: Fix warnings arising from the package db refactoring (7925a43)

git at git.haskell.org git at git.haskell.org
Sun Aug 24 22:47:34 UTC 2014


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/remove-cabal-dep
Link       : http://ghc.haskell.org/trac/ghc/changeset/7925a43240e7155274f723f0d9a7b5335aff7473/ghc

>---------------------------------------------------------------

commit 7925a43240e7155274f723f0d9a7b5335aff7473
Author: Duncan Coutts <duncan at well-typed.com>
Date:   Fri Aug 22 15:57:07 2014 +0100

    Fix warnings arising from the package db refactoring


>---------------------------------------------------------------

7925a43240e7155274f723f0d9a7b5335aff7473
 libraries/bin-package-db/GHC/PackageDb.hs | 10 +++++-----
 utils/ghc-pkg/Main.hs                     |  6 +-----
 2 files changed, 6 insertions(+), 10 deletions(-)

diff --git a/libraries/bin-package-db/GHC/PackageDb.hs b/libraries/bin-package-db/GHC/PackageDb.hs
index 08dabd2..b29d707 100644
--- a/libraries/bin-package-db/GHC/PackageDb.hs
+++ b/libraries/bin-package-db/GHC/PackageDb.hs
@@ -1,6 +1,6 @@
 {-# LANGUAGE CPP #-}
 -- This module deliberately defines orphan instances for now (Binary Version).
-{-# OPTIONS_GHC -fno-warn-orphans #-}
+{-# OPTIONS_GHC -fno-warn-orphans -fno-warn-name-shadowing #-}
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  GHC.PackageDb
@@ -246,10 +246,10 @@ writeFileAtomic targetPath content = do
   let (targetDir, targetName) = splitFileName targetPath
   Exception.bracketOnError
     (openBinaryTempFileWithDefaultPermissions targetDir $ targetName <.> "tmp")
-    (\(tmpPath, handle) -> hClose handle >> removeFile tmpPath)
-    (\(tmpPath, handle) -> do
-        BS.Lazy.hPut handle content
-        hClose handle
+    (\(tmpPath, hnd) -> hClose hnd >> removeFile tmpPath)
+    (\(tmpPath, hnd) -> do
+        BS.Lazy.hPut hnd content
+        hClose hnd
 #if mingw32_HOST_OS || mingw32_TARGET_OS
         renameFile tmpPath targetPath
           -- If the targetPath exists then renameFile will fail
diff --git a/utils/ghc-pkg/Main.hs b/utils/ghc-pkg/Main.hs
index d9af8fb..858797f 100644
--- a/utils/ghc-pkg/Main.hs
+++ b/utils/ghc-pkg/Main.hs
@@ -1,5 +1,6 @@
 {-# LANGUAGE CPP, TypeSynonymInstances, FlexibleInstances, RecordWildCards,
              GeneralizedNewtypeDeriving, StandaloneDeriving #-}
+{-# OPTIONS_GHC -fno-warn-orphans #-}
 -----------------------------------------------------------------------------
 --
 -- (c) The University of Glasgow 2004-2009.
@@ -13,7 +14,6 @@ module Main (main) where
 import Version ( version, targetOS, targetARCH )
 import qualified GHC.PackageDb as GhcPkg
 import qualified Distribution.Simple.PackageIndex as PackageIndex
-import qualified Distribution.Package as Cabal
 import qualified Distribution.ModuleName as ModuleName
 import Distribution.ModuleName (ModuleName)
 import Distribution.InstalledPackageInfo as Cabal
@@ -1899,10 +1899,6 @@ throwIOIO = Exception.throwIO
 catchIO :: IO a -> (Exception.IOException -> IO a) -> IO a
 catchIO = Exception.catch
 
-catchError :: IO a -> (String -> IO a) -> IO a
-catchError io handler = io `Exception.catch` handler'
-    where handler' (Exception.ErrorCall err) = handler err
-
 tryIO :: IO a -> IO (Either Exception.IOException a)
 tryIO = Exception.try
 



More information about the ghc-commits mailing list