diff --git a/ghc/compiler/absCSyn/CallConv.lhs b/ghc/compiler/absCSyn/CallConv.lhs
index d09d063218fe70c7871c4184620efcadacd44a06..97a92bb27f2a7ae81904aef7610999c210c0998a 100644
--- a/ghc/compiler/absCSyn/CallConv.lhs
+++ b/ghc/compiler/absCSyn/CallConv.lhs
@@ -11,6 +11,7 @@ module CallConv
 
        , stdCallConv
        , cCallConv
+       , defaultCallConv
        , callConvAttribute
        , decorateExtName
        ) where
@@ -33,6 +34,9 @@ stdCallConv = 0
 
 cCallConv  :: CallConv
 cCallConv = 1
+
+defaultCallConv :: CallConv
+defaultCallConv = cCallConv
 \end{code}
 
 Generate the gcc attribute corresponding to the given
diff --git a/ghc/compiler/parser/hsparser.y b/ghc/compiler/parser/hsparser.y
index 30bfa6f2b7bbb45e3c20b16d38f7bedc28e94d16..d4befff5ebc565870324e45380c392a8e574a0ca 100644
--- a/ghc/compiler/parser/hsparser.y
+++ b/ghc/compiler/parser/hsparser.y
@@ -555,8 +555,8 @@ callconv: STDCALL 	{ $$ = CALLCONV_STDCALL;  }
 	| C_CALL        { $$ = CALLCONV_CCALL;    }
 	| PASCAL        { $$ = CALLCONV_PASCAL;   }
 	| FASTCALL      { $$ = CALLCONV_FASTCALL; }
-/* If you leave out the specification of a calling convention, you'll get C's. */
-        | /*empty*/     { $$ = CALLCONV_CCALL;    }
+/* If you leave out the specification of a calling convention, you'll (probably) get C's. */
+        | /*empty*/     { $$ = CALLCONV_NONE;    }
 	;
 
 ext_name: STRING	{ $$ = mkjust(lsing($1)); }
diff --git a/ghc/compiler/parser/utils.h b/ghc/compiler/parser/utils.h
index 4ebf921a538e10f30829e5a8fbe538ea243a7861..76d0d0e5b3eba18e5c92824bb480c3c7f16c1560 100644
--- a/ghc/compiler/parser/utils.h
+++ b/ghc/compiler/parser/utils.h
@@ -115,6 +115,7 @@ void	checkprec PROTO((tree, qid, BOOLEAN));
 */
 
 /* FFI predefines */
+#define CALLCONV_NONE     (-1)
 #define CALLCONV_STDCALL  0
 #define CALLCONV_CCALL    1
 #define CALLCONV_PASCAL   2
diff --git a/ghc/compiler/reader/ReadPrefix.lhs b/ghc/compiler/reader/ReadPrefix.lhs
index 8024e08f60669e9d4309fdcd22ddc44d382a66aa..44e8e6295655662c16b1a2774370b8d457ceca27 100644
--- a/ghc/compiler/reader/ReadPrefix.lhs
+++ b/ghc/compiler/reader/ReadPrefix.lhs
@@ -962,7 +962,12 @@ wlkExtName (U_just pt)
       [mod,nm] -> returnUgn (ExtName nm (Just mod))
 
 rdCallConv :: Int -> UgnM CallConv
-rdCallConv x = returnUgn x
+rdCallConv x = 
+   -- this tracks the #defines in parser/utils.h
+  case x of
+    (-1) -> -- no calling convention specified, use default.
+          returnUgn defaultCallConv
+    _    -> returnUgn x
 
 rdForKind :: Int -> Bool -> UgnM ForKind
 rdForKind 0 isUnsafe = -- foreign import