[Git][ghc/ghc][master] Improve prepForeignCall error reporting
Marge Bot
gitlab at gitlab.haskell.org
Sat Apr 18 17:21:53 UTC 2020
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
15ab6cd5 by Ömer Sinan Ağacan at 2020-04-18T13:21:44-04:00
Improve prepForeignCall error reporting
Show parameters and description of the error code when ffi_prep_cif
fails.
This may be helpful for debugging #17018.
- - - - -
1 changed file:
- libraries/ghci/GHCi/FFI.hsc
Changes:
=====================================
libraries/ghci/GHCi/FFI.hsc
=====================================
@@ -58,15 +58,29 @@ prepForeignCall cconv arg_types result_type = do
cif <- mallocBytes (#const sizeof(ffi_cif))
let abi = convToABI cconv
r <- ffi_prep_cif cif abi (fromIntegral n_args) (ffiType result_type) arg_arr
- if (r /= fFI_OK)
- then throwIO (ErrorCall ("prepForeignCallFailed: " ++ show r))
- else return (castPtr cif)
+ if r /= fFI_OK then
+ throwIO $ ErrorCall $ concat
+ [ "prepForeignCallFailed: ", strError r,
+ "(cconv: ", show cconv,
+ " arg tys: ", show arg_types,
+ " res ty: ", show result_type, ")" ]
+ else
+ return (castPtr cif)
freeForeignCallInfo :: Ptr C_ffi_cif -> IO ()
freeForeignCallInfo p = do
free ((#ptr ffi_cif, arg_types) p)
free p
+strError :: C_ffi_status -> String
+strError r
+ | r == fFI_BAD_ABI
+ = "invalid ABI (FFI_BAD_ABI)"
+ | r == fFI_BAD_TYPEDEF
+ = "invalid type description (FFI_BAD_TYPEDEF)"
+ | otherwise
+ = "unknown error: " ++ show r
+
convToABI :: FFIConv -> C_ffi_abi
convToABI FFICCall = fFI_DEFAULT_ABI
#if defined(mingw32_HOST_OS) && defined(i386_HOST_ARCH)
@@ -108,12 +122,10 @@ foreign import ccall "&ffi_type_float" ffi_type_float :: Ptr C_ffi_type
foreign import ccall "&ffi_type_double" ffi_type_double :: Ptr C_ffi_type
foreign import ccall "&ffi_type_pointer"ffi_type_pointer :: Ptr C_ffi_type
-fFI_OK :: C_ffi_status
-fFI_OK = (#const FFI_OK)
---fFI_BAD_ABI :: C_ffi_status
---fFI_BAD_ABI = (#const FFI_BAD_ABI)
---fFI_BAD_TYPEDEF :: C_ffi_status
---fFI_BAD_TYPEDEF = (#const FFI_BAD_TYPEDEF)
+fFI_OK, fFI_BAD_ABI, fFI_BAD_TYPEDEF :: C_ffi_status
+fFI_OK = (#const FFI_OK)
+fFI_BAD_ABI = (#const FFI_BAD_ABI)
+fFI_BAD_TYPEDEF = (#const FFI_BAD_TYPEDEF)
fFI_DEFAULT_ABI :: C_ffi_abi
fFI_DEFAULT_ABI = (#const FFI_DEFAULT_ABI)
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/15ab6cd548f284732a7f89d78c2b89b1bfc4ea1d
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/15ab6cd548f284732a7f89d78c2b89b1bfc4ea1d
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/20200418/321bdd71/attachment-0001.html>
More information about the ghc-commits
mailing list