Repository : ssh://darcs.haskell.org//srv/darcs/ghc

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/3e314cc2060734ade9b82d4da418c119b3a05b4c

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

commit 3e314cc2060734ade9b82d4da418c119b3a05b4c
Author: Ian Lynagh <[email protected]>
Date:   Tue Apr 24 23:12:25 2012 +0100

    Add a flag for the unsupported calling convention warning

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

 compiler/main/DynFlags.hs        |    7 +++++--
 compiler/typecheck/TcForeign.lhs |    5 ++++-
 2 files changed, 9 insertions(+), 3 deletions(-)

diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs
index c04b474..a497ded 100644
--- a/compiler/main/DynFlags.hs
+++ b/compiler/main/DynFlags.hs
@@ -357,6 +357,7 @@ data WarningFlag =
    | Opt_WarnUnsafe
    | Opt_WarnSafe
    | Opt_WarnPointlessPragmas
+   | Opt_WarnUnsupportedCallingConventions
    deriving (Eq, Show, Enum)
 
 data Language = Haskell98 | Haskell2010
@@ -1842,7 +1843,8 @@ fWarningFlags = [
   ( "warn-alternative-layout-rule-transitional", 
Opt_WarnAlternativeLayoutRuleTransitional, nop ),
   ( "warn-unsafe",                      Opt_WarnUnsafe, setWarnUnsafe ),
   ( "warn-safe",                        Opt_WarnSafe, setWarnSafe ),
-  ( "warn-pointless-pragmas",           Opt_WarnPointlessPragmas, nop ) ]
+  ( "warn-pointless-pragmas",           Opt_WarnPointlessPragmas, nop ),
+  ( "warn-unsupported-calling-conventions", 
Opt_WarnUnsupportedCallingConventions, nop ) ]
 
 -- | These @-f\<blah\>@ flags can all be reversed with @-fno-\<blah\>@
 fFlags :: [FlagSpec DynFlag]
@@ -2174,7 +2176,8 @@ standardWarnings
         Opt_WarnDodgyForeignImports,
         Opt_WarnWrongDoBind,
         Opt_WarnAlternativeLayoutRuleTransitional,
-        Opt_WarnPointlessPragmas
+        Opt_WarnPointlessPragmas,
+        Opt_WarnUnsupportedCallingConventions
       ]
 
 minusWOpts :: [WarningFlag]
diff --git a/compiler/typecheck/TcForeign.lhs b/compiler/typecheck/TcForeign.lhs
index ae8ac26..34632a5 100644
--- a/compiler/typecheck/TcForeign.lhs
+++ b/compiler/typecheck/TcForeign.lhs
@@ -48,6 +48,8 @@ import Platform
 import SrcLoc
 import Bag
 import FastString
+
+import Control.Monad
 \end{code}
 
 \begin{code}
@@ -454,7 +456,8 @@ checkCConv StdCallConv  = do dflags <- getDynFlags
                              if platformArch platform == ArchX86
                                  then return StdCallConv
                                  else do -- This is a warning, not an error. 
see #3336
-                                         addWarnTc (text "the 'stdcall' 
calling convention is unsupported on this platform," $$ text "treating as 
ccall")
+                                         when (wopt 
Opt_WarnUnsupportedCallingConventions dflags) $
+                                             addWarnTc (text "the 'stdcall' 
calling convention is unsupported on this platform," $$ text "treating as 
ccall")
                                          return CCallConv
 checkCConv PrimCallConv = do addErrTc (text "The `prim' calling convention can 
only be used with `foreign import'")
                              return PrimCallConv



_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to