[Git][ghc/ghc][ghc-9.10] 4 commits: EPA: Fix FamDecl range

Ben Gamari (@bgamari) gitlab at gitlab.haskell.org
Fri Mar 29 13:57:34 UTC 2024



Ben Gamari pushed to branch ghc-9.10 at Glasgow Haskell Compiler / GHC


Commits:
a17965fc by Alan Zimmerman at 2024-03-28T15:50:35-04:00
EPA: Fix FamDecl range

The span was incorrect if opt_datafam_kind_sig was empty

- - - - -
89dee1d6 by Alan Zimmerman at 2024-03-28T15:50:39-04:00
EPA: do not duplicate comments in signature RHS

(cherry picked from commit d2ba41e8c3e71d70a0f80dcc3f588ecbdc5ce4b2)

- - - - -
7d9c2102 by Ben Gamari at 2024-03-28T15:50:56-04:00
compiler: Allow more types in GHCForeignImportPrim

For many, many years `GHCForeignImportPrim` has suffered from the rather
restrictive limitation of not allowing any non-trivial types in arguments
or results. This limitation was justified by the code generator allegely
barfing in the presence of such types.

However, this restriction appears to originate well before the NCG
rewrite and the new NCG does not appear to have any trouble with such
types (see the added `T24598` test). Lift this restriction.

Fixes #24598.

- - - - -
16e1fca2 by Ben Gamari at 2024-03-28T15:51:22-04:00
Fix type of _get_osfhandle foreign import

Fixes #24601.

- - - - -


15 changed files:

- compiler/GHC/Hs/Utils.hs
- compiler/GHC/Parser.y
- compiler/GHC/Runtime/Utils.hs
- compiler/GHC/Tc/Gen/Foreign.hs
- testsuite/tests/ffi/should_fail/ccfail001.stderr
- + testsuite/tests/ffi/should_run/T24598.hs
- + testsuite/tests/ffi/should_run/T24598.stdout
- + testsuite/tests/ffi/should_run/T24598_cmm.cmm
- + testsuite/tests/ffi/should_run/T24598b.hs
- + testsuite/tests/ffi/should_run/T24598b.stdout
- + testsuite/tests/ffi/should_run/T24598b_cmm.cmm
- + testsuite/tests/ffi/should_run/T24598c.hs
- + testsuite/tests/ffi/should_run/T24598c.stdout
- + testsuite/tests/ffi/should_run/T24598c_cmm.cmm
- testsuite/tests/ffi/should_run/all.T


Changes:

=====================================
compiler/GHC/Hs/Utils.hs
=====================================
@@ -736,12 +736,12 @@ mkBigLHsPatTup = mkChunkified mkLHsPatTup
 
 -- | Convert an 'LHsType' to an 'LHsSigType'.
 hsTypeToHsSigType :: LHsType GhcPs -> LHsSigType GhcPs
-hsTypeToHsSigType lty@(L loc ty) = L loc $ case ty of
+hsTypeToHsSigType lty@(L loc ty) = case ty of
   HsForAllTy { hst_tele = HsForAllInvis { hsf_xinvis = an
                                         , hsf_invis_bndrs = bndrs }
              , hst_body = body }
-    -> mkHsExplicitSigType an bndrs body
-  _ -> mkHsImplicitSigType lty
+    -> L loc $ mkHsExplicitSigType an bndrs body
+  _ -> L (l2l loc) $ mkHsImplicitSigType lty -- The annotations are in lty, erase them from loc
 
 -- | Convert an 'LHsType' to an 'LHsSigWcType'.
 hsTypeToHsSigWcType :: LHsType GhcPs -> LHsSigWcType GhcPs


=====================================
compiler/GHC/Parser.y
=====================================
@@ -1313,7 +1313,7 @@ ty_decl :: { LTyClDecl GhcPs }
 
           -- data/newtype family
         | 'data' 'family' type opt_datafam_kind_sig
