From 9a0dbd72c242b4a4ec7e6760bda9cf774fd8001e Mon Sep 17 00:00:00 2001
From: sof <unknown>
Date: Fri, 13 Nov 1998 19:34:34 +0000
Subject: [PATCH] [project @ 1998-11-13 19:34:33 by sof] Allow 'foreign import'
 calling conv. to be optional

---
 ghc/compiler/parser/hsparser.y     | 2 ++
 ghc/compiler/reader/ReadPrefix.lhs | 7 ++++---
 2 files changed, 6 insertions(+), 3 deletions(-)

diff --git a/ghc/compiler/parser/hsparser.y b/ghc/compiler/parser/hsparser.y
index 8a691fdcaf37..30bfa6f2b7bb 100644
--- a/ghc/compiler/parser/hsparser.y
+++ b/ghc/compiler/parser/hsparser.y
@@ -555,6 +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;    }
 	;
 
 ext_name: STRING	{ $$ = mkjust(lsing($1)); }
diff --git a/ghc/compiler/reader/ReadPrefix.lhs b/ghc/compiler/reader/ReadPrefix.lhs
index 33ef93b7c0e3..8024e08f6066 100644
--- a/ghc/compiler/reader/ReadPrefix.lhs
+++ b/ghc/compiler/reader/ReadPrefix.lhs
@@ -608,7 +608,7 @@ wlkBinding binding
 	  wlkHsType ty				   `thenUgn` \ h_ty ->
 	  wlkExtName ext_name			   `thenUgn` \ h_ext_name ->
 	  rdCallConv cconv		           `thenUgn` \ h_cconv ->
-	  rdImpExp imp_exp (cvFlag unsafe_flag)    `thenUgn` \ h_imp_exp ->
+	  rdForKind imp_exp (cvFlag unsafe_flag)    `thenUgn` \ h_imp_exp ->
  	  returnUgn (RdrForeignDecl (ForeignDecl h_id h_imp_exp h_ty h_ext_name h_cconv src_loc))
 
       a_sig_we_hope ->
@@ -967,8 +967,9 @@ rdCallConv x = returnUgn x
 rdForKind :: Int -> Bool -> UgnM ForKind
 rdForKind 0 isUnsafe = -- foreign import
   returnUgn (FoImport isUnsafe)
-rdImpExp 1 _ = -- foreign export
+rdForKind 1 _ = -- foreign export
   returnUgn FoExport
-rdImpExp 2 _ = -- foreign label
+rdForKind 2 _ = -- foreign label
   returnUgn FoLabel
+
 \end{code}
-- 
GitLab