Skip to content
Snippets Groups Projects
Commit ff04eb59 authored by John Ericson's avatar John Ericson Committed by Marge Bot
Browse files

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.
parent a7176fa1
No related branches found
No related tags found
No related merge requests found
......@@ -68,8 +68,8 @@
defaults
has_side_effects = False
out_of_line = False -- See Note Note [PrimOp can_fail and has_side_effects] in PrimOp
can_fail = False -- See Note Note [PrimOp can_fail and has_side_effects] in PrimOp
out_of_line = False -- See Note [When do out-of-line primops go in primops.txt.pp]
can_fail = False -- See Note [PrimOp can_fail and has_side_effects] in PrimOp
commutable = False
code_size = { primOpCodeSizeDefault }
strictness = { \ arity -> mkClosedStrictSig (replicate arity topDmd) topRes }
......@@ -78,15 +78,48 @@ defaults
vector = []
deprecated_msg = {} -- A non-empty message indicates deprecation
-- Note [When do out-of-line primops go in primops.txt.pp]
-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
--
-- Out of line primops are those with a C-- implementation. But that
-- doesn't mean they *just* have an C-- implementation. As mentioned in
-- Note [Inlining out-of-line primops and heap checks], some out-of-line
-- primops also have additional internal implementations under certain
-- conditions. Now that `foreign import prim` exists, only those primops
-- which have both internal and external implementations ought to be
-- this file. The rest aren't really primops, since they don't need
-- bespoke compiler support but just a general way to interface with
-- C--. They are just foreign calls.
--
-- Unfortunately, for the time being most of the primops which should be
-- moved according to the previous paragraph can't yet. There are some
-- superficial restrictions in `foreign import prim` which mus be fixed
-- first. Specifically, `foreign import prim` always requires:
--
-- - No polymorphism in type
-- - `strictness = <default>`
-- - `can_fail = False`
-- - `has_side_effects = True`
--
-- https://gitlab.haskell.org/ghc/ghc/issues/16929 tracks this issue,
-- and has a table of which external-only primops are blocked by which
-- of these. Hopefully those restrictions are relaxed so the rest of
-- those can be moved over.
--
-- 'module GHC.Prim.Ext is a temporarily "holding ground" for primops
-- that were formally in here, until they can be given a better home.
-- Likewise, their underlying C-- implementation need not live in the
-- RTS either. Best case (in my view), both the C-- and `foreign import
-- prim` can be moved to a small library tailured to the features being
-- implemented and dependencies of those features.
-- Currently, documentation is produced using latex, so contents of
-- description fields should be legal latex. Descriptions can contain
-- matched pairs of embedded curly brackets.
#include "MachDeps.h"
-- We need platform defines (tests for mingw32 below).
#include "ghc_boot_platform.h"
section "The word size story."
{Haskell98 specifies that signed integers (type {\tt Int})
must contain at least 30 bits. GHC always implements {\tt
......@@ -2797,30 +2830,6 @@ primop WaitWriteOp "waitWrite#" GenPrimOp
has_side_effects = True
out_of_line = True
#if defined(mingw32_TARGET_OS)
primop AsyncReadOp "asyncRead#" GenPrimOp
Int# -> Int# -> Int# -> Addr# -> State# RealWorld-> (# State# RealWorld, Int#, Int# #)
{Asynchronously read bytes from specified file descriptor.}
with
has_side_effects = True
out_of_line = True
primop AsyncWriteOp "asyncWrite#" GenPrimOp
Int# -> Int# -> Int# -> Addr# -> State# RealWorld-> (# State# RealWorld, Int#, Int# #)
{Asynchronously write bytes from specified file descriptor.}
with
has_side_effects = True
out_of_line = True
primop AsyncDoProcOp "asyncDoProc#" GenPrimOp
Addr# -> Addr# -> State# RealWorld-> (# State# RealWorld, Int#, Int# #)
{Asynchronously perform procedure (first arg), passing it 2nd arg.}
with
has_side_effects = True
out_of_line = True
#endif
------------------------------------------------------------------------
section "Concurrency primitives"
------------------------------------------------------------------------
......@@ -3413,13 +3422,6 @@ primop TraceMarkerOp "traceMarker#" GenPrimOp
has_side_effects = True
out_of_line = True
primop GetThreadAllocationCounter "getThreadAllocationCounter#" GenPrimOp
State# RealWorld -> (# State# RealWorld, INT64 #)
{ Retrieves the allocation counter for the current thread. }
with
has_side_effects = True
out_of_line = True
primop SetThreadAllocationCounter "setThreadAllocationCounter#" GenPrimOp
INT64 -> State# RealWorld -> State# RealWorld
{ Sets the allocation counter for the current thread to the given value. }
......
......@@ -116,7 +116,7 @@ module GHC.Base
module GHC.Magic,
module GHC.Types,
module GHC.Prim, -- Re-export GHC.Prim and [boot] GHC.Err,
-- to avoid lots of people having to
module GHC.Prim.Ext, -- to avoid lots of people having to
module GHC.Err, -- import it explicitly
module GHC.Maybe
)
......@@ -127,6 +127,7 @@ import GHC.Classes
import GHC.CString
import GHC.Magic
import GHC.Prim
import GHC.Prim.Ext
import GHC.Err
import GHC.Maybe
import {-# SOURCE #-} GHC.IO (failIO,mplusIO)
......
......@@ -52,6 +52,7 @@ import GHC.Real (div, fromIntegral)
import GHC.Show (Show)
import GHC.Word (Word32, Word64)
import GHC.Windows
import GHC.Prim.Ext
#if defined(mingw32_HOST_OS)
# if defined(i386_HOST_ARCH)
......
......@@ -29,6 +29,7 @@ module GHC.Exts
-- * Primitive operations
module GHC.Prim,
module GHC.Prim.Ext,
shiftL#, shiftRL#, iShiftL#, iShiftRA#, iShiftRL#,
uncheckedShiftL64#, uncheckedShiftRL64#,
uncheckedIShiftL64#, uncheckedIShiftRA64#,
......@@ -89,6 +90,7 @@ module GHC.Exts
import GHC.Prim hiding ( coerce, TYPE )
import qualified GHC.Prim
import qualified GHC.Prim.Ext
import GHC.Base hiding ( coerce )
import GHC.Word
import GHC.Int
......
{-# 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 #)
......@@ -45,6 +45,7 @@ Library
GHC.Debug
GHC.IntWord64
GHC.Magic
GHC.Prim.Ext
GHC.PrimopWrappers
GHC.Tuple
GHC.Types
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment