Warning police: eliminate all defaulting within stage1
authorIsaac Dupree <id@isaac.cedarswampstudios.org>
Tue, 7 Aug 2007 12:14:54 +0000 (12:14 +0000)
committerIsaac Dupree <id@isaac.cedarswampstudios.org>
Tue, 7 Aug 2007 12:14:54 +0000 (12:14 +0000)
Defaulting makes compilation of multiple modules more complicated (re: #1405)
Although it was all locally within functions, not because of the module
monomorphism-restriction... but it's better to be clear what's meant, anyway.
I changed some that were defaulting to Integer, to explicit Int, where Int
seemed appropriate rather than Integer.

compiler/codeGen/CgHpc.hs
compiler/deSugar/DsForeign.lhs
compiler/main/BreakArray.hs
compiler/main/SysTools.lhs
compiler/parser/Lexer.x
compiler/utils/Pretty.lhs
compiler/utils/StringBuffer.lhs

index 6da243b..811029b 100644 (file)
@@ -48,7 +48,7 @@ hpcTable this_mod (HpcInfo hpc_tickCount _) = do
                         emitData Data $ [ CmmDataLabel (mkHpcTicksLabel this_mod)
                                         ] ++
                                         [ CmmStaticLit (CmmInt 0 I64)
-                                        | _ <- take hpc_tickCount [0..]
+                                        | _ <- take hpc_tickCount [0::Int ..]
                                         ]
   where
     module_name_str = moduleNameString (Module.moduleName this_mod)
index 6c58176..e7d5c39 100644 (file)
@@ -448,7 +448,7 @@ mkFExportCBits c_nm maybe_target arg_htys res_hty is_IO_res_ty cc
                MachRep)]       -- the MachRep
   arg_info  = [ (text ('a':show n), showStgType ty, ty, 
                 typeMachRep (getPrimTyOf ty))
-             | (ty,n) <- zip arg_htys [1..] ]
+             | (ty,n) <- zip arg_htys [1::Int ..] ]
 
   -- add some auxiliary args; the stable ptr in the wrapper case, and
   -- a slot for the dummy return address in the wrapper + ccall case
index dbae88a..50a1170 100644 (file)
@@ -26,8 +26,8 @@ import Constants
 data BreakArray = BA (MutableByteArray# RealWorld)
 
 breakOff, breakOn :: Word
-breakOn  = fromIntegral 1
-breakOff = fromIntegral 0
+breakOn  = 1
+breakOff = 0
 
 -- XXX crude
 showBreakArray :: BreakArray -> IO ()
index e58270d..64e7b78 100644 (file)
@@ -579,7 +579,8 @@ newTempName dflags extn
   = do d <- getTempDir dflags
        x <- getProcessID
        findTempName (d ++ "/ghc" ++ show x ++ "_") 0
-  where 
+  where
+    findTempName :: FilePath -> Integer -> IO FilePath
     findTempName prefix x
       = do let filename = (prefix ++ show x) `joinFileExt` extn
           b  <- doesFileExist filename
@@ -596,6 +597,8 @@ getTempDir dflags@(DynFlags{tmpDir=tmp_dir})
            Nothing ->
                do x <- getProcessID
                   let prefix = tmp_dir ++ "/ghc" ++ show x ++ "_"
+                  let
+                      mkTempDir :: Integer -> IO FilePath
                       mkTempDir x
                        = let dirname = prefix ++ show x
                          in do createDirectory dirname
@@ -719,7 +722,11 @@ builderMainLoop dflags filter_fn pgm real_args mb_env = do
   hSetBuffering hStdErr LineBuffering
   forkIO (readerProc chan hStdOut filter_fn)
   forkIO (readerProc chan hStdErr filter_fn)
-  rc <- loop chan hProcess 2 1 ExitSuccess
+  -- we don't want to finish until 2 streams have been completed
+  -- (stdout and stderr)
+  -- nor until 1 exit code has been retrieved.
+  rc <- loop chan hProcess (2::Integer) (1::Integer) ExitSuccess
+  -- after that, we're done here.
   hClose hStdIn
   hClose hStdOut
   hClose hStdErr
index 8b637da..96f1ad2 100644 (file)
@@ -774,7 +774,7 @@ multiline_doc_comment span buf _len = withLexedDocType (worker "")
 nested_comment :: P (Located Token) -> Action
 nested_comment cont span _str _len = do
   input <- getInput
-  go 1 input
+  go (1::Int) input
   where
     go 0 input = do setInput input; cont
     go n input = case alexGetChar input of
index 96ea1fb..51ecf31 100644 (file)
@@ -446,7 +446,7 @@ int      n = text (show n)
 integer  n = text (show n)
 float    n = text (show n)
 double   n = text (show n)
-rational n = text (show (fromRat n))
+rational n = text (show (fromRat n :: Double))
 --rational n = text (show (fromRationalX n)) -- _showRational 30 n)
 
 quotes p        = char '`' <> p <> char '\''
index 1835945..e02a3ba 100644 (file)
@@ -113,7 +113,7 @@ hGetStringBufferBlock handle wanted
          withForeignPtr buf $ \ptr ->
              do r <- if size == 0 then return 0 else hGetBuf handle ptr size
                 if r /= size
-                   then ioError (userError $ "short read of file: "++show(r,size,fromIntegral size_i,handle))
+                   then ioError (userError $ "short read of file: "++show(r,size,size_i,handle))
                    else do pokeArray (ptr `plusPtr` size :: Ptr Word8) [0,0,0]
                            return (StringBuffer buf size 0)