summaryrefslogtreecommitdiff
path: root/libraries/ghc-prim
diff options
context:
space:
mode:
authorJohn Ericson <git@JohnEricson.me>2019-06-30 23:33:09 -0400
committerMarge Bot <ben+marge-bot@smart-cactus.org>2019-07-14 01:19:22 -0400
commitff04eb5973b69fcc60e7d0945a74becd068c1888 (patch)
tree4a5fe83657fec03529ab3724cf33d9e15219c7ec /libraries/ghc-prim
parenta7176fa1bf42dd4f22381d238f6e65d76290887e (diff)
downloadhaskell-ff04eb5973b69fcc60e7d0945a74becd068c1888.tar.gz
Remove purely external primops
The compiler doesn't create uses nor compiles the uses that exist specially. These are just plain C-- FFI. These `await*` ones are especially important to so convert because "true" primops are hard to make platform-specific currently. The other exports are part of this commit so this module always exports something, which avoids silly CPP elsewhere. More will be added later once `foreign import prim` is extended.
Diffstat (limited to 'libraries/ghc-prim')
-rw-r--r--libraries/ghc-prim/GHC/Prim/Ext.hs105
-rw-r--r--libraries/ghc-prim/ghc-prim.cabal1
2 files changed, 106 insertions, 0 deletions
diff --git a/libraries/ghc-prim/GHC/Prim/Ext.hs b/libraries/ghc-prim/GHC/Prim/Ext.hs
new file mode 100644
index 0000000000..402d5725c8
--- /dev/null
+++ b/libraries/ghc-prim/GHC/Prim/Ext.hs
@@ -0,0 +1,105 @@
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE UnboxedTuples #-}
+{-# LANGUAGE NoImplicitPrelude #-}
+{-# LANGUAGE GHCForeignImportPrim #-}
+{-# LANGUAGE UnliftedFFITypes #-}
+
+-- We need platform defines (tests for mingw32 below).
+#include "ghcplatform.h"
+#include "MachDeps.h"
+
+-- See note [When do out-of-line primops go in primops.txt.pp]. More primops
+-- there are elgible according to the description below, but cannot yet be moved
+-- here because of superficial restrictions to `foreign import prim`. Hopefully
+-- that is fixed soon.
+
+-- | Extra C-- routines exposed from the RTS
+--
+-- Actual primops are emitted by the compiler itself. They are special bits of
+-- code with backend support. The foreign functions in this module aren't actual
+-- primops because the compiler doesn't care about them at all: they just are
+-- extra foreign C-- calls libraries can make into the RTS.
+--
+-- Note that 'GHC.Prim' has the same haddock section names as this module, but
+-- with descriptions. Consult that module's documentation for what each section means.
+-- are described over there.
+module GHC.Prim.Ext
+ (
+ -- 64-bit bit aliases
+ INT64
+ , WORD64
+ -- * Delay\/wait operations
+#if defined(mingw32_TARGET_OS)
+ , asyncRead#
+ , asyncWrite#
+ , asyncDoProc#
+#endif
+ -- * Misc
+ , getThreadAllocationCounter#
+ ) where
+
+import GHC.Prim
+import GHC.Types () -- Make implicit dependency known to build system
+
+default () -- Double and Integer aren't available yet
+
+------------------------------------------------------------------------
+-- 64-bit bit aliases
+------------------------------------------------------------------------
+
+type INT64 =
+#if WORD_SIZE_IN_BITS < 64
+ Int64#
+#else
+ Int#
+#endif
+
+type WORD64 =
+#if WORD_SIZE_IN_BITS < 64
+ Word64#
+#else
+ Word#
+#endif
+
+------------------------------------------------------------------------
+-- Delay/wait operations
+------------------------------------------------------------------------
+
+#if defined(mingw32_TARGET_OS)
+
+-- | Asynchronously read bytes from specified file descriptor.
+foreign import prim "stg_asyncReadzh" asyncRead#
+ :: Int#
+ -> Int#
+ -> Int#
+ -> Addr#
+ -> State# RealWorld
+ -> (# State# RealWorld, Int#, Int# #)
+
+-- | Asynchronously write bytes from specified file descriptor.
+foreign import prim "stg_asyncWritezh" asyncWrite#
+ :: Int#
+ -> Int#
+ -> Int#
+ -> Addr#
+ -> State# RealWorld
+ -> (# State# RealWorld, Int#, Int# #)
+
+-- | Asynchronously perform procedure (first arg), passing it 2nd arg.
+foreign import prim "stg_asyncDoProczh" asyncDoProc#
+ :: Addr#
+ -> Addr#
+ -> State# RealWorld
+ -> (# State# RealWorld, Int#, Int# #)
+
+#endif
+
+------------------------------------------------------------------------
+-- Misc
+------------------------------------------------------------------------
+
+-- | Retrieves the allocation counter for the current thread.
+foreign import prim "stg_getThreadAllocationCounterzh" getThreadAllocationCounter#
+ :: State# RealWorld
+ -> (# State# RealWorld, INT64 #)
diff --git a/libraries/ghc-prim/ghc-prim.cabal b/libraries/ghc-prim/ghc-prim.cabal
index bfc47c87c2..040eb43b27 100644
--- a/libraries/ghc-prim/ghc-prim.cabal
+++ b/libraries/ghc-prim/ghc-prim.cabal
@@ -45,6 +45,7 @@ Library
GHC.Debug
GHC.IntWord64
GHC.Magic
+ GHC.Prim.Ext
GHC.PrimopWrappers
GHC.Tuple
GHC.Types