[project @ 2005-04-29 08:19:49 by simonpj]
[ghc-hetmet.git] / ghc / compiler / main / DriverPipeline.hs
index c6d7a4d..fbd2d49 100644 (file)
@@ -20,7 +20,10 @@ module DriverPipeline (
    link, 
 
         -- DLL building
-   doMkDLL
+   doMkDLL,
+
+   getOptionsFromStringBuffer, -- used in module GHC
+   optionsErrorMsgs,           -- ditto
   ) where
 
 #include "HsVersions.h"
@@ -46,11 +49,15 @@ import StringBuffer ( hGetStringBuffer )
 import BasicTypes      ( SuccessFlag(..) )
 import Maybes          ( expectJust )
 import Ctype           ( is_ident )
-
-import ParserCoreUtils ( getCoreModuleName )
+import StringBuffer    ( StringBuffer(..), lexemeToString )
+import ParserCoreUtils ( getCoreModuleName )
+import SrcLoc          ( srcLocSpan, mkSrcLoc )
+import FastString      ( mkFastString )
+import Bag             ( listToBag, emptyBag )
 
 import EXCEPTION
 import DATA_IOREF      ( readIORef, writeIORef, IORef )
+import GLAEXTS         ( Int(..) )
 
 import Directory
 import System
@@ -86,9 +93,11 @@ preprocess dflags filename =
 -- NB.  No old interface can also mean that the source has changed.
 
 compile :: HscEnv
+       -> (Messages -> IO ())  -- error message callback
        -> ModSummary
        -> Maybe Linkable       -- Just linkable <=> source unchanged
         -> Maybe ModIface       -- Old interface, if available
+        -> Int -> Int
         -> IO CompResult
 
 data CompResult
@@ -99,7 +108,7 @@ data CompResult
    | CompErrs 
 
 
-compile hsc_env mod_summary maybe_old_linkable old_iface = do 
+compile hsc_env msg_act mod_summary maybe_old_linkable old_iface mod_index nmods = do 
 
    let dflags0     = hsc_dflags hsc_env
        this_mod    = ms_mod mod_summary
@@ -111,19 +120,22 @@ compile hsc_env mod_summary maybe_old_linkable old_iface = do
 
    showPass dflags0 ("Compiling " ++ showModMsg have_object mod_summary)
 
-   let verb      = verbosity dflags0
    let location          = ms_location mod_summary
    let input_fn   = expectJust "compile:hs" (ml_hs_file location) 
    let input_fnpp = expectJust "compile:hspp" (ms_hspp_file mod_summary)
 
-   when (verb >= 2) (hPutStrLn stderr ("compile: input file " ++ input_fnpp))
+   debugTraceMsg dflags0 2 ("compile: input file " ++ input_fnpp)
 
    -- Add in the OPTIONS from the source file
    -- This is nasty: we've done this once already, in the compilation manager
    -- It might be better to cache the flags in the ml_hspp_file field,say
-   opts <- getOptionsFromSource input_fnpp
-   (dflags1,unhandled_flags) <- parseDynamicFlags dflags0 opts
-   checkProcessArgsResult unhandled_flags input_fn
+   let hspp_buf = expectJust "compile:hspp_buf" (ms_hspp_buf mod_summary)
+       opts = getOptionsFromStringBuffer hspp_buf
+   (dflags1,unhandled_flags) <- parseDynamicFlags dflags0 (map snd opts)
+   if (not (null unhandled_flags))
+       then do msg_act (optionsErrorMsgs unhandled_flags opts input_fn)
+               return CompErrs
+       else do
 
    let (basename, _) = splitFilename input_fn
 
@@ -152,10 +164,12 @@ compile hsc_env mod_summary maybe_old_linkable old_iface = do
    let do_recomp = dopt Opt_RecompChecking dflags
        source_unchanged = isJust maybe_old_linkable && do_recomp
        hsc_env' = hsc_env { hsc_dflags = dflags' }
+       object_filename = ml_obj_file location
 
    -- run the compiler
-   hsc_result <- hscMain hsc_env' printErrorsAndWarnings mod_summary
+   hsc_result <- hscMain hsc_env' msg_act mod_summary
                         source_unchanged have_object old_iface
