Make BinIface warning-free
[ghc-hetmet.git] / compiler / iface / BinIface.hs
index 3443e6a..321eac1 100644 (file)
@@ -1,16 +1,11 @@
+
 -- 
 --  (c) The University of Glasgow 2002-2006
 -- 
 -- Binary interface file support.
 
-{-# OPTIONS_GHC -w #-}
--- The above warning supression flag is a temporary kludge.
--- While working on this module you are encouraged to remove it and fix
--- any warnings in the module. See
---     http://hackage.haskell.org/trac/ghc/wiki/WorkingConventions#Warnings
--- for details
-
-module BinIface ( writeBinIface, readBinIface, v_IgnoreHiWay ) where
+module BinIface ( writeBinIface, readBinIface,
+                  CheckHiWay(..), TraceBinIFaceReading(..) ) where
 
 #include "HsVersions.h"
 
@@ -31,11 +26,9 @@ import UniqFM
 import UniqSupply
 import CostCentre
 import StaticFlags
-import PackageConfig
 import Panic
 import Binary
 import SrcLoc
-import Util
 import ErrUtils
 import Config
 import FastMutInt
@@ -48,72 +41,89 @@ import Data.IORef
 import Control.Exception
 import Control.Monad
 
+data CheckHiWay = CheckHiWay | IgnoreHiWay
+    deriving Eq
+
+data TraceBinIFaceReading = TraceBinIFaceReading | QuietBinIFaceReading
+    deriving Eq
+
 -- ---------------------------------------------------------------------------
 -- Reading and writing binary interface files
 
-readBinIface :: FilePath -> TcRnIf a b ModIface
-readBinIface hi_path = do
+readBinIface :: CheckHiWay -> TraceBinIFaceReading -> FilePath
+             -> TcRnIf a b ModIface
+readBinIface checkHiWay traceBinIFaceReading hi_path = do
   nc <- getNameCache
-  (new_nc, iface) <- ioToIOEnv $ readBinIface_ hi_path nc
+  (new_nc, iface) <- liftIO $
+    readBinIface_ checkHiWay traceBinIFaceReading hi_path nc
   setNameCache new_nc
   return iface
 
-readBinIface_ :: FilePath -> NameCache -> IO (NameCache, ModIface)
-readBinIface_ hi_path nc = do
+readBinIface_ :: CheckHiWay -> TraceBinIFaceReading -> FilePath -> NameCache
+              -> IO (NameCache, ModIface)
+readBinIface_ checkHiWay traceBinIFaceReading hi_path nc = do
+  let printer :: SDoc -> IO ()
+      printer = case traceBinIFaceReading of
+                TraceBinIFaceReading -> \sd -> printSDoc sd defaultDumpStyle
+                QuietBinIFaceReading -> \_ -> return ()
+      wantedGot :: Outputable a => String -> a -> a -> IO ()
+      wantedGot what wanted got
+          = printer (text what <> text ": " <>
+                     vcat [text "Wanted " <> ppr wanted <> text ",",
+                           text "got    " <> ppr got])
+      errorOnMismatch :: (Eq a, Show a) => String -> a -> a -> IO ()
+      errorOnMismatch what wanted got
+            -- This will be caught by readIface which will emit an error
+            -- msg containing the iface module name.
+          = when (wanted /= got) $ throwDyn $ ProgramError
+                        (what ++ " (wanted " ++ show wanted
+                              ++ ", got "    ++ show got ++ ")")
   bh <- Binary.readBinMem hi_path
 
-       -- Read the magic number to check that this really is a GHC .hi file
-       -- (This magic number does not change when we change 
-       --  GHC interface file format)
+        -- Read the magic number to check that this really is a GHC .hi file
+        -- (This magic number does not change when we change
+        --  GHC interface file format)
   magic <- get bh
-  when (magic /= binaryInterfaceMagic) $
-       throwDyn (ProgramError (
-          "magic number mismatch: old/corrupt interface file?"))
+  wantedGot "Magic" binaryInterfaceMagic magic
+  errorOnMismatch "magic number mismatch: old/corrupt interface file?"
+      binaryInterfaceMagic magic
 
         -- Get the dictionary pointer.  We won't attempt to actually
         -- read the dictionary until we've done the version checks below,
         -- just in case this isn't a valid interface.  In retrospect the
         -- version should have come before the dictionary pointer, but this
         -- is the way it was done originally, and we can't change it now.
-  dict_p <- Binary.get bh      -- Get the dictionary ptr
+  dict_p <- Binary.get bh       -- Get the dictionary ptr
 
         -- Check the interface file version and ways.
   check_ver  <- get bh
   let our_ver = show opt_HiVersion
-  when (check_ver /= our_ver) $
-        -- This will be caught by readIface which will emit an error
-        -- msg containing the iface module name.
-    throwDyn (ProgramError (
-        "mismatched interface file versions: expected "
-        ++ our_ver ++ ", found " ++ check_ver))
+  wantedGot "Version" our_ver check_ver
+  errorOnMismatch "mismatched interface file versions" our_ver check_ver
 
   check_way <- get bh
-  ignore_way <- readIORef v_IgnoreHiWay
   way_descr <- getWayDescr
-  when (not ignore_way && check_way /= way_descr) $
-        -- This will be caught by readIface
-        -- which will emit an error msg containing the iface module name.
-     throwDyn (ProgramError (
-       "mismatched interface file ways: expected "
-       ++ way_descr ++ ", found " ++ check_way))
-
-       -- Read the dictionary
-       -- The next word in the file is a pointer to where the dictionary is
-       -- (probably at the end of the file)
-  data_p <- tellBin bh         -- Remember where we are now
+  wantedGot "Way" way_descr check_way
+  when (checkHiWay == CheckHiWay) $
+       errorOnMismatch "mismatched interface file ways" way_descr check_way
+
+        -- Read the dictionary
+        -- The next word in the file is a pointer to where the dictionary is
+        -- (probably at the end of the file)
+  data_p <- tellBin bh          -- Remember where we are now
   seekBin bh dict_p
   dict <- getDictionary bh
-  seekBin bh data_p            -- Back to where we were before
+  seekBin bh data_p             -- Back to where we were before
 
-       -- Initialise the user-data field of bh
+        -- Initialise the user-data field of bh
   ud <- newReadState dict
   bh <- return (setUserData bh ud)
-       
-  symtab_p <- Binary.get bh    -- Get the symtab ptr
-  data_p <- tellBin bh         -- Remember where we are now
+        
+  symtab_p <- Binary.get bh     -- Get the symtab ptr
+  data_p <- tellBin bh          -- Remember where we are now
   seekBin bh symtab_p
   (nc', symtab) <- getSymbolTable bh nc
-  seekBin bh data_p            -- Back to where we were before
+  seekBin bh data_p             -- Back to where we were before
   let ud = getUserData bh
   bh <- return $! setUserData bh ud{ud_symtab = symtab}
   iface <- get bh
@@ -175,15 +185,17 @@ writeBinIface dflags hi_path mod_iface = do
        -- And send the result to the file
   writeBinMem bh hi_path
 
-initBinMemSize       = (1024*1024) :: Int
+initBinMemSize :: Int
+initBinMemSize = 1024 * 1024
 
 -- The *host* architecture version:
 #include "MachDeps.h"
 
+binaryInterfaceMagic :: Word32
 #if   WORD_SIZE_IN_BITS == 32
-binaryInterfaceMagic = 0x1face :: Word32
+binaryInterfaceMagic = 0x1face
 #elif WORD_SIZE_IN_BITS == 64
-binaryInterfaceMagic = 0x1face64 :: Word32
+binaryInterfaceMagic = 0x1face64
 #endif
   
 -- -----------------------------------------------------------------------------
@@ -213,7 +225,7 @@ fromOnDiskName
    -> NameCache
    -> OnDiskName
    -> (NameCache, Name)
-fromOnDiskName arr nc (pid, mod_name, occ) =
+fromOnDiskName _ nc (pid, mod_name, occ) =
   let 
         mod   = mkModule pid mod_name
         cache = nsNames nc
@@ -232,7 +244,7 @@ fromOnDiskName arr nc (pid, mod_name, occ) =
         }
 
 serialiseName :: BinHandle -> Name -> UniqFM (Int,Name) -> IO ()
-serialiseName bh name symtab = do
+serialiseName bh name _ = do
   let mod = nameModule name
   put_ bh (modulePackageId mod, moduleName mod, nameOccName name)
 
@@ -367,8 +379,6 @@ instance Binary ModIface where
                 mi_fix_fn    = mkIfaceFixCache fixities,
                 mi_ver_fn    = mkIfaceVerCache decls })
 
