FFI: Incompatible pointer to integer conversion

Let’s say we have the file FunPtrs.hs with the following contents:

{-# LANGUAGE ForeignFunctionInterface #-}

module FunPtrs where

import Foreign.Ptr

foreign import ccall "wrapper" 
  mk'callback :: IO (Ptr Int) -> IO (FunPtr (IO (Ptr Int)))

Compiling this (with both GHC-9.2.7 and GHC-9.6.1 on aarch64-darwin) yields the following warning:

ghc ./FunPtrs.hs
[1 of 1] Compiling FunPtrs          ( /Users/bas/Downloads/FunPtrs.hs, /Users/bas/Downloads/FunPtrs.o )

/var/folders/7_/m1k33c791pz5v9nt2bdd89d80000gn/T/ghc89726_0/ghc_2.c:19:17: error:
     warning: incompatible pointer to integer conversion assigning to 'ffi_arg' (aka 'unsigned long') from 'HsPtr' (aka 'void *') [-Wint-conversion]
   |
19 | *(ffi_arg*)resp = cret;
   |                 ^
*(ffi_arg*)resp = cret;
                ^ ~~~~
1 warning generated.

According to the docs of FunPtr:

  • the return type is either a marshallable foreign type or has the form IO t where t is a marshallable foreign type or ().

Isn’t Ptr Int a marshallable foreign type? I thought that it was, so why am I getting this warning?

If I replace the return type to a non-pointer like Int the warning disappears.

The warning also doesn’t happen on x86_64-linux.

(Also reported as a GHC issue:
#23456: FFI: Incompatible pointer to integer conversion · Issues · Glasgow Haskell Compiler / GHC · GitLab)