-                {% mkFamDecl (comb3 $1 $2 $4) DataFamily TopLevel $3
+                {% mkFamDecl (comb4 $1 $2 $3 $4) DataFamily TopLevel $3
                                    (snd $ unLoc $4) Nothing
                           (mj AnnData $1:mj AnnFamily $2:(fst $ unLoc $4)) }
 


=====================================
compiler/GHC/Runtime/Utils.hs
=====================================
@@ -29,7 +29,7 @@ foreign import ccall "io.h _close"
    c__close :: CInt -> IO CInt
 
 foreign import ccall unsafe "io.h _get_osfhandle"
-   _get_osfhandle :: CInt -> IO CInt
+   _get_osfhandle :: CInt -> IO CIntPtr
 
 runWithPipesPOSIX :: (CreateProcess -> IO ProcessHandle)
                   -> FilePath -> [String] -> [String] -> IO (ProcessHandle, Handle, Handle)


=====================================
compiler/GHC/Tc/Gen/Foreign.hs
=====================================
@@ -84,7 +84,6 @@ import Control.Monad.Trans.Writer.CPS
 import Control.Monad.Trans.Class
   ( lift )
 import Data.Maybe (isJust)
-import GHC.Types.RepType (tyConPrimRep)
 import GHC.Builtin.Types (unitTyCon)
 
 -- Defines a binding
@@ -737,7 +736,6 @@ marshalablePrimTyCon tc = isPrimTyCon tc && not (isLiftedTypeKind (tyConResKind
 marshalableTyCon :: DynFlags -> TyCon -> Validity' TypeCannotBeMarshaledReason
 marshalableTyCon dflags tc
   | marshalablePrimTyCon tc
-  , not (null (tyConPrimRep tc)) -- Note [Marshalling void]
   = validIfUnliftedFFITypes dflags
   | otherwise
   = boxedMarshalableTyCon tc
@@ -772,7 +770,6 @@ legalFIPrimResultTyCon :: DynFlags -> TyCon -> Validity' TypeCannotBeMarshaledRe
 -- types and also unboxed tuple and sum result types.
 legalFIPrimResultTyCon dflags tc
   | marshalablePrimTyCon tc
-  , not (null (tyConPrimRep tc))   -- Note [Marshalling void]
   = validIfUnliftedFFITypes dflags
 
   | isUnboxedTupleTyCon tc || isUnboxedSumTyCon tc
@@ -786,13 +783,3 @@ validIfUnliftedFFITypes dflags
   | xopt LangExt.UnliftedFFITypes dflags =  IsValid
   | otherwise = NotValid UnliftedFFITypesNeeded
 
-{-
-Note [Marshalling void]
-~~~~~~~~~~~~~~~~~~~~~~~
-We don't treat State# (whose PrimRep is VoidRep) as marshalable.
-In turn that means you can't write
-        foreign import foo :: Int -> State# RealWorld
-
-Reason: the back end falls over with panic "primRepHint:VoidRep";
-        and there is no compelling reason to permit it
--}


=====================================
testsuite/tests/ffi/should_fail/ccfail001.stderr
=====================================
@@ -1,6 +1,8 @@
 
-ccfail001.hs:10:1: error: [GHC-89401]
+ccfail001.hs:10:1: error: [GHC-10964]
     • Unacceptable result type in foreign declaration:
         ‘State# RealWorld’ cannot be marshalled in a foreign call
+        UnliftedFFITypes is required to marshal unlifted types
     • When checking declaration:
         foreign import ccall safe foo :: Int -> State# RealWorld
+    Suggested fix: Perhaps you intended to use UnliftedFFITypes


=====================================
testsuite/tests/ffi/should_run/T24598.hs
=====================================
@@ -0,0 +1,20 @@
+{-# LANGUAGE GHCForeignImportPrim #-}
+{-# LANGUAGE UnboxedTuples #-}
+{-# LANGUAGE UnliftedFFITypes #-}
+{-# LANGUAGE MagicHash #-}
+
+-- | Test that `foreign import prim` imports handle `State#` in results correctly.
+module Main where
+
+import GHC.IO
+import GHC.Int
+import GHC.Exts
+
+foreign import prim "hello"
+  hello# :: State# RealWorld -> (# State# RealWorld, Int# #)
+
+main :: IO ()
+main = hello >>= print
+
+hello :: IO Int
+hello = IO $ \s -> case hello# s of (# s', n# #) -> (# s', I# n# #)


=====================================
testsuite/tests/ffi/should_run/T24598.stdout
=====================================
@@ -0,0 +1 @@
+42


=====================================
testsuite/tests/ffi/should_run/T24598_cmm.cmm
=====================================
@@ -0,0 +1,5 @@
+#include "Cmm.h"
+
+hello() {
+    return (42);
+}


=====================================
testsuite/tests/ffi/should_run/T24598b.hs
=====================================
@@ -0,0 +1,22 @@
+{-# LANGUAGE GHCForeignImportPrim #-}
+{-# LANGUAGE UnboxedTuples #-}
+{-# LANGUAGE UnliftedFFITypes #-}
+{-# LANGUAGE MagicHash #-}
+
+-- | Test that `foreign import prim` imports handle `State#` in arguments correctly.
+module Main where
+
+import GHC.IO
+import GHC.Int
+import GHC.Exts
+
+foreign import prim "hello"
+  hello# :: Int# -> State# RealWorld -> (# State# RealWorld, Int# #)
+
+main :: IO ()
+main = hello 21 >>= print
+
+hello :: Int -> IO Int
+hello (I# n#) = IO $ \s ->
+  case hello# n# s of (# s', n# #) -> (# s', I# n# #)
+


=====================================
testsuite/tests/ffi/should_run/T24598b.stdout
=====================================
@@ -0,0 +1 @@
+42


=====================================
testsuite/tests/ffi/should_run/T24598b_cmm.cmm
=====================================
@@ -0,0 +1,5 @@
+#include "Cmm.h"
+
+hello(W_ n) {
+    return (2*n);
+}


=====================================
testsuite/tests/ffi/should_run/T24598c.hs
=====================================
@@ -0,0 +1,21 @@
+{-# LANGUAGE GHCForeignImportPrim #-}
+{-# LANGUAGE UnboxedTuples #-}
+{-# LANGUAGE UnliftedFFITypes #-}
+{-# LANGUAGE MagicHash #-}
+
+-- | Test that `foreign import prim` imports handle `State#` in arguments correctly.
+module Main where
+
+import GHC.IO
+import GHC.Exts
+
+foreign import prim "hello"
+  hello# :: State# RealWorld -> State# RealWorld
+
+main :: IO ()
+main = hello
+
+hello :: IO ()
+hello = IO $ \s ->
+  case hello# s of s' -> (# s', () #)
+


=====================================
testsuite/tests/ffi/should_run/T24598c.stdout
=====================================
@@ -0,0 +1 @@
+hello


=====================================
testsuite/tests/ffi/should_run/T24598c_cmm.cmm
=====================================
@@ -0,0 +1,11 @@
+#include "Cmm.h"
+
+section "data" {
+  test_str: bits8[] "hello";
+}
+
+hello() {
+    ccall puts(test_str);
+    return ();
+}
+


=====================================
testsuite/tests/ffi/should_run/all.T
=====================================
@@ -268,3 +268,7 @@ test('T24314',
       # libffi-wasm doesn't support more than 4 args yet
       when(arch('wasm32'), skip)],
      compile_and_run, ['T24314_c.c'])
+
+test('T24598', req_cmm, compile_and_run, ['T24598_cmm.cmm'])
+test('T24598b', req_cmm, compile_and_run, ['T24598b_cmm.cmm'])
+test('T24598c', req_cmm, compile_and_run, ['T24598c_cmm.cmm'])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6ecd5f2ff97af53c7334f2d8581651203a2c6b7d...16e1fca214c4f90d9d881e44cb82bd193231204b

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6ecd5f2ff97af53c7334f2d8581651203a2c6b7d...16e1fca214c4f90d9d881e44cb82bd193231204b
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20240329/55af2530/attachment-0001.html>


More information about the ghc-commits mailing list