+                         (Just (mod_index, nmods))
 
    case hsc_result of
       HscFail -> return CompErrs
@@ -164,15 +178,17 @@ compile hsc_env mod_summary maybe_old_linkable old_iface = do
          ASSERT(isJust maybe_old_linkable)
          return (CompOK details iface maybe_old_linkable)
 
-      HscRecomp details iface
-               stub_h_exists stub_c_exists maybe_interpreted_code 
+      HscRecomp details iface stub_h_exists stub_c_exists maybe_interpreted_code 
 
        | isHsBoot src_flavour  -- No further compilation to do
-       -> return (CompOK details iface Nothing)
+       -> do   case hsc_lang of
+                  HscInterpreted -> return ()
+                  _other -> SysTools.touch dflags' "Touching object file" 
+                                           object_filename
+               return (CompOK details iface Nothing)
 
-       | otherwise             -- Normal Haskell source files
+       | otherwise     -- Normal source file
        -> do
-          let 
           maybe_stub_o <- compileStub dflags' stub_c_exists
           let stub_unlinked = case maybe_stub_o of
                                  Nothing -> []
@@ -183,8 +199,8 @@ compile hsc_env mod_summary maybe_old_linkable old_iface = do
 
                -- in interpreted mode, just return the compiled code
                -- as our "unlinked" object.
-               HscInterpreted -> 
-                   case maybe_interpreted_code of
+               HscInterpreted
+                 -> case maybe_interpreted_code of
 #ifdef GHCI
                       Just comp_bc -> return ([BCOs comp_bc], ms_hs_date mod_summary)
                        -- Why do we use the timestamp of the source file here,
@@ -196,16 +212,14 @@ compile hsc_env mod_summary maybe_old_linkable old_iface = do
 #endif
                       Nothing -> panic "compile: no interpreted code"
 
-               -- we're in batch mode: finish the compilation pipeline.
-               _other -> do
-                  let object_filename = ml_obj_file location
+               -- We're in --make mode: finish the compilation pipeline.
+               _other
+                 -> do runPipeline StopLn dflags output_fn Persistent
+                                   (Just location)
+                               -- The object filename comes from the ModLocation
 
-                  runPipeline StopLn dflags output_fn Persistent
-                              (Just location)
-                       -- the object filename comes from the ModLocation
-
-                  o_time <- getModificationTime object_filename
-                  return ([DotO object_filename], o_time)
+                       o_time <- getModificationTime object_filename
+                       return ([DotO object_filename], o_time)
 
           let linkable = LM unlinked_time this_mod
                             (hs_unlinked ++ stub_unlinked)
@@ -247,6 +261,9 @@ link Interactive dflags batch_attempt_linking hpt
         return Succeeded
 #endif
 
+link JustTypecheck dflags batch_attempt_linking hpt
+   = return Succeeded
+
 link BatchCompile dflags batch_attempt_linking hpt
    | batch_attempt_linking
    = do 
@@ -259,19 +276,16 @@ link BatchCompile dflags batch_attempt_linking hpt
            -- the linkables to link
            linkables = map (fromJust.hm_linkable) home_mod_infos
 
-        when (verb >= 3) $ do
-            hPutStrLn stderr "link: linkables are ..."
-             hPutStrLn stderr (showSDoc (vcat (map ppr linkables)))
+        debugTraceMsg dflags 3 "link: linkables are ..."
+        debugTraceMsg dflags 3 (showSDoc (vcat (map ppr linkables)))
 
        -- check for the -no-link flag
        if isNoLink (ghcLink dflags)
-         then do when (verb >= 3) $
-                   hPutStrLn stderr "link(batch): linking omitted (-c flag given)."
+         then do debugTraceMsg dflags 3 "link(batch): linking omitted (-c flag given)."
                  return Succeeded
          else do
 
-       when (verb >= 1) $
-             hPutStrLn stderr "Linking ..."
+       debugTraceMsg dflags 1 "Linking ..."
 
        let getOfiles (LM _ _ us) = map nameOfObject (filter isObject us)
            obj_files = concatMap getOfiles linkables
