summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authordoyougnu <jeffrey.young@iohk.io>2022-05-19 13:25:23 -0400
committerdoyougnu <jeffrey.young@iohk.io>2022-06-13 13:42:45 -0400
commit345df225872e1cb39f363fc914c1ea071fc18c26 (patch)
treefda263cc3ad1ff1105c27f592240a6e60c191760
parent59bd0722fe65f7d7fc1810c8e2353f1049e07759 (diff)
downloadhaskell-345df225872e1cb39f363fc914c1ea071fc18c26.tar.gz
GHCi.FFI: ignore ffi.h and friends for js-backend
-rw-r--r--libraries/ghci/GHCi/FFI.hsc39
1 files changed, 35 insertions, 4 deletions
diff --git a/libraries/ghci/GHCi/FFI.hsc b/libraries/ghci/GHCi/FFI.hsc
index 74c9e175b1..64cb962325 100644
--- a/libraries/ghci/GHCi/FFI.hsc
+++ b/libraries/ghci/GHCi/FFI.hsc
@@ -6,7 +6,24 @@
--
-----------------------------------------------------------------------------
+{- Note [FFI for the JS-Backend]
+ ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
+ The JS-backend does not use GHC's native rts, as such you might think that it
+ doesn't require ghci. However, that is not true, because we need ghci in
+ order to interoperate with iserv even if we do not use any of the FFI stuff
+ in this file. So obviously we do not require libffi, but we still need to be
+ able to build ghci in order for the JS-Backend to supply its own iserv
+ interop solution. Thus we bite the bullet and wrap all the unneeded bits in a
+ CPP conditional compilation blocks that detect the JS-backend. A necessary
+ evil to be sure; notice that the only symbols remaining the JS_HOST_ARCH case
+ are those that are explicitly exported by this module and set to error if
+ they are every used.
+-}
+
+#if !defined(js_HOST_ARCH)
#include <ffi.h>
+#endif
{-# LANGUAGE CPP, DeriveGeneric, DeriveAnyClass #-}
module GHCi.FFI
@@ -18,11 +35,13 @@ module GHCi.FFI
) where
import Prelude -- See note [Why do we import Prelude here?]
+#if !defined(js_HOST_ARCH)
import Control.Exception
+import Foreign.C
+#endif
import Data.Binary
import GHC.Generics
import Foreign
-import Foreign.C
data FFIType
= FFIVoid
@@ -51,6 +70,7 @@ prepForeignCall
-> FFIType -- result type
-> IO (Ptr C_ffi_cif) -- token for making calls (must be freed by caller)
+#if !defined(js_HOST_ARCH)
prepForeignCall cconv arg_types result_type = do
let n_args = length arg_types
arg_arr <- mallocArray n_args
@@ -66,12 +86,25 @@ prepForeignCall cconv arg_types result_type = do
" res ty: ", show result_type, ")" ]
else
return (castPtr cif)
+#else
+prepForeignCall _ _ _ =
+ error "GHCi.FFI.prepForeignCall: Called with JS_HOST_ARCH! Perhaps you need to run configure?"
+#endif
+
freeForeignCallInfo :: Ptr C_ffi_cif -> IO ()
freeForeignCallInfo p = do
+#if !defined(js_HOST_ARCH)
free ((#ptr ffi_cif, arg_types) p)
free p
+#else
+ error "GHCi.FFI.freeForeignCallInfo: Called with JS_HOST_ARCH! Perhaps you need to run configure?"
+#endif
+data C_ffi_type
+data C_ffi_cif
+
+#if !defined(js_HOST_ARCH)
strError :: C_ffi_status -> String
strError r
| r == fFI_BAD_ABI
@@ -103,9 +136,6 @@ ffiType FFIUInt16 = ffi_type_uint16
ffiType FFIUInt32 = ffi_type_uint32
ffiType FFIUInt64 = ffi_type_uint64
-data C_ffi_type
-data C_ffi_cif
-
type C_ffi_status = (#type ffi_status)
type C_ffi_abi = (#type ffi_abi)
@@ -161,3 +191,4 @@ foreign import ccall "ffi_prep_cif"
-- -> Ptr () -- put result here
-- -> Ptr (Ptr ()) -- arg values
-- -> IO ()
+#endif