haskell / core-libraries-committee

95 stars 16 forks source link

Add `ConstPtr` to Foreign.C.Types #118

Closed bgamari closed 1 year ago

bgamari commented 1 year ago

As noted in ghc#22034, foreign imports using the CApiFFI extension must match the imported function's C signature in const-ness lest the compiler-generated wrapper may produce compile-time errors. However, currently base offers no means of expressing const pointers.

I propose that we introduce the following in Foreign.C.Types:

type ConstPtr :: Type -> Type
type role ConstPtr phantom
newtype ConstPtr a = ConstPtr { unConstPtr :: Ptr a }

instance Eq (ConstPtr a)
instance Ord (ConstPtr a)
instance Show (ConstPtr a)
instance Storable (ConstPtr a)
instance Data a => Data (ConstPtr a)

Assuming a is marshalled to C as CTYPE a value of type ConstPtr a would be marshalled to C as const CTYPE*

I opted to place these in Foreign.C.ConstPtr as const is a characteristic of the C ABI. Other options include:

Note that the goal of this proposal is merely to allow precise specification of const arguments in capi foreign imports (addressing ghc#22034). The goal is expressly not to provide a "safe" notion of pointer to constant data, complementing the mutable Foreign.Ptr.

Bodigrim commented 1 year ago

@bgamari how about Foreign.C.ConstPtr?

Foreign.C.Types is dedicated to platform-specific types (like CLong) and is a part of Haskell Report. A new module with a clear remit would avoid both complications.

bgamari commented 1 year ago

@Bodigrim, that sounds good to me.

treeowl commented 1 year ago

Are we talking about constant pointers

int * const p

or pointers to constants?

const int *p

Presumably we want both?

thielema commented 1 year ago

On Tue, 17 Jan 2023, Ben Gamari wrote:

As noted in ghc#22043, foreign imports using the CApiFFI extension must match the imported function's C signature in const-ness lest the compiler-generated wrapper may produce compile-time errors. However, currently base offers no means of expressing const pointers.

I propose that we introduce the following in Foreign.C.Types:

type ConstPtr :: Type -> Type type role ConstPtr phantom newtype ConstPtr a = ConstPtr { unConstPtr :: Ptr a }

What about a pointer type with a phantom for the readability of the Ptr, i.e.

newtype BlaPtr mode a = BlaPtr (Ptr a)

where 'mode' can be Const or just left as type variable.

This would simplify passing a read/write pointer to a constant pointer argument.

bgamari commented 1 year ago

@treeowl we are referring to pointers to constants. The fact that an argument of non-pointer type is declared as const is a detail of its implementation does not change its ABI. For this reason, signatures needn't include such const occurrences and typically don't. For instance, it is fine to write:

int hello(int *c);
int hello(int *const c) { return *c; }

By contrast, the following will be rejected:

int hello(int *c);
int hello(const int * c) { return *c; }
bgamari commented 1 year ago

@thielema I am rather skeptical of the phantom approach as it (in conjunction with TypeFamilies) allows programs to be written that do not have clear behavior. For instance,

type family F a where
    F Int = Const
    F a = a

foreign import ccall "hi"
    hi :: PerhapsConstPtr (F a) a -> IO ()

What is C type of hi? We don't know until it is instantiated. Moreover, even if we knew the compiler would need to generate a bit of code for each instantiation.

treeowl commented 1 year ago

@bgamari Should it be called ConstPtr or PtrConst? I don't have a strong opinion, but the latter seems slightly more intuitive to me. What makes the ABI different?

treeowl commented 1 year ago

Oh, I see; a pointer to a constant may point to non-writable memory.

endgame commented 1 year ago

I remember @ekmett writing https://github.com/ekmett/codex/tree/master/const a while back, but I don't know if there's anything there that you might want to use, or whether he has other comments on this proposal.

bgamari commented 1 year ago

What makes the ABI different?

Whoops, I should have said API here, not ABI. C doesn't define an ABI, although under the System V ABI there is no difference between const and non-const pointer arguments.

Oh, I see; a pointer to a constant may point to non-writable memory.

Correct. The types are making different promises. If I have functions,

void f(int *x);
void g(const int *x);

I can call g(y) and have assurance that the evaluation of *y didn't change (aliasing notwithstanding). This is not true of f, however.

bgamari commented 1 year ago

@endgame, thanks for the reference. This is indeed a useful reference. I suppose the question here is what fraction of the functionality of Foreign.Ptr we want to replicate for ConstPtr.

bgasiorzewski commented 1 year ago

I can call g(y) and have assurance that the evaluation of *y didn't change (aliasing notwithstanding).

Not sure if my comment adds to the discussion, but I wanted to point out that generally there is no such guarantee. g may cast away constness and modify the value of *y. The compiler will typically need to load *y from memory after the call to g if *y is used again later.

treeowl commented 1 year ago

@bgasiorzewski , couldn't you have this?

const int a = 3;
const int *p = &a;

In that case, I believe a could be in memory marked read-only, and something like *((int *)p) = 4 will dump core. Presumably we'd like to avoid that. On the flip side, I imagine we would often want to cast on constness.

bgamari commented 1 year ago

g may cast away constness and modify the value of *y.

By my understanding, under the C standard such a cast is undefined behavior. Yes, in practice it will often work and the prevalence of such casts is one consideration that prevent compilers from being able to exploit constness (the other being that const is merely a local property of a pointer; other non-const pointers to the same object may exist in the program). However, semantically, such a program has no meaning.

bgasiorzewski commented 1 year ago

By my understanding, under the C standard such a cast is undefined behavior

Just a cast is always okay. Some standard library functions such as strstr do that.

Modifying a non-const object via such pointer might be bad style, but it's not forbidden by the standard as far as I'm aware.

Modifing a const object as in @treeowl's example is UB though. Quote from the C17 standard:

If an attempt is made to modify an object defined with a const-qualified type through use of an lvalue with non-const-qualified type, the behavior is undefined.

treeowl commented 1 year ago

The phantom approach sounds very attractive, with liberal use of casts inserted on the C side.

bgamari commented 1 year ago

I'll admit, I am having a hard time seeing what the phantom approach is buying us here. Nearly all FFI programs are quite monomorphic and rarely does polymorphism in constness in particular make much sense. If a user did need such polymorphism they could simply use Coercible to coerce between Ptr and ConstPtr..

Does someone have an example of a useful concrete program which this more elaborate mechanism would allow us to write?

Bodigrim commented 1 year ago

As a point of order, due to the interaction with GHC release cycle we need to come to a resolution on this quickly. I'll keep the floor open until the end of the week. @bgamari could you please update the proposal and prepare an MR by next Monday? Then we'll be able to vote next week.

Back to the proposal, I think it's better to have a simple robust solution with a newtype first. If in future there appears a justification for a more arcane approach with phantom types, it can be dealt with separately.

bgamari commented 1 year ago

I have updated the proposal. I will prepare an MR now.

treeowl commented 1 year ago

@bgamari Aren't function inputs (that the function doesn't edit) polymorphic in constness?