-GLOBAL_VAR(v_IgnoreHiWay, False, Bool)
-
 getWayDescr :: IO String
 getWayDescr = do
   tag <- readIORef v_Build_tag
@@ -428,7 +438,7 @@ instance Binary Usage where
                        usg_exports = exps, usg_entities = ents,
                        usg_rules = rules })
 
-instance Binary a => Binary (Deprecs a) where
+instance Binary Deprecations where
     put_ bh NoDeprecs     = putByte bh 0
     put_ bh (DeprecAll t) = do
            putByte bh 1
@@ -846,6 +856,7 @@ instance Binary IfacePredType where
              2 -> do ac <- get bh
                      ad <- get bh
                      return (IfaceEqPred ac ad)
+             _ -> panic ("get IfacePredType " ++ show h)
 
 -------------------------------------------------------------------------
 --             IfaceExpr and friends
@@ -946,6 +957,7 @@ instance Binary IfaceExpr where
               12 -> do m <- get bh
                        ix <- get bh
                        return (IfaceTick m ix)
+              _ -> panic ("get IfaceExpr " ++ show h)
 
 instance Binary IfaceConAlt where
     put_ bh IfaceDefault = do
@@ -1052,6 +1064,7 @@ instance Binary IfaceNote where
              3 -> do return IfaceInlineMe
               4 -> do ac <- get bh
                       return (IfaceCoreNote ac)
+              _ -> panic ("get IfaceNote " ++ show h)
 
 -------------------------------------------------------------------------
 --             IfaceDecl and friends
@@ -1069,7 +1082,7 @@ instance Binary IfaceDecl where
            put_ bh (occNameFS name)
            put_ bh ty
            put_ bh idinfo
-    put_ bh (IfaceForeign ae af) = 
+    put_ _ (IfaceForeign _ _) = 
        error "Binary.put_(IfaceDecl): IfaceForeign"
     put_ bh (IfaceData a1 a2 a3 a4 a5 a6 a7 a8) = do
            putByte bh 2
@@ -1169,6 +1182,7 @@ instance Binary OverlapFlag where
                  0 -> return NoOverlap
                  1 -> return OverlapOk
                  2 -> return Incoherent
+                 _ -> panic ("get OverlapFlag " ++ show h)
 
 instance Binary IfaceConDecls where
     put_ bh IfAbstractTyCon = putByte bh 0