RFC SUMMARY
I propose we add an @align attribute, which will apply in two places:
- Globals: @align(32) let foo = bar { ... };
- Pointers: *@align(8) int
For globals, @align is analogous to alignas in C. The alignment must be
a power of two greater than or equal to the alignment of the type. The
maximum supported alignment is implementation-defined. For pointers,
@align acts as a form of type safety. The alignment can be any power of
two, and it defaults to the alignment of the secondary type if omitted.
LANGUAGE IMPLICATIONS
As mentioned above, @align is added for globals. When taking the address
of a global, the pointer alignment is set to that of the global:
let x = 0u32;
@align(8) let y = 0u32;
let xptr = &x; // -> *u32, or equivalently, *@align(4) u32
let yptr = &y; // -> *@align(8) u32
We could also allow @align on local bindings:
static @align(8) let x = 0u32; // statically allocated
@align(8) let y = 0u32; // stack allocated
To see why @align on pointers is desirable, take the following code:
// use crypto::random;
let buf: [size(u64)]u8 = [0...];
random::buffer(buf);
const n = *(&buf: *u64);
At a glance, this code looks perfectly fine. Code similar to this is
used multiple times in the standard library. But there's a subtle nasty
bug: buf may not meet the alignment requirements for u64. So when
casting to *u64, the pointer may be misaligned! This doesn't cause
issues on our currently supported targets (besides poor performance),
but on some targets this could cause a crash, or potentially worse. We
currently provide no safeguards against bugs caused by pointer
misalignment.
Introducing @align on pointer types would fix this issue. The
assignability and castability rules for pointers are adjusted as
follows:
- A pointer type is assignable to a pointer type of the same secondary
type if the new pointer alignment is less than or equal to the old
alignment
- A pointer cast can only increase the alignment if the secondary type
doesn't change
For example:
- `*u64` is assignable to `*@align(4) u64`, but not to `*@align(16) u64`
- `*u8` is castable to `*@align(4) u8`, but not to `*@align(4) u16` or `*u32`
- `*@align(4) u8` is castable to `*u16` and `*u32`, but not to `*u64`
- `*u32` is still castable to `*u8` and `*u16`
So the random::buffer example now refuses to compile, because
`*[size(u64)]u8` isn't castable to `*u64`, because the alignment
increases from 1 to 8. If you wanted to keep the same behavior, you
could rewrite the cast like this:
const n = *(&buf: *@align(8) [8]u8: *u64);
This is very verbose and cumbersome, but that's a good thing, because
the actual correct thing to do is to rewrite the code so the alignment
is correct to begin with:
let n = 0u64;
random::buffer(&n: *[size(u64)]u8);
There's a couple complications that arise which necessitate special
cases:
1. If @align is omitted, and the pointer's secondary type has undefined
alignment, then the pointer also has undefined alignment. Such
pointers can be cast/assigned to/from other pointers without any
regard to pointer alignment. For example, `*opaque` is castable to
any other pointer, and all pointers are assignable to `*opaque`. I
don't think there's any way around this unfortunately.
2. When taking the address of a misaligned struct/union (either because
of an unaligned @offset or a @packed struct), the alignment is always
1. This also applies to nested access expressions. For example:
type t = struct { @offset(6) x: struct { y: [2]u32 } };
let foo = t { ... };
let bar = &foo.x.y[1]; // -> *@align(1) u32
Another option is to set the alignment to the largest power of two
multiple of the offset, so in the above example the alignment would
be 2. I prefer always having it be 1, but either-or is fine.
When `alloc` is provided a pointer type hint with a custom alignment,
the allocated storage has (at least) that alignment. The maximum
supported alignment is implementation-defined. No matter what, the
alignment is guaranteed to be greater than or equal to the largest
definite type alignment (currently 8, but possibly 16 in the future if
we add 128-bit types). The alignment of the returned pointer is always
at least this value. So the following code *is* correct, and will
continue to compile:
let buf = alloc([0...]: [size(u64)]u8)!; // -> *@align(8) [size(u64)]u8
random::buffer(buf);
const n = *(buf: *u64);
I'm not bothering with @align on slice types in this RFC, since the
semantics are unintuitive: `[]@align(8) u32` would mean that the backing
array has the alignment 8 (i.e. its type is `*@align(8) [*]u32`), *not*
that the elements all do.
STANDARD LIBRARY IMPLICATIONS
None
ECOSYSTEM IMPLICATIONS
This is technically a breaking change, but I don't think there should be
any automated migration procedure, since if your code stops compiling
after this change, your code was likely incorrect to begin with.
EXAMPLE CODE
In addition to the random::buffer example given above, here's an example
from net/ip/+linux.ha:
return rt::sockaddr {
in = rt::sockaddr_in {
sin_family = rt::AF_INET,
sin_port = endian::htonu16(port),
sin_addr = rt::in_addr { s_addr = *(&v4[0]: *opaque: *u32) },
...
},
...
};
v4's type is addr4, which is an alias of [4]u8, so the above code is
incorrect. If this RFC is implemented, the bug would be diagnosed, and
the code could be rewritten like this:
const addr = rt::in_addr {
s_addr = endian::host.getu32(v4),
};
return rt::sockaddr {
in = rt::sockaddr_in {
sin_family = rt::AF_INET,
sin_port = endian::htonu16(port),
sin_addr = addr,
...
},
...
};
RELATED RFCS
None
Prior art:
- C: alignas
- Zig: https://ziglang.org/documentation/master/#Alignment
hmm, generally i think that some way of specifiying the alignment is a very
good idea. i also like your ideas.
but isn't this a bit too complex than it needs to be? what
if we make @align() an attribute for types, wouldn't that be much simpler
because it removes the special case in the syntax everywhere, although that
would be less flexible. however, i don't imagine you need it that often.
type int_align8 = @align(8) int;
seems fine for me. also given that a type already has an implicit
alignment, this would allow users to set it explicitly, not chagning
much really.
either way, i think that the assignability rules are Good.
On Tue Sep 10, 2024 at 10:40 PM EDT, Lorenz (xha) wrote:
> but isn't this a bit too complex than it needs to be? what> if we make @align() an attribute for types, wouldn't that be much simpler> because it removes the special case in the syntax everywhere, although that> would be less flexible. however, i don't imagine you need it that often.>> type int_align8 = @align(8) int;>> seems fine for me. also given that a type already has an implicit> alignment, this would allow users to set it explicitly, not chagning> much really.
This doesn't make sense IMO, for a few reasons:
- We assume the alignment of a type doesn't exceed its size. Breaking
this assumption would cause weird behavior, like padding in arrays.
- Actually, in general, having padding for non-aggregate types is,
really weird.
- Stuff is passed by value, so either alignment would be discarded on
assignment, or it would be viral, and neither make sense IMO. It's
similar to the issue we currently have with const (and type flags in
general), and also similar to type qualifiers in C, which have weird
semantics.
- Adding onto the last point: if `foo` has type `*@align(8) int`, what's
the type of `*foo`? With my proposal, it's `int`, but if @align were
generalized to all types then this would become unclear.
- We'd need to special case types with zero or undefined size. The
latter special case (undefined size) is necessary for pointers as
well, but the former (zero size) isn't.
I also can't think of any reason you'd use @align on a type, so, it
feels unnecessary to me.
I don't understand what you mean by my proposal being "more complex than
it needs to be". Your proposal is more complex than mine is. It moves
the @align syntax from pointers to types, which is a net-zero change in
"complexity", but it also necessitates implementing the semantics for
@align on types outside of pointers.
(As an aside, I don't think words like "complexity"/"simple" are very
descriptive, especially here. They read like buzzwords to me, especially
because everyone has a different idea on what "complex" means so it
leaves lots of room for miscommunication.)
what i was trying to say is that types already have an alignment
and that, when adding @align just for types, users can change the
already present, but implicit, alignment. in my opionion, alignment
is more of a property of types, and less of a property of the
pointer. more comments inline.
On Wed, Sep 11, 2024 at 02:05:42AM -0400, Sebastian wrote:
> On Tue Sep 10, 2024 at 10:40 PM EDT, Lorenz (xha) wrote:> > but isn't this a bit too complex than it needs to be? what> > if we make @align() an attribute for types, wouldn't that be much simpler> > because it removes the special case in the syntax everywhere, although that> > would be less flexible. however, i don't imagine you need it that often.> >> > type int_align8 = @align(8) int;> >> > seems fine for me. also given that a type already has an implicit> > alignment, this would allow users to set it explicitly, not chagning> > much really.> > This doesn't make sense IMO, for a few reasons:> > - We assume the alignment of a type doesn't exceed its size. Breaking> this assumption would cause weird behavior, like padding in arrays.
yes, but as a trade-off this would solve the issue of wanting an explicit
alignment of the items in a slice-or-array type, for example. aren't slices
and arrays the only places where this would cause "weird" behavior? it would
make the alignment thing more complete in the whole language.
> - Actually, in general, having padding for non-aggregate types is,> really weird.
hmm, well, i am not sure what is so weird about it. you also have "implcit
padding" in structs that people not expect, too. however, when compared with
the padding in structs, @align() on types is less weird imo.
> - Stuff is passed by value, so either alignment would be discarded on> assignment, or it would be viral, and neither make sense IMO. It's> similar to the issue we currently have with const (and type flags in> general), and also similar to type qualifiers in C, which have weird> semantics.
if you pass stuff by value, the alignment would just be discarded, i think
this makes sense, because it is the expected behavior, at least the one
that i would expect.
> - Adding onto the last point: if `foo` has type `*@align(8) int`, what's> the type of `*foo`? With my proposal, it's `int`, but if @align were> generalized to all types then this would become unclear.
hmm, sorry, i am not sure what you mean. if you deferefence foo,
you would get an int which is 8-byte aligned? is this the specific
case you are talking about?:
type int_align8 = @align(8) int;
let x: int_align8 = 2;
let foo: *int_align8 = &x;
let y: int_align8 = *foo;
> - We'd need to special case types with zero or undefined size. The> latter special case (undefined size) is necessary for pointers as> well, but the former (zero size) isn't.
hmm, i would not do a special case for opaque: if you have a
*@align(8) opaque, you'd just be able to assign pointers to 8-byte
aligned types.
> I also can't think of any reason you'd use @align on a type, so, it> feels unnecessary to me.
the reason is that i think that the alignment is more of a property
of a type than it is a property of the pointer.
> I don't understand what you mean by my proposal being "more complex than> it needs to be". Your proposal is more complex than mine is. It moves> the @align syntax from pointers to types, which is a net-zero change in> "complexity", but it also necessitates implementing the semantics for> @align on types outside of pointers.
hmm, in the case of @align for types, only all corner cases that will be
broken have to be checked, because the logic for alignment of types is
already there and has to exist. in the case of pointers and global object,
the same has to be done, however, i think it adds another logic thing to
pointer types? either way, not a very strong argument
> (As an aside, I don't think words like "complexity"/"simple" are very> descriptive, especially here. They read like buzzwords to me, especially> because everyone has a different idea on what "complex" means so it> leaves lots of room for miscommunication.)
i should stop using these words, sorry. you're right.
+1, and i'd much rather stick @align on declarations and pointers
On Wed Sep 11, 2024 at 2:07 PM UTC, Lorenz (xha) wrote:
> what i was trying to say is that types already have an alignment> and that, when adding @align just for types, users can change the> already present, but implicit, alignment. in my opionion, alignment
the fundamental issue is that the currently-existing alignment system
has the invariant that type.align <= type.size, and we don't want @align
to have that invariant. we can pretend to get rid of that invariant by
having @align implicitly increase a type's size if it's lower than the
alignment, but that's extremely weird and not actually in line with the
semantics that the user requested
for example, consider (in the global context)
let a: @align(4) u8 = 0;
what the user wants here is a 1-byte u8, whose address is guaranteed to
be a multiple of 4. in order to be able to preserve proper alignment
semantics, if we're doing a generalized @align, a would need to allocate
4 bytes here instead
another example:
let b: [4]@align(4) u8 = [0...];
in order to do a generalized @align, we'd now need to 4-align &b[i] for
all i, which requires 16 bytes instead of the 4 that the user probably
wanted us to use. not only that, but now [4]@align(4) u8 is completely
abi-incompatible with [4]u8, which means we probably can't have them be
assignable
(now, in practice, you'd actually probably want @align(4) [4]u8 instead,
but the existence of the latter is a problem that you need to deal with
as soon as you're generalizing @align beyond declarations and pointers)
more generally (hah), generalizing @align introduces quite a few ways to
get harec to generate bizarre code, but i don't think it actually allows
you to do any useful new things
On Sat Sep 7, 2024 at 11:01 PM UTC, Sebastian wrote:
> 2. When taking the address of a misaligned struct/union (either because> of an unaligned @offset or a @packed struct), the alignment is always> 1. This also applies to nested access expressions. For example:>> type t = struct { @offset(6) x: struct { y: [2]u32 } };> let foo = t { ... };> let bar = &foo.x.y[1]; // -> *@align(1) u32>> Another option is to set the alignment to the largest power of two> multiple of the offset, so in the above example the alignment would> be 2. I prefer always having it be 1, but either-or is fine.
i think we should use pointer alignment to represent the minimum
alignment that the compiler can guarantee will always be met, which
implies that bar's alignment should be 2 here. is there a reason you'd
prefer for it to be 1?
i can't think of any real-world contexts where you'd care about the
difference between a 2-aligned and a 1-aligned u32, but consider:
// as in your example
type t = struct { @offset(6) x: struct { y: [2]u32 } };
let foo = t { ... };
let bar = &foo.x.y[1]; // -> *@align(2) u32
let baz = bar: *[2]u16; // allowed, since the implicit alignment here is also 2
baz[1]; // guaranteed to be aligned, even though bar wasn't
the cast to get baz is safe, even though under your proposal it'd
require a double-cast in order to appease the alignment gods
i only suggest this because i don't think it'll be particularly harder
to implement, and it seems slightly more Correct to me
> When `alloc` is provided a pointer type hint with a custom alignment,> the allocated storage has (at least) that alignment. The maximum> supported alignment is implementation-defined. No matter what, the> alignment is guaranteed to be greater than or equal to the largest> definite type alignment (currently 8, but possibly 16 in the future if> we add 128-bit types). The alignment of the returned pointer is always> at least this value. So the following code *is* correct, and will> continue to compile:
this isn't gonna be trivial, i'd prefer not to implement aligned_alloc
unless there's a particularly strong need for it
(or, put a different way: if we do this, i'd like for our
implementation-defined limit to be 8/16)
On Thu Sep 12, 2024 at 1:08 AM EDT, Ember Sawady wrote:
> On Sat Sep 7, 2024 at 11:01 PM UTC, Sebastian wrote:> > 2. When taking the address of a misaligned struct/union (either because> > of an unaligned @offset or a @packed struct), the alignment is always> > 1. This also applies to nested access expressions. For example:> >> > type t = struct { @offset(6) x: struct { y: [2]u32 } };> > let foo = t { ... };> > let bar = &foo.x.y[1]; // -> *@align(1) u32> >> > Another option is to set the alignment to the largest power of two> > multiple of the offset, so in the above example the alignment would> > be 2. I prefer always having it be 1, but either-or is fine.>> i think we should use pointer alignment to represent the minimum > alignment that the compiler can guarantee will always be met, which > implies that bar's alignment should be 2 here. is there a reason you'd > prefer for it to be 1?>> i can't think of any real-world contexts where you'd care about the > difference between a 2-aligned and a 1-aligned u32, but consider:>> // as in your example> type t = struct { @offset(6) x: struct { y: [2]u32 } };> let foo = t { ... };> let bar = &foo.x.y[1]; // -> *@align(2) u32>> let baz = bar: *[2]u16; // allowed, since the implicit alignment here is also 2> baz[1]; // guaranteed to be aligned, even though bar wasn't>> the cast to get baz is safe, even though under your proposal it'd > require a double-cast in order to appease the alignment gods>> i only suggest this because i don't think it'll be particularly harder > to implement, and it seems slightly more Correct to me
We already talked about most of this on IRC, but for completeness here's
a summary of stuff:
I think making the alignment 1 felt more "consistent" to me, and less
"arbitrary" (even though it isn't arbitrary at all). For example:
type t = struct {
x: u32,
y: u64,
z: u32,
};
let foo = t { ... };
foo.x and foo.z are always 8-byte aligned, but IMO it makes more sense
to treat them as 4-byte aligned. If we go with this behavior (plus
calculating the alignment of unaligned fields), then the behavior for
@offset and @packed would be to use the maximum guaranteed alignment,
unless that alignment is larger than the type's alignment, in which case
the type's alignment is used instead.
Another example is with arrays:
type t = struct {
x: u64,
y: [5]u16,
};
let foo = t { ... };
foo.y[0] has alignment 8, foo.y[2] has alignment 4, and foo.y[4] has
alignment 8 again. foo.y[1] and foo.y[3] have alignment 2. harec can
figure this out, but it feels a bit more intuitive to me that foo.y[N]
always has alignment 2.
This also applies outside of structs, with pointers:
let x = alloc([1u32, 2, 3])!;
&x[0]; // -> *@align(8) u32
&x[1]; // -> *u32
&x[2]; // -> *@align(8) u32
This *works*, and I guess it's technically safer, but it still feels
weird to me. Especially because the binding could be written like this:
let x: *[_]u32 = alloc([1, 2, 3]);
In which case &x[N] is always *u32, because the array's overalignment is
assigned away.
This also relies on information which isn't stored within the type,
resulting in strange behavior:
let x = (1u64, 2u32, (3u32, 4u32));
&x.2[1]; // -> *@align(8) u32
let x = (1u64, 2u32, (3u32, 4u32));
let y = &x.2;
&y[1]; // -> *u32
let x = (1u64, 2u32, (3u32, 4u32));
&(&x.2)[1]; // -> probably *u32?
Another example, which doesn't use overalignment:
type t = struct {
@offset(6) x: struct @packed {
x: u16,
y: u32,
}.
};
let foo = t { ... };
&foo.x.y; // -> *u32
let x = &foo.x;
&x.y; // -> *@align(2) u32
&(&foo.x).y; // -> probably *@align(2) u32?
So doing this would require that nested alignments were checked as a
single expression, pretty much. And that's ugly and a bad idea, so then
the two options are to compromise by having semantics for unaligned
fields that give them an alignment greater than 1 without deducing
alignment for other accesses, or just saying that unaligned stuff is
always given alignment 1, end of story. No matter which we choose, it
still leaves open the question of what to do with anonymous embedded
structs:
type t = struct @packed {
@offset(2) struct @packed {
@offset(2) x: u32,
},
};
let foo = t { ... };
&foo.x; // *u32?
The actual offset of field x relative to t is known, but if we don't
compute alignment across nested accesses, then using this when deducing
alignment would mean that x's type changes depending on whether the
struct is named or not. But saying foo.x has alignment 2 is also
strange, since one would expect that the expression would give the same
result if foo's type were `struct @packed { offset(4) x: u32 }`, but it
wouldn't.
The conclusion we came to is that we should treat anonymous embedded
structs as a sort of implicit nested access, so &foo.x's type would be
`*@align(2) u32`, even though harec could easily deduce that the field
is aligned. It's the least ugly solution. I was also convinced that
taking the maximum alignment of a field not greater than the alignment
of its type (rather than always using alignment 1) is probably the best
option.
Finally, we talked about the special cases needed for nested
indexing/access expressions when a field is misaligned. If the operand
isn't a pointer, this information isn't preserved in the type, so check
will need to handle it some other way. With the object model proposed
alongside mutability overhaul, this could be achieved by storing the
alignment alongside the result of each expression, but with our current
semantics this would be incorrect, since we sometimes makes a copy but
sometimes doesn't (for example: &*x makes a copy, but &(*x)[0] doesn't,
since the latter is an object selector but the former isn't).
So I think the best way to handle this is to check the operand of an
indexing/access expression as though its address were being taken,
unless it's a unary * expression, in which case the * is discarded
(recursively). The special case with unary * will cease to be necessary
with the improved object model, but for now it's necessary.
> > When `alloc` is provided a pointer type hint with a custom alignment,> > the allocated storage has (at least) that alignment. The maximum> > supported alignment is implementation-defined. No matter what, the> > alignment is guaranteed to be greater than or equal to the largest> > definite type alignment (currently 8, but possibly 16 in the future if> > we add 128-bit types). The alignment of the returned pointer is always> > at least this value. So the following code *is* correct, and will> > continue to compile:>> this isn't gonna be trivial, i'd prefer not to implement aligned_alloc > unless there's a particularly strong need for it>> (or, put a different way: if we do this, i'd like for our > implementation-defined limit to be 8/16)
Hm, I assumed it would be relatively simple to implement, but if it
isn't then I guess that's fine.
On Thu, Sep 12, 2024 at 05:08:34AM +0000, Ember Sawady wrote:
> +1, and i'd much rather stick @align on declarations and pointers> > On Wed Sep 11, 2024 at 2:07 PM UTC, Lorenz (xha) wrote:> > what i was trying to say is that types already have an alignment> > and that, when adding @align just for types, users can change the> > already present, but implicit, alignment. in my opionion, alignment> > the fundamental issue is that the currently-existing alignment system > has the invariant that type.align <= type.size, and we don't want @align > to have that invariant. we can pretend to get rid of that invariant by > having @align implicitly increase a type's size if it's lower than the > alignment, but that's extremely weird and not actually in line with the > semantics that the user requested> > for example, consider (in the global context)> > let a: @align(4) u8 = 0;> > what the user wants here is a 1-byte u8, whose address is guaranteed to > be a multiple of 4. in order to be able to preserve proper alignment > semantics, if we're doing a generalized @align, a would need to allocate > 4 bytes here instead
exactly this is my selling point of having align for types lol
and also, i'd expect that an @align(4) u8 is allocating 4 bytes,
but i might be asking for too much knowledge from users how stuff
in the background works
> another example:> > let b: [4]@align(4) u8 = [0...];> > in order to do a generalized @align, we'd now need to 4-align &b[i] for > all i, which requires 16 bytes instead of the 4 that the user probably > wanted us to use. not only that, but now [4]@align(4) u8 is completely > abi-incompatible with [4]u8, which means we probably can't have them be > assignable
assignable by could value work, but by reference doesn't. that'd be
kinda intended though.
> (now, in practice, you'd actually probably want @align(4) [4]u8 instead, > but the existence of the latter is a problem that you need to deal with> as soon as you're generalizing @align beyond declarations and pointers)> > more generally (hah), generalizing @align introduces quite a few ways to > get harec to generate bizarre code, but i don't think it actually allows > you to do any useful new things
i mean, there are some cases where processors and stuff expect
specifically aligned memory (SIMD, for example, i belive), and for
that it is quite nice to not have to fall back to assembly.
On Fri Sep 13, 2024 at 3:02 AM UTC, Lorenz (xha) wrote:
> and also, i'd expect that an @align(4) u8 is allocating 4 bytes,> but i might be asking for too much knowledge from users how stuff> in the background works
doing the @align in the binding allows us to avoid allocating more than
1 byte - the only thing we actually care about is that the global's
address % 4 == 0
> > another example:> > > > let b: [4]@align(4) u8 = [0...];> > > > in order to do a generalized @align, we'd now need to 4-align &b[i] for > > all i, which requires 16 bytes instead of the 4 that the user probably > > wanted us to use. not only that, but now [4]@align(4) u8 is completely > > abi-incompatible with [4]u8, which means we probably can't have them be > > assignable>> assignable by could value work, but by reference doesn't. that'd be> kinda intended though.
the code to implicitly convert between those is gonna be awful, and
it'll require an implicit allocation + loop for slices. no thanks
and, bear in mind: the thing people almost certainly want is for the
start of the array to be aligned, not each individual element
> i mean, there are some cases where processors and stuff expect> specifically aligned memory (SIMD, for example, i belive), and for> that it is quite nice to not have to fall back to assembly.
for example, here. simd cares about the alignment of the start of the
vector, but it *definitely* isn't adding internal padding in order to
over-align individual elements, because nobody wants to do that
a slightly different framing i got to on irc earlier today: alignment is
a property of objects, similar to mutability, and the reason for
restricting it to operating on objects is similar to the reasoning for
restricting mutability to bindings and pointers in the mutability
overhaul
ok, well, convinced. +1 to @align in pointers, globals and static
locals, thanks for discussing this with me :-)
don't think it is worth having for non-static locals.
What are people's thoughts on allowing pointer alignment to be increased
via type assertion?
type s = struct {
@offset(2) struct {
@offset(2) x: u32,
},
};
let foo = s { ... };
&foo.x as *@align(4) u32; // runtime check succeeds
let bar = (0u32, 1u8, 2u8);
&bar.2 as *@align(4) u8; // runtime check fails; abort
I like the idea of enabling runtime safety here, but this would imply
also allowing matching on pointer alignment, and I'm unsure exactly what
the semantics of that would be.
Prior art: https://ziglang.org/documentation/master/#Incorrect-Pointer-Alignment
On Sat, Sep 14, 2024 at 02:34:41AM -0400, Sebastian wrote:
> What are people's thoughts on allowing pointer alignment to be increased> via type assertion?
i am not sure. that would mean that there is another use for "as"
(in addition to the ones that will probably come in the future) and
i don't know why you'd want to use a runtime-assertion that something
has a specific alignment? even in that case, you could use:
assert(&foo.x: uintptr % 4 == 0);
are there more use-cases that justify adding this to "as"? also
with regards to weirdness, this is... somewhat weird and the
hand-written assertion is definitely easier to understand and read.
> type s = struct {> @offset(2) struct {> @offset(2) x: u32,> },> };> let foo = s { ... };> &foo.x as *@align(4) u32; // runtime check succeeds> > let bar = (0u32, 1u8, 2u8);> &bar.2 as *@align(4) u8; // runtime check fails; abort> > I like the idea of enabling runtime safety here, but this would imply> also allowing matching on pointer alignment, and I'm unsure exactly what> the semantics of that would be.> > Prior art: https://ziglang.org/documentation/master/#Incorrect-Pointer-Alignment