@@ -279,18 +293,15 @@ link BatchCompile dflags batch_attempt_linking hpt
        -- Don't showPass in Batch mode; doLink will do that for us.
         staticLink dflags obj_files pkg_deps
 
-        when (verb >= 3) (hPutStrLn stderr "link: done")
+        debugTraceMsg dflags 3 "link: done"
 
        -- staticLink only returns if it succeeds
         return Succeeded
 
    | otherwise
-   = do when (verb >= 3) $ do
-           hPutStrLn stderr "link(batch): upsweep (partially) failed OR"
-            hPutStrLn stderr "   Main.main not exported; not linking."
+   = do debugTraceMsg dflags 3 "link(batch): upsweep (partially) failed OR"
+        debugTraceMsg dflags 3 "   Main.main not exported; not linking."
         return Succeeded
-   where
-      verb = verbosity dflags
       
 
 -- -----------------------------------------------------------------------------
@@ -651,6 +662,7 @@ runPhase (Hsc src_flavour) stop dflags0 basename suff input_fn get_output_fn _ma
                                        ms_hspp_buf  = hspp_buf,
                                        ms_location  = location4,
                                        ms_hs_date   = src_timestamp,
+                                       ms_obj_date  = Nothing,
                                        ms_imps      = unused_field,
                                        ms_srcimps   = unused_field }
 
@@ -701,6 +713,7 @@ runPhase (Hsc src_flavour) stop dflags0 basename suff input_fn get_output_fn _ma
                          mod_summary source_unchanged 
                          False         -- No object file
                          Nothing       -- No iface
+                          Nothing       -- No "module i of n" progress info
 
        case result of
 
@@ -708,6 +721,9 @@ runPhase (Hsc src_flavour) stop dflags0 basename suff input_fn get_output_fn _ma
 
             HscNoRecomp details iface -> do
                SysTools.touch dflags' "Touching object file" o_file
+                       -- The .o file must have a later modification date
+                       -- than the source file (else we wouldn't be in HscNoRecomp)
+                       -- but we touch it anyway, to keep 'make' happy (we think).
                return (StopLn, dflags', Just location4, o_file)
 
            HscRecomp _details _iface 
@@ -1303,6 +1319,24 @@ getOptionsFromSource file
                               return (opts ++ rest)
                       | otherwise -> return []
 
+getOptionsFromStringBuffer :: StringBuffer -> [(Int,String)]
+getOptionsFromStringBuffer buffer@(StringBuffer _ len# _) = 
+  let 
+       ls = lines (lexemeToString buffer (I# len#))  -- lazy, so it's ok
+  in
+  look 1 ls
+  where
+       look i [] = []
+       look i (l':ls) = do
+           let l = removeSpaces l'
+           case () of
+               () | null l -> look (i+1) ls
+                  | prefixMatch "#" l -> look (i+1) ls
+                  | prefixMatch "{-# LINE" l -> look (i+1) ls   -- -}
+                  | Just opts <- matchOptions l
+                       -> zip (repeat i) opts ++ look (i+1) ls
+                  | otherwise -> []
+
 -- detect {-# OPTIONS_GHC ... #-}.  For the time being, we accept OPTIONS
 -- instead of OPTIONS_GHC, but that is deprecated.
 matchOptions s
@@ -1329,6 +1363,19 @@ matchOptions s
     | otherwise = Nothing
 
 
+optionsErrorMsgs :: [String] -> [(Int,String)] -> FilePath -> Messages
+optionsErrorMsgs unhandled_flags flags_lines filename
+  = (emptyBag, listToBag (map mkMsg unhandled_flags_lines))
+  where
+       unhandled_flags_lines = [ (l,f) | f <- unhandled_flags, 
+                                         (l,f') <- flags_lines, f == f' ]
+       mkMsg (line,flag) = 
+           ErrUtils.mkPlainErrMsg (srcLocSpan loc) $
+               text "unknown flag in  {-# OPTIONS #-} pragma:" <+> text flag
+         where
+               loc = mkSrcLoc (mkFastString filename) line 0
+               -- ToDo: we need a better SrcSpan here
+
 -- -----------------------------------------------------------------------------
 -- Misc.