diff --git a/System/Posix/Temp.hsc b/System/Posix/Temp.hsc
index 473364c8b075ee7c67bb82776c98e4d856195984..398414480892da3fb848398b87975d9718a645d2 100644
--- a/System/Posix/Temp.hsc
+++ b/System/Posix/Temp.hsc
@@ -1,3 +1,4 @@
+{-# LANGUAGE CApiFFI #-}
 #if __GLASGOW_HASKELL__ >= 709
 {-# LANGUAGE Safe #-}
 #else
@@ -33,7 +34,7 @@ import System.Posix.IO
 import System.Posix.Types
 import System.Posix.Internals (withFilePath, peekFilePath)
 
-foreign import ccall unsafe "HsUnix.h __hscore_mkstemp"
+foreign import capi unsafe "HsUnix.h mkstemp"
   c_mkstemp :: CString -> IO CInt
 
 -- | Make a unique filename and open it for reading\/writing. The returned
@@ -53,7 +54,7 @@ mkstemp template' = do
     return (name, h)
 
 #if HAVE_MKSTEMPS
-foreign import ccall unsafe "HsUnix.h __hscore_mkstemps"
+foreign import capi unsafe "HsUnix.h mkstemps"
   c_mkstemps :: CString -> CInt -> IO CInt
 #endif
 
@@ -81,7 +82,7 @@ mkstemps = error "System.Posix.Temp.mkstemps: not available on this platform"
 #endif
 
 #if HAVE_MKDTEMP
-foreign import ccall unsafe "HsUnix.h __hscore_mkdtemp"
+foreign import capi unsafe "HsUnix.h mkdtemp"
   c_mkdtemp :: CString -> IO CString
 #endif
 
diff --git a/System/Posix/Temp/ByteString.hsc b/System/Posix/Temp/ByteString.hsc
index 67442fc36c44f0a481630178aa3a61b795254f01..0e30c6f345e11b285f4ce6f32bf75e7092b8398d 100644
--- a/System/Posix/Temp/ByteString.hsc
+++ b/System/Posix/Temp/ByteString.hsc
@@ -1,3 +1,4 @@
+{-# LANGUAGE CApiFFI #-}
 #if __GLASGOW_HASKELL__ >= 709
 {-# LANGUAGE Safe #-}
 #else
@@ -38,7 +39,7 @@ import System.Posix.Directory (createDirectory)
 import System.Posix.IO
 import System.Posix.Types
 
-foreign import ccall unsafe "HsUnix.h __hscore_mkstemp"
+foreign import capi unsafe "HsUnix.h mkstemp"
   c_mkstemp :: CString -> IO CInt
 
 -- | Make a unique filename and open it for reading\/writing. The returned
@@ -58,7 +59,7 @@ mkstemp template' = do
     return (name, h)
 
 #if HAVE_MKSTEMPS
-foreign import ccall unsafe "HsUnix.h __hscore_mkstemps"
+foreign import capi unsafe "HsUnix.h mkstemps"
   c_mkstemps :: CString -> CInt -> IO CInt
 #endif
 
@@ -82,7 +83,7 @@ mkstemps = error "System.Posix.Temp.mkstemps: not available on this platform"
 #endif
 
 #if HAVE_MKDTEMP
-foreign import ccall unsafe "HsUnix.h __hscore_mkdtemp"
+foreign import capi unsafe "HsUnix.h mkdtemp"
   c_mkdtemp :: CString -> IO CString
 #endif
 
diff --git a/cbits/HsUnix.c b/cbits/HsUnix.c
index 55f9679d8c4292b9958d640ec40530da3c9be02b..aec53686ec51dd2c9b2fc5b2a85044b28f148b24 100644
--- a/cbits/HsUnix.c
+++ b/cbits/HsUnix.c
@@ -65,22 +65,6 @@ int __hsunix_push_module(int fd, const char *module)
 #endif
 }
 
-int __hscore_mkstemp(char *filetemplate) {
-    return (mkstemp(filetemplate));
-}
-
-#if HAVE_MKSTEMPS
-int __hscore_mkstemps(char *filetemplate, int suffixlen) {
-    return (mkstemps(filetemplate, suffixlen));
-}
-#endif
-
-#if HAVE_MKDTEMP
-char *__hscore_mkdtemp(char *filetemplate) {
-    return (mkdtemp(filetemplate));
-}
-#endif
-
 #ifdef HAVE_UNSETENV
 int __hsunix_unsetenv(const char *name)
 {
diff --git a/include/HsUnix.h b/include/HsUnix.h
index 093c9e3dea4dfe5d4acfc292063ca280a74851a0..5daff0cc4559087417115d4ae9d21fc5e4bcdde3 100644
--- a/include/HsUnix.h
+++ b/include/HsUnix.h
@@ -134,16 +134,6 @@ int __hsunix_unlockpt(int fd);
 // push a SVR4 STREAMS module; do nothing if STREAMS not available
 int __hsunix_push_module(int fd, const char *module);
 
-int __hscore_mkstemp(char *filetemplate);
-
-#if HAVE_MKSTEMPS
-int __hscore_mkstemps(char *filetemplate, int suffixlen);
-#endif
-
-#if HAVE_MKDTEMP
-char *__hscore_mkdtemp(char *filetemplate);
-#endif
-
 int __hsunix_unsetenv(const char *name);
 
 /* A size that will contain many path names, but not necessarily all