bgamari commented 1 year ago

I have opened !9749 implementing this proposal.

phadej commented 1 year ago

A small nitpick:

however, this seems too GHC-specific for a type that addresses a deficiency in the Report's FFI specification.

It's a deficiency in GHC's CApiFFI implementation. Reports FFI calling conventions don't need ConstPtr, Report puts the burden of matching the types on the programmer, constness does affect calling convention.

OTOH CApiFFI is GHC specific calling convention.

Another way to solve constness-issues would be to use explicit casts in CApiFFI generated stubs, but it's would be clearly worse, and in fact defy the purpose of CApiFFI (as there isn't specific constness cast like const_cast in C, AFAIK)

cdsmith commented 1 year ago

I don't think the desirability of ConstPtr is specific to capi. I would also hope, for instance, that a foreign export ccall of a function with ConstPtr in its type would generate a stub with the const qualifier on arguments, avoiding the need to cast away constness in C even for arguments that are pointers to constant values.

phadej commented 1 year ago

AFAIK foreign export ccall doesn't generate any stubs, it just generates a call directly to the C function. That's why anything like ConstPtr wasn't required (until lately as usage of CApiFFI was advertised more).


For example

module Main where

import Foreign.C.Types

foreign import ccall "putchar" c_putchar :: CInt -> IO CInt

main :: IO ()
main = do
    _ <- c_putchar 60
    _ <- c_putchar 10
    return ()

Generates (-dump-cmm):

(_u2V4::I64) = call "ccall" arg hints:  [PtrHint,]  result hints:  [PtrHint] suspendThread(BaseReg, 0);
(_s2Ts::I64) = call "ccall" arg hints:  [‘signed’]  result hints:  [‘signed’] putchar(60);
(_u2V5::I64) = call "ccall" arg hints:  [PtrHint]  result hints:  [PtrHint] resumeThread(_u2V4::I64);
...
(_u2UU::I64) = call "ccall" arg hints:  [PtrHint,]  result hints:  [PtrHint] suspendThread(BaseReg, 0);
(_s2Tw::I64) = call "ccall" arg hints:  [‘signed’]  result hints:  [‘signed’] putchar(10);
(_u2UV::I64) = call "ccall" arg hints:  [PtrHint]  result hints:  [PtrHint] resumeThread(_u2UU::I64);

But the CApiFFI version with

foreign import capi "stdio.h putchar" c_putchar :: CInt -> IO CInt

generates a stub, the corresponding lines in C-- are:

(_u2V4::I64) = call "ccall" arg hints:  [PtrHint,]  result hints:  [PtrHint] suspendThread(BaseReg, 0);
(_s2Ts::I64) = call "capi" arg hints:  [‘signed’]  result hints:  [‘signed’] ghczuwrapperZC0ZCmainZCMainZCputchar(60);
(_u2V5::I64) = call "ccall" arg hints:  [PtrHint]  result hints:  [PtrHint] resumeThread(_u2V4::I64);
...
(_u2UU::I64) = call "ccall" arg hints:  [PtrHint,]  result hints:  [PtrHint] suspendThread(BaseReg, 0);
(_s2Tw::I64) = call "capi" arg hints:  [‘signed’]  result hints:  [‘signed’] ghczuwrapperZC0ZCmainZCMainZCputchar(10);
(_u2UV::I64) = call "ccall" arg hints:  [PtrHint]  result hints:  [PtrHint] resumeThread(_u2UU::I64);
phadej commented 1 year ago

@bgamari is there a -ddump-* flag to dump CApiFFI generated stubs?

EDIT: -ddump-foreign

So for above example, the CApiFFI generates:

#include "stdio.h"
HsInt32 ghczuwrapperZC0ZCmainZCMainZCputchar(HsInt32 a1) {return putchar(a1);}

(EDIT: on my 64bit machine newtype CInt = CInt GHC.Int.Int32)

but with ccall Foreign export stubs are empty.

ekmett commented 1 year ago

I think the main issue with const is that, as always, it is a bit of a backwards guarantee. You really want to know that what is what is on the other side won't be changed, so you can safely peek without side-effects, but all const tells you is that you won't change it, so you need to be careful about layering that extra level of meaning on yourself, on a case-by-case basis.

phadej commented 1 year ago

@ekmett, yes, but how it is related? If some third party api (e.g. libpq) has const all over their API and I want to use CApiFFI, we are out of luck.

No-one is proposing changing peek to have ConstPtr a -> IO a signature.

phadej commented 1 year ago

EDIT: I think that we & @bgamari should clarify in ConstPtr haddocks that there is no guarantees about "constness" of the pointer. That it's sole purpose is to provide const in the CApiFFi stubs, i.e. that there are no semantics in "Haskell Land".

That makes me think that Foreign.C.ConstPtr is not the best place for such specific type, nor the ConstPtr name. But I have no better ideas.

bgamari commented 1 year ago

That makes me think that Foreign.C.ConstPtr is not the best place for such specific type, nor the ConstPtr name. But I have no better ideas.

Perhaps these names aren't ideal, but I think they are acceptable and ultimately documentation can fill in any gaps and ambiguities that they may introduce.

bgamari commented 1 year ago

Regarding @ekmett's comment, I agree with @phadej here. The goal of this proposal is not to introduce const because it is an incredibly useful language construct that we want to carry over from C. Rather it merely seeks to address the fact that const is a reality of dealing with C interfaces and, when using the foreign import capi, it must be correctly represented in the Haskell type of the import. Perhaps the proposal should make this more explicit.

cdsmith commented 1 year ago

@phadej

AFAIK foreign export ccall doesn't generate any stubs, it just generates a call directly to the C function.

I think I wrote foreign export ccall and you misread it as foreign import ccall? Otherwise, I'm just very confused. I agree that const is not needed for ccall imports.

phadej commented 1 year ago

@cdsmith Sorry, i missed that.

foreign export stub generation could use ConstPtr as well, indeed. But it doesn't in the current implementation.

That said, export ccall generates terrible stubs. CInt is converted to HsInt32 on my machine for example, i.e. the stubs are good starting point, but IMHO not usable as is.

Bodigrim commented 1 year ago

Dear CLC members, let's vote on the proposal to add a new module Foreign.C.ConstPtr, exporting newtype ConstPtr as detailed in https://gitlab.haskell.org/ghc/ghc/-/merge_requests/9749. The goal of this addition is to make more foreign functions available for foreign import capi (as opposed to foreign import ccall), which is a recommended way to use FFI in Haskell. See https://gitlab.haskell.org/ghc/ghc/-/issues/22043 for more details.

@tomjaguarpaw @chessai @cgibbard @emilypi @mixphix


+1 from me.

mixphix commented 1 year ago

+1 from me!

cgibbard commented 1 year ago

+1

Bodigrim commented 1 year ago

@emilypi @chessai @tomjaguarpaw just a gentle reminder to vote.

tomjaguarpaw commented 1 year ago

This is far from my area of expertise so I'd prefer to withhold my vote unless it's needed to break a tie.

chessai commented 1 year ago

+1

Bodigrim commented 1 year ago

We have 4 votes in favour out of 6 possible, this is enough to approve.

chshersh commented 1 year ago

I'm trying to summarise the state of this proposal as part of my volunteering effort to track the progress of all approved CLC proposals.

Field Value
Authors @bgamari
Status merged
base version 4.18.0.0
Merge Request (MR) https://gitlab.haskell.org/ghc/ghc/-/merge_requests/9749
Blocked by nothing
CHANGELOG entry present with a mistake
Migration guide not needed

Please, let me know if you find any mistakes 🙂


There's a typo in changelog though. The relevant change mentions CLC proposal #117 while this proposal is actually #118.