Skip to content
Snippets Groups Projects
Commit 67dd5635 authored by Ben Gamari's avatar Ben Gamari
Browse files

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.
parent 237194ce
No related branches found
No related tags found
No related merge requests found
Pipeline #92123 failed
......@@ -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
-}
{-# 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# #)
42
#include "Cmm.h"
hello() {
return (42);
}
{-# 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# #)
42
#include "Cmm.h"
hello(W_ n) {
return (2*n);
}
{-# 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', () #)
#include "Cmm.h"
section "data" {
test_str: bits8[] "hello";
}
hello() {
ccall puts(test_str);
return ();
}
......@@ -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'])
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment