Commit 9f0b9b8da1
Changed files (6)
src/astgen.zig
@@ -527,21 +527,8 @@ pub fn expr(mod: *Module, scope: *Scope, rl: ResultLoc, node: ast.Node.Index) In
const result = try addZIRBinOp(mod, scope, src, .merge_error_sets, lhs, rhs);
return rvalue(mod, scope, rl, result);
},
- .anyframe_literal => {
- if (true) @panic("TODO update for zir-memory-layout");
- const main_token = main_tokens[node];
- const result = try addZIRInstConst(mod, scope, src, .{
- .ty = Type.initTag(.type),
- .val = Value.initTag(.anyframe_type),
- });
- return rvalue(mod, scope, rl, result);
- },
- .anyframe_type => {
- if (true) @panic("TODO update for zir-memory-layout");
- const return_type = try typeExpr(mod, scope, node_datas[node].rhs);
- const result = try addZIRUnOp(mod, scope, src, .anyframe_type, return_type);
- return rvalue(mod, scope, rl, result);
- },
+ .anyframe_literal => return mod.failNode(scope, node, "async and related features are not yet supported", .{}),
+ .anyframe_type => return mod.failNode(scope, node, "async and related features are not yet supported", .{}),
.@"catch" => {
if (true) @panic("TODO update for zir-memory-layout");
const catch_token = main_tokens[node];
@@ -641,12 +628,10 @@ pub fn expr(mod: *Module, scope: *Scope, rl: ResultLoc, node: ast.Node.Index) In
.@"comptime" => return comptimeExpr(mod, scope, rl, node_datas[node].lhs),
.@"switch", .switch_comma => return switchExpr(mod, scope, rl, node),
- .@"nosuspend" => return nosuspendExpr(mod, scope, rl, node),
- .@"suspend" => @panic("TODO"),
- //.@"suspend" => return rvalue(mod, scope, rl, try suspendExpr(mod, scope, node)),
- .@"await" => return awaitExpr(mod, scope, rl, node),
- .@"resume" => @panic("TODO"),
- //.@"resume" => return rvalue(mod, scope, rl, try resumeExpr(mod, scope, node)),
+ .@"nosuspend" => return mod.failNode(scope, node, "async and related features are not yet supported", .{}),
+ .@"suspend" => return mod.failNode(scope, node, "async and related features are not yet supported", .{}),
+ .@"await" => return mod.failNode(scope, node, "async and related features are not yet supported", .{}),
+ .@"resume" => return mod.failNode(scope, node, "async and related features are not yet supported", .{}),
.@"defer" => return mod.failNode(scope, node, "TODO implement astgen.expr for .defer", .{}),
.@"errdefer" => return mod.failNode(scope, node, "TODO implement astgen.expr for .errdefer", .{}),
@@ -782,8 +767,6 @@ fn breakExpr(
},
.local_val => scope = scope.cast(Scope.LocalVal).?.parent,
.local_ptr => scope = scope.cast(Scope.LocalPtr).?.parent,
- .gen_suspend => scope = scope.cast(Scope.GenZir).?.parent,
- .gen_nosuspend => scope = scope.cast(Scope.Nosuspend).?.parent,
else => if (break_label != 0) {
const label_name = try mod.identifierTokenString(parent_scope, break_label);
return mod.failTok(parent_scope, break_label, "label not found: '{s}'", .{label_name});
@@ -836,8 +819,6 @@ fn continueExpr(
},
.local_val => scope = scope.cast(Scope.LocalVal).?.parent,
.local_ptr => scope = scope.cast(Scope.LocalPtr).?.parent,
- .gen_suspend => scope = scope.cast(Scope.GenZir).?.parent,
- .gen_nosuspend => scope = scope.cast(Scope.Nosuspend).?.parent,
else => if (break_label != 0) {
const label_name = try mod.identifierTokenString(parent_scope, break_label);
return mod.failTok(parent_scope, break_label, "label not found: '{s}'", .{label_name});
@@ -910,8 +891,6 @@ fn checkLabelRedefinition(mod: *Module, parent_scope: *Scope, label: ast.TokenIn
},
.local_val => scope = scope.cast(Scope.LocalVal).?.parent,
.local_ptr => scope = scope.cast(Scope.LocalPtr).?.parent,
- .gen_suspend => scope = scope.cast(Scope.GenZir).?.parent,
- .gen_nosuspend => scope = scope.cast(Scope.Nosuspend).?.parent,
else => return,
}
}
@@ -1111,8 +1090,6 @@ fn varDecl(
s = local_ptr.parent;
},
.gen_zir => s = s.cast(Scope.GenZir).?.parent,
- .gen_suspend => s = s.cast(Scope.GenZir).?.parent,
- .gen_nosuspend => s = s.cast(Scope.Nosuspend).?.parent,
else => break,
};
}
@@ -2797,8 +2774,6 @@ fn identifier(
s = local_ptr.parent;
},
.gen_zir => s = s.cast(Scope.GenZir).?.parent,
- .gen_suspend => s = s.cast(Scope.GenZir).?.parent,
- .gen_nosuspend => s = s.cast(Scope.Nosuspend).?.parent,
else => break,
};
}
@@ -3272,7 +3247,6 @@ fn builtinCall(
.add_with_overflow,
.align_cast,
.align_of,
- .async_call,
.atomic_load,
.atomic_rmw,
.atomic_store,
@@ -3305,10 +3279,6 @@ fn builtinCall(
.fence,
.field_parent_ptr,
.float_to_int,
- .frame,
- .Frame,
- .frame_address,
- .frame_size,
.has_decl,
.has_field,
.int_to_enum,
@@ -3362,6 +3332,13 @@ fn builtinCall(
=> return mod.failTok(scope, builtin_token, "TODO: implement builtin function {s}", .{
builtin_name,
}),
+
+ .async_call,
+ .frame,
+ .Frame,
+ .frame_address,
+ .frame_size,
+ => return mod.failTok(scope, builtin_token, "async and related features are not yet supported", .{}),
}
}
@@ -3373,7 +3350,7 @@ fn callExpr(
call: ast.full.Call,
) InnerError!zir.Inst.Ref {
if (call.async_token) |async_token| {
- return mod.failTok(scope, async_token, "TODO implement async fn call", .{});
+ return mod.failTok(scope, async_token, "async and related features are not yet supported", .{});
}
const lhs = try expr(mod, scope, .none, call.ast.fn_expr);
@@ -3402,10 +3379,10 @@ fn callExpr(
true => break :res try gz.addUnNode(.call_none, lhs, node),
false => .call,
},
- .async_kw => .call_async_kw,
+ .async_kw => return mod.failNode(scope, node, "async and related features are not yet supported", .{}),
.never_tail => unreachable,
.never_inline => unreachable,
- .no_async => .call_no_async,
+ .no_async => return mod.failNode(scope, node, "async and related features are not yet supported", .{}),
.always_tail => unreachable,
.always_inline => unreachable,
.compile_time => .call_compile_time,
@@ -3415,99 +3392,6 @@ fn callExpr(
return rvalue(mod, scope, rl, result, node); // TODO function call with result location
}
-fn suspendExpr(mod: *Module, scope: *Scope, node: ast.Node.Index) InnerError!zir.Inst.Ref {
- const tree = scope.tree();
- const src = tree.tokens.items(.start)[tree.nodes.items(.main_token)[node]];
-
- if (scope.getNosuspend()) |some| {
- const msg = msg: {
- const msg = try mod.errMsg(scope, src, "suspend in nosuspend block", .{});
- errdefer msg.destroy(mod.gpa);
- try mod.errNote(scope, some.src, msg, "nosuspend block here", .{});
- break :msg msg;
- };
- return mod.failWithOwnedErrorMsg(scope, msg);
- }
-
- if (scope.getSuspend()) |some| {
- const msg = msg: {
- const msg = try mod.errMsg(scope, src, "cannot suspend inside suspend block", .{});
- errdefer msg.destroy(mod.gpa);
- try mod.errNote(scope, some.src, msg, "other suspend block here", .{});
- break :msg msg;
- };
- return mod.failWithOwnedErrorMsg(scope, msg);
- }
-
- var suspend_scope: Scope.GenZir = .{
- .base = .{ .tag = .gen_suspend },
- .parent = scope,
- .decl = scope.ownerDecl().?,
- .arena = scope.arena(),
- .force_comptime = scope.isComptime(),
- .instructions = .{},
- };
- defer suspend_scope.instructions.deinit(mod.gpa);
-
- const operand = tree.nodes.items(.data)[node].lhs;
- if (operand != 0) {
- const possibly_unused_result = try expr(mod, &suspend_scope.base, .none, operand);
- if (!possibly_unused_result.tag.isNoReturn()) {
- _ = try addZIRUnOp(mod, &suspend_scope.base, src, .ensure_result_used, possibly_unused_result);
- }
- } else {
- return addZIRNoOp(mod, scope, src, .@"suspend");
- }
-
- const block = try addZIRInstBlock(mod, scope, src, .suspend_block, .{
- .instructions = try scope.arena().dupe(zir.Inst.Ref, suspend_scope.instructions.items),
- });
- return &block.base;
-}
-
-fn nosuspendExpr(mod: *Module, scope: *Scope, rl: ResultLoc, node: ast.Node.Index) InnerError!zir.Inst.Ref {
- if (true) @panic("TODO update for zir-memory-layout");
- const tree = scope.tree();
- var child_scope = Scope.Nosuspend{
- .parent = scope,
- .gen_zir = scope.getGenZir(),
- .src = tree.tokens.items(.start)[tree.nodes.items(.main_token)[node]],
- };
-
- return expr(mod, &child_scope.base, rl, tree.nodes.items(.data)[node].lhs);
-}
-
-fn awaitExpr(mod: *Module, scope: *Scope, rl: ResultLoc, node: ast.Node.Index) InnerError!zir.Inst.Ref {
- if (true) @panic("TODO update for zir-memory-layout");
- const tree = scope.tree();
- const src = tree.tokens.items(.start)[tree.nodes.items(.main_token)[node]];
- const is_nosuspend = scope.getNosuspend() != null;
-
- // TODO some @asyncCall stuff
-
- if (scope.getSuspend()) |some| {
- const msg = msg: {
- const msg = try mod.errMsg(scope, src, "cannot await inside suspend block", .{});
- errdefer msg.destroy(mod.gpa);
- try mod.errNote(scope, some.src, msg, "suspend block here", .{});
- break :msg msg;
- };
- return mod.failWithOwnedErrorMsg(scope, msg);
- }
-
- const operand = try expr(mod, scope, .ref, tree.nodes.items(.data)[node].lhs);
- // TODO pass result location
- return addZIRUnOp(mod, scope, src, if (is_nosuspend) .nosuspend_await else .@"await", operand);
-}
-
-fn resumeExpr(mod: *Module, scope: *Scope, node: ast.Node.Index) InnerError!zir.Inst.Ref {
- const tree = scope.tree();
- const src = tree.tokens.items(.start)[tree.nodes.items(.main_token)[node]];
-
- const operand = try expr(mod, scope, .ref, tree.nodes.items(.data)[node].lhs);
- return addZIRUnOp(mod, scope, src, .@"resume", operand);
-}
-
pub const simple_types = std.ComptimeStringMap(zir.Const, .{
.{ "u8", .u8_type },
.{ "i8", .i8_type },
@@ -3542,7 +3426,6 @@ pub const simple_types = std.ComptimeStringMap(zir.Const, .{
.{ "noreturn", .noreturn_type },
.{ "null", .null_type },
.{ "undefined", .undefined_type },
- .{ "anyframe", .anyframe_type },
.{ "undefined", .undef },
.{ "null", .null_value },
.{ "true", .bool_true },
src/Module.zig
@@ -410,8 +410,6 @@ pub const Scope = struct {
.gen_zir => return scope.cast(GenZir).?.zir_code.arena,
.local_val => return scope.cast(LocalVal).?.gen_zir.zir_code.arena,
.local_ptr => return scope.cast(LocalPtr).?.gen_zir.zir_code.arena,
- .gen_suspend => return scope.cast(GenZir).?.zir_code.arena,
- .gen_nosuspend => return scope.cast(Nosuspend).?.gen_zir.zir_code.arena,
.file => unreachable,
.container => unreachable,
.decl_ref => unreachable,
@@ -428,8 +426,6 @@ pub const Scope = struct {
.gen_zir => scope.cast(GenZir).?.zir_code.decl,
.local_val => scope.cast(LocalVal).?.gen_zir.zir_code.decl,
.local_ptr => scope.cast(LocalPtr).?.gen_zir.zir_code.decl,
- .gen_suspend => return scope.cast(GenZir).?.zir_code.decl,
- .gen_nosuspend => return scope.cast(Nosuspend).?.gen_zir.zir_code.decl,
.file => null,
.container => null,
.decl_ref => scope.cast(DeclRef).?.decl,
@@ -442,8 +438,6 @@ pub const Scope = struct {
.gen_zir => scope.cast(GenZir).?.zir_code.decl,
.local_val => scope.cast(LocalVal).?.gen_zir.zir_code.decl,
.local_ptr => scope.cast(LocalPtr).?.gen_zir.zir_code.decl,
- .gen_suspend => return scope.cast(GenZir).?.zir_code.decl,
- .gen_nosuspend => return scope.cast(Nosuspend).?.gen_zir.zir_code.decl,
.file => null,
.container => null,
.decl_ref => scope.cast(DeclRef).?.decl,
@@ -459,8 +453,6 @@ pub const Scope = struct {
.local_ptr => return scope.cast(LocalPtr).?.gen_zir.zir_code.decl.container,
.file => return &scope.cast(File).?.root_container,
.container => return scope.cast(Container).?,
- .gen_suspend => return scope.cast(GenZir).?.zir_code.decl.container,
- .gen_nosuspend => return scope.cast(Nosuspend).?.gen_zir.zir_code.decl.container,
.decl_ref => return scope.cast(DeclRef).?.decl.container,
}
}
@@ -474,8 +466,6 @@ pub const Scope = struct {
.gen_zir => unreachable,
.local_val => unreachable,
.local_ptr => unreachable,
- .gen_suspend => unreachable,
- .gen_nosuspend => unreachable,
.file => unreachable,
.container => return scope.cast(Container).?.fullyQualifiedNameHash(name),
.decl_ref => unreachable,
@@ -491,8 +481,6 @@ pub const Scope = struct {
.local_val => return &scope.cast(LocalVal).?.gen_zir.zir_code.decl.container.file_scope.tree,
.local_ptr => return &scope.cast(LocalPtr).?.gen_zir.zir_code.decl.container.file_scope.tree,
.container => return &scope.cast(Container).?.file_scope.tree,
- .gen_suspend => return &scope.cast(GenZir).?.zir_code.decl.container.file_scope.tree,
- .gen_nosuspend => return &scope.cast(Nosuspend).?.gen_zir.zir_code.decl.container.file_scope.tree,
.decl_ref => return &scope.cast(DeclRef).?.decl.container.file_scope.tree,
}
}
@@ -501,10 +489,9 @@ pub const Scope = struct {
pub fn getGenZir(scope: *Scope) *GenZir {
return switch (scope.tag) {
.block => unreachable,
- .gen_zir, .gen_suspend => scope.cast(GenZir).?,
+ .gen_zir => scope.cast(GenZir).?,
.local_val => return scope.cast(LocalVal).?.gen_zir,
.local_ptr => return scope.cast(LocalPtr).?.gen_zir,
- .gen_nosuspend => return scope.cast(Nosuspend).?.gen_zir,
.file => unreachable,
.container => unreachable,
.decl_ref => unreachable,
@@ -521,8 +508,6 @@ pub const Scope = struct {
.gen_zir => unreachable,
.local_val => unreachable,
.local_ptr => unreachable,
- .gen_suspend => unreachable,
- .gen_nosuspend => unreachable,
.decl_ref => unreachable,
}
}
@@ -535,8 +520,6 @@ pub const Scope = struct {
.local_val => unreachable,
.local_ptr => unreachable,
.block => unreachable,
- .gen_suspend => unreachable,
- .gen_nosuspend => unreachable,
.decl_ref => unreachable,
}
}
@@ -552,41 +535,11 @@ pub const Scope = struct {
.local_val => @fieldParentPtr(LocalVal, "base", cur).parent,
.local_ptr => @fieldParentPtr(LocalPtr, "base", cur).parent,
.block => return @fieldParentPtr(Block, "base", cur).src_decl.container.file_scope,
- .gen_suspend => @fieldParentPtr(GenZir, "base", cur).parent,
- .gen_nosuspend => @fieldParentPtr(Nosuspend, "base", cur).parent,
.decl_ref => return @fieldParentPtr(DeclRef, "base", cur).decl.container.file_scope,
};
}
}
- pub fn getSuspend(base: *Scope) ?*Scope.GenZir {
- var cur = base;
- while (true) {
- cur = switch (cur.tag) {
- .gen_zir => @fieldParentPtr(GenZir, "base", cur).parent,
- .local_val => @fieldParentPtr(LocalVal, "base", cur).parent,
- .local_ptr => @fieldParentPtr(LocalPtr, "base", cur).parent,
- .gen_nosuspend => @fieldParentPtr(Nosuspend, "base", cur).parent,
- .gen_suspend => return @fieldParentPtr(GenZir, "base", cur),
- else => return null,
- };
- }
- }
-
- pub fn getNosuspend(base: *Scope) ?*Scope.Nosuspend {
- var cur = base;
- while (true) {
- cur = switch (cur.tag) {
- .gen_zir => @fieldParentPtr(GenZir, "base", cur).parent,
- .local_val => @fieldParentPtr(LocalVal, "base", cur).parent,
- .local_ptr => @fieldParentPtr(LocalPtr, "base", cur).parent,
- .gen_suspend => @fieldParentPtr(GenZir, "base", cur).parent,
- .gen_nosuspend => return @fieldParentPtr(Nosuspend, "base", cur),
- else => return null,
- };
- }
- }
-
fn name_hash_hash(x: NameHash) u32 {
return @truncate(u32, @bitCast(u128, x));
}
@@ -604,8 +557,6 @@ pub const Scope = struct {
gen_zir,
local_val,
local_ptr,
- gen_suspend,
- gen_nosuspend,
/// Used for simple error reporting. Only contains a reference to a
/// `Decl` for use with `srcDecl` and `ownerDecl`.
/// Has no parents or children.
@@ -1382,16 +1333,6 @@ pub const Scope = struct {
src: LazySrcLoc,
};
- pub const Nosuspend = struct {
- pub const base_tag: Tag = .gen_nosuspend;
-
- base: Scope = Scope{ .tag = base_tag },
- /// Parents can be: `LocalVal`, `LocalPtr`, `GenZir`.
- parent: *Scope,
- gen_zir: *GenZir,
- src: LazySrcLoc,
- };
-
pub const DeclRef = struct {
pub const base_tag: Tag = .decl_ref;
base: Scope = Scope{ .tag = base_tag },
@@ -1475,8 +1416,6 @@ pub const WipZirCode = struct {
.bool_and,
.bool_or,
.call,
- .call_async_kw,
- .call_no_async,
.call_compile_time,
.call_none,
.cmp_lt,
@@ -1549,7 +1488,6 @@ pub const WipZirCode = struct {
.enum_literal,
.enum_literal_small,
.merge_error_sets,
- .anyframe_type,
.error_union_type,
.bit_not,
.error_set,
@@ -1560,9 +1498,6 @@ pub const WipZirCode = struct {
.import,
.typeof_peer,
.resolve_inferred_alloc,
- .@"resume",
- .@"await",
- .nosuspend_await,
=> return false,
.breakpoint,
@@ -1581,8 +1516,6 @@ pub const WipZirCode = struct {
.ret_coerce,
.@"unreachable",
.loop,
- .suspend_block,
- .suspend_block_one,
.elided,
=> return true,
}
@@ -1692,7 +1625,6 @@ pub const SrcLoc = struct {
.node_offset_asm_source,
.node_offset_asm_ret_ty,
.node_offset_if_cond,
- .node_offset_anyframe_type,
.node_offset_bin_op,
.node_offset_bin_lhs,
.node_offset_bin_rhs,
@@ -1750,7 +1682,6 @@ pub const SrcLoc = struct {
.node_offset_asm_source => @panic("TODO"),
.node_offset_asm_ret_ty => @panic("TODO"),
.node_offset_if_cond => @panic("TODO"),
- .node_offset_anyframe_type => @panic("TODO"),
.node_offset_bin_op => @panic("TODO"),
.node_offset_bin_lhs => @panic("TODO"),
.node_offset_bin_rhs => @panic("TODO"),
@@ -1872,12 +1803,6 @@ pub const LazySrcLoc = union(enum) {
/// to the condition expression.
/// The Decl is determined contextually.
node_offset_if_cond: i32,
- /// The source location points to the type expression of an `anyframe->T`
- /// expression, found by taking this AST node index offset from the containing
- /// Decl AST node, which points to a `anyframe->T` expression AST node. Next, navigate
- /// to the type expression.
- /// The Decl is determined contextually.
- node_offset_anyframe_type: i32,
/// The source location points to a binary expression, such as `a + b`, found
/// by taking this AST node index offset from the containing Decl AST node.
/// The Decl is determined contextually.
@@ -1922,7 +1847,6 @@ pub const LazySrcLoc = union(enum) {
.node_offset_asm_source,
.node_offset_asm_ret_ty,
.node_offset_if_cond,
- .node_offset_anyframe_type,
.node_offset_bin_op,
.node_offset_bin_lhs,
.node_offset_bin_rhs,
@@ -1962,7 +1886,6 @@ pub const LazySrcLoc = union(enum) {
.node_offset_asm_source,
.node_offset_asm_ret_ty,
.node_offset_if_cond,
- .node_offset_anyframe_type,
.node_offset_bin_op,
.node_offset_bin_lhs,
.node_offset_bin_rhs,
@@ -3888,7 +3811,7 @@ pub fn failWithOwnedErrorMsg(mod: *Module, scope: *Scope, err_msg: *ErrorMsg) In
}
mod.failed_decls.putAssumeCapacityNoClobber(block.sema.owner_decl, err_msg);
},
- .gen_zir, .gen_suspend => {
+ .gen_zir => {
const gen_zir = scope.cast(Scope.GenZir).?;
gen_zir.zir_code.decl.analysis = .sema_failure;
gen_zir.zir_code.decl.generation = mod.generation;
@@ -3906,12 +3829,6 @@ pub fn failWithOwnedErrorMsg(mod: *Module, scope: *Scope, err_msg: *ErrorMsg) In
gen_zir.zir_code.decl.generation = mod.generation;
mod.failed_decls.putAssumeCapacityNoClobber(gen_zir.zir_code.decl, err_msg);
},
- .gen_nosuspend => {
- const gen_zir = scope.cast(Scope.Nosuspend).?.gen_zir;
- gen_zir.zir_code.decl.analysis = .sema_failure;
- gen_zir.zir_code.decl.generation = mod.generation;
- mod.failed_decls.putAssumeCapacityNoClobber(gen_zir.zir_code.decl, err_msg);
- },
.file => unreachable,
.container => unreachable,
.decl_ref => {
@@ -4157,10 +4074,6 @@ pub fn errorUnionType(
});
}
-pub fn anyframeType(mod: *Module, arena: *Allocator, return_type: Type) Allocator.Error!Type {
- return Type.Tag.anyframe_T.create(arena, return_type);
-}
-
pub fn dumpInst(mod: *Module, scope: *Scope, inst: *ir.Inst) void {
const zir_module = scope.namespace();
const source = zir_module.getSource(mod) catch @panic("dumpInst failed to get source");
src/Sema.zig
@@ -97,8 +97,6 @@ pub fn analyzeBody(sema: *Sema, block: *Scope.Block, body: []const zir.Inst.Inde
.break_void_tok => try sema.zirBreakVoidTok(block, zir_inst),
.breakpoint => try sema.zirBreakpoint(block, zir_inst),
.call => try sema.zirCall(block, zir_inst, .auto),
- .call_async_kw => try sema.zirCall(block, zir_inst, .async_kw),
- .call_no_async => try sema.zirCall(block, zir_inst, .no_async),
.call_compile_time => try sema.zirCall(block, zir_inst, .compile_time),
.call_none => try sema.zirCallNone(block, zir_inst),
.coerce_result_ptr => try sema.zirCoerceResultPtr(block, zir_inst),
@@ -205,7 +203,6 @@ pub fn analyzeBody(sema: *Sema, block: *Scope.Block, body: []const zir.Inst.Inde
.enum_literal_small => try sema.zirEnumLiteralSmall(block, zir_inst),
.merge_error_sets => try sema.zirMergeErrorSets(block, zir_inst),
.error_union_type => try sema.zirErrorUnionType(block, zir_inst),
- .anyframe_type => try sema.zirAnyframeType(block, zir_inst),
.error_set => try sema.zirErrorSet(block, zir_inst),
.error_value => try sema.zirErrorValue(block, zir_inst),
.slice_start => try sema.zirSliceStart(block, zir_inst),
@@ -214,11 +211,6 @@ pub fn analyzeBody(sema: *Sema, block: *Scope.Block, body: []const zir.Inst.Inde
.import => try sema.zirImport(block, zir_inst),
.bool_and => try sema.zirBoolOp(block, zir_inst, false),
.bool_or => try sema.zirBoolOp(block, zir_inst, true),
- .@"await" => try sema.zirAwait(block, zir_inst),
- .nosuspend_await => try sema.zirNosuspendAwait(block, zir_inst),
- .suspend_block_one => @panic("TODO"),
- .suspend_block => @panic("TODO"),
- .@"resume" => @panic("TODO"),
// TODO
//.switchbr => try sema.zirSwitchBr(block, zir_inst, false),
//.switchbr_ref => try sema.zirSwitchBr(block, zir_inst, true),
@@ -1276,19 +1268,6 @@ fn zirErrorUnionType(sema: *Sema, block: *Scope.Block, inst: zir.Inst.Index) Inn
return sema.mod.constType(sema.arena, .unneeded, err_union_ty);
}
-fn zirAnyframeType(sema: *Sema, block: *Scope.Block, inst: zir.Inst.Index) InnerError!*Inst {
- const tracy = trace(@src());
- defer tracy.end();
-
- const inst_data = sema.code.instructions.items(.data)[inst].un_node;
- const src = inst_data.src();
- const operand_src: LazySrcLoc = .{ .node_offset_anyframe_type = inst_data.src_node };
- const return_type = try sema.resolveType(block, operand_src, inst_data.operand);
- const anyframe_type = try sema.mod.anyframeType(sema.arena, return_type);
-
- return sema.mod.constType(sema.arena, src, anyframe_type);
-}
-
fn zirErrorSet(sema: *Sema, block: *Scope.Block, inst: zir.Inst.Index) InnerError!*Inst {
const tracy = trace(@src());
defer tracy.end();
@@ -2989,16 +2968,6 @@ fn zirPtrType(sema: *Sema, block: *Scope.Block, inst: zir.Inst.Index) InnerError
return sema.mod.constType(sema.arena, src, ty);
}
-fn zirAwait(sema: *Sema, block: *Scope.Block, inst: zir.Inst.Index) InnerError!*Inst {
- const inst_data = sema.code.instructions.items(.data)[inst].un_node;
- return sema.mod.fail(&block.base, inst_data.src(), "TODO implement Sema await", .{});
-}
-
-fn zirNosuspendAwait(sema: *Sema, block: *Scope.Block, inst: zir.Inst.Index) InnerError!*Inst {
- const inst_data = sema.code.instructions.items(.data)[inst].un_node;
- return sema.mod.fail(&block.base, inst_data.src(), "TODO implement Sema nosuspend_await", .{});
-}
-
fn requireFunctionBlock(sema: *Sema, block: *Scope.Block, src: LazySrcLoc) !void {
if (sema.func == null) {
return sema.mod.fail(&block.base, src, "instruction illegal outside function body", .{});
src/type.zig
@@ -92,8 +92,6 @@ pub const Type = extern union {
.anyerror_void_error_union, .error_union => return .ErrorUnion,
- .anyframe_T, .@"anyframe" => return .AnyFrame,
-
.empty_struct => return .Struct,
.var_args_param => unreachable, // can be any type
@@ -397,7 +395,6 @@ pub const Type = extern union {
.const_slice_u8,
.enum_literal,
.anyerror_void_error_union,
- .@"anyframe",
.inferred_alloc_const,
.inferred_alloc_mut,
.var_args_param,
@@ -418,7 +415,6 @@ pub const Type = extern union {
.optional,
.optional_single_mut_pointer,
.optional_single_const_pointer,
- .anyframe_T,
=> return self.copyPayloadShallow(allocator, Payload.ElemType),
.int_signed,
@@ -546,7 +542,6 @@ pub const Type = extern union {
// TODO this should print the structs name
.empty_struct => return out_stream.writeAll("struct {}"),
- .@"anyframe" => return out_stream.writeAll("anyframe"),
.anyerror_void_error_union => return out_stream.writeAll("anyerror!void"),
.const_slice_u8 => return out_stream.writeAll("[]const u8"),
.fn_noreturn_no_args => return out_stream.writeAll("fn() noreturn"),
@@ -574,12 +569,6 @@ pub const Type = extern union {
continue;
},
- .anyframe_T => {
- const return_type = ty.castTag(.anyframe_T).?.data;
- try out_stream.print("anyframe->", .{});
- ty = return_type;
- continue;
- },
.array_u8 => {
const len = ty.castTag(.array_u8).?.data;
return out_stream.print("[{d}]u8", .{len});
@@ -814,8 +803,6 @@ pub const Type = extern union {
.optional,
.optional_single_mut_pointer,
.optional_single_const_pointer,
- .@"anyframe",
- .anyframe_T,
.anyerror_void_error_union,
.error_set,
.error_set_single,
@@ -898,8 +885,6 @@ pub const Type = extern union {
.mut_slice,
.optional_single_const_pointer,
.optional_single_mut_pointer,
- .@"anyframe",
- .anyframe_T,
=> return @divExact(target.cpu.arch.ptrBitWidth(), 8),
.pointer => {
@@ -1025,7 +1010,7 @@ pub const Type = extern union {
.i64, .u64 => return 8,
.u128, .i128 => return 16,
- .@"anyframe", .anyframe_T, .isize, .usize => return @divExact(target.cpu.arch.ptrBitWidth(), 8),
+ .isize, .usize => return @divExact(target.cpu.arch.ptrBitWidth(), 8),
.const_slice,
.mut_slice,
@@ -1169,8 +1154,6 @@ pub const Type = extern union {
.const_slice,
.mut_slice,
.error_union,
- .@"anyframe",
- .anyframe_T,
.anyerror_void_error_union,
.error_set,
.error_set_single,
@@ -1244,8 +1227,6 @@ pub const Type = extern union {
.optional_single_const_pointer,
.enum_literal,
.error_union,
- .@"anyframe",
- .anyframe_T,
.anyerror_void_error_union,
.error_set,
.error_set_single,
@@ -1338,8 +1319,6 @@ pub const Type = extern union {
.optional_single_const_pointer,
.enum_literal,
.error_union,
- .@"anyframe",
- .anyframe_T,
.anyerror_void_error_union,
.error_set,
.error_set_single,
@@ -1416,8 +1395,6 @@ pub const Type = extern union {
.enum_literal,
.mut_slice,
.error_union,
- .@"anyframe",
- .anyframe_T,
.anyerror_void_error_union,
.error_set,
.error_set_single,
@@ -1503,8 +1480,6 @@ pub const Type = extern union {
.optional_single_const_pointer,
.enum_literal,
.error_union,
- .@"anyframe",
- .anyframe_T,
.anyerror_void_error_union,
.error_set,
.error_set_single,
@@ -1585,8 +1560,6 @@ pub const Type = extern union {
.optional_single_const_pointer,
.enum_literal,
.error_union,
- .@"anyframe",
- .anyframe_T,
.anyerror_void_error_union,
.error_set,
.error_set_single,
@@ -1709,8 +1682,6 @@ pub const Type = extern union {
.optional_single_mut_pointer => unreachable,
.enum_literal => unreachable,
.error_union => unreachable,
- .@"anyframe" => unreachable,
- .anyframe_T => unreachable,
.anyerror_void_error_union => unreachable,
.error_set => unreachable,
.error_set_single => unreachable,
@@ -1859,8 +1830,6 @@ pub const Type = extern union {
.optional_single_const_pointer,
.enum_literal,
.error_union,
- .@"anyframe",
- .anyframe_T,
.anyerror_void_error_union,
.error_set,
.error_set_single,
@@ -1931,8 +1900,6 @@ pub const Type = extern union {
.optional_single_const_pointer,
.enum_literal,
.error_union,
- .@"anyframe",
- .anyframe_T,
.anyerror_void_error_union,
.error_set,
.error_set_single,
@@ -2018,8 +1985,6 @@ pub const Type = extern union {
.optional_single_const_pointer,
.enum_literal,
.error_union,
- .@"anyframe",
- .anyframe_T,
.anyerror_void_error_union,
.error_set,
.error_set_single,
@@ -2101,8 +2066,6 @@ pub const Type = extern union {
.optional_single_const_pointer,
.enum_literal,
.error_union,
- .@"anyframe",
- .anyframe_T,
.anyerror_void_error_union,
.error_set,
.error_set_single,
@@ -2170,8 +2133,6 @@ pub const Type = extern union {
.optional_single_const_pointer,
.enum_literal,
.error_union,
- .@"anyframe",
- .anyframe_T,
.anyerror_void_error_union,
.error_set,
.error_set_single,
@@ -2267,8 +2228,6 @@ pub const Type = extern union {
.optional_single_const_pointer,
.enum_literal,
.error_union,
- .@"anyframe",
- .anyframe_T,
.anyerror_void_error_union,
.error_set,
.error_set_single,
@@ -2385,8 +2344,6 @@ pub const Type = extern union {
.optional_single_const_pointer,
.enum_literal,
.error_union,
- .@"anyframe",
- .anyframe_T,
.anyerror_void_error_union,
.error_set,
.error_set_single,
@@ -2469,8 +2426,6 @@ pub const Type = extern union {
.optional_single_const_pointer,
.enum_literal,
.error_union,
- .@"anyframe",
- .anyframe_T,
.anyerror_void_error_union,
.error_set,
.error_set_single,
@@ -2552,8 +2507,6 @@ pub const Type = extern union {
.optional_single_const_pointer,
.enum_literal,
.error_union,
- .@"anyframe",
- .anyframe_T,
.anyerror_void_error_union,
.error_set,
.error_set_single,
@@ -2635,8 +2588,6 @@ pub const Type = extern union {
.optional_single_const_pointer,
.enum_literal,
.error_union,
- .@"anyframe",
- .anyframe_T,
.anyerror_void_error_union,
.error_set,
.error_set_single,
@@ -2715,8 +2666,6 @@ pub const Type = extern union {
.optional_single_const_pointer,
.enum_literal,
.error_union,
- .@"anyframe",
- .anyframe_T,
.anyerror_void_error_union,
.error_set,
.error_set_single,
@@ -2795,8 +2744,6 @@ pub const Type = extern union {
.optional_single_const_pointer,
.enum_literal,
.error_union,
- .@"anyframe",
- .anyframe_T,
.anyerror_void_error_union,
.error_set,
.error_set_single,
@@ -2875,8 +2822,6 @@ pub const Type = extern union {
.optional_single_const_pointer,
.enum_literal,
.error_union,
- .@"anyframe",
- .anyframe_T,
.anyerror_void_error_union,
.error_set,
.error_set_single,
@@ -2939,8 +2884,6 @@ pub const Type = extern union {
.optional_single_const_pointer,
.enum_literal,
.anyerror_void_error_union,
- .anyframe_T,
- .@"anyframe",
.error_union,
.error_set,
.error_set_single,
@@ -3047,8 +2990,6 @@ pub const Type = extern union {
.optional_single_const_pointer,
.enum_literal,
.error_union,
- .@"anyframe",
- .anyframe_T,
.anyerror_void_error_union,
.error_set,
.error_set_single,
@@ -3136,8 +3077,6 @@ pub const Type = extern union {
.optional_single_const_pointer,
.enum_literal,
.error_union,
- .@"anyframe",
- .anyframe_T,
.anyerror_void_error_union,
.error_set,
.error_set_single,
@@ -3259,7 +3198,6 @@ pub const Type = extern union {
fn_ccc_void_no_args,
single_const_pointer_to_comptime_int,
anyerror_void_error_union,
- @"anyframe",
const_slice_u8,
/// This is a special type for variadic parameters of a function call.
/// Casts to it will validate that the type can be passed to a c calling convetion function.
@@ -3292,7 +3230,6 @@ pub const Type = extern union {
optional_single_mut_pointer,
optional_single_const_pointer,
error_union,
- anyframe_T,
error_set,
error_set_single,
empty_struct,
@@ -3345,7 +3282,6 @@ pub const Type = extern union {
.fn_ccc_void_no_args,
.single_const_pointer_to_comptime_int,
.anyerror_void_error_union,
- .@"anyframe",
.const_slice_u8,
.inferred_alloc_const,
.inferred_alloc_mut,
@@ -3367,7 +3303,6 @@ pub const Type = extern union {
.optional,
.optional_single_mut_pointer,
.optional_single_const_pointer,
- .anyframe_T,
=> Payload.ElemType,
.int_signed,
src/value.zig
@@ -62,7 +62,6 @@ pub const Value = extern union {
single_const_pointer_to_comptime_int_type,
const_slice_u8_type,
enum_literal_type,
- anyframe_type,
undef,
zero,
@@ -153,7 +152,6 @@ pub const Value = extern union {
.single_const_pointer_to_comptime_int_type,
.const_slice_u8_type,
.enum_literal_type,
- .anyframe_type,
.undef,
.zero,
.one,
@@ -308,7 +306,6 @@ pub const Value = extern union {
.single_const_pointer_to_comptime_int_type,
.const_slice_u8_type,
.enum_literal_type,
- .anyframe_type,
.undef,
.zero,
.one,
@@ -462,7 +459,6 @@ pub const Value = extern union {
.single_const_pointer_to_comptime_int_type => return out_stream.writeAll("*const comptime_int"),
.const_slice_u8_type => return out_stream.writeAll("[]const u8"),
.enum_literal_type => return out_stream.writeAll("@Type(.EnumLiteral)"),
- .anyframe_type => return out_stream.writeAll("anyframe"),
// TODO this should print `NAME{}`
.empty_struct_value => return out_stream.writeAll("struct {}{}"),
@@ -590,7 +586,6 @@ pub const Value = extern union {
.single_const_pointer_to_comptime_int_type => Type.initTag(.single_const_pointer_to_comptime_int),
.const_slice_u8_type => Type.initTag(.const_slice_u8),
.enum_literal_type => Type.initTag(.enum_literal),
- .anyframe_type => Type.initTag(.@"anyframe"),
.int_type => {
const payload = self.castTag(.int_type).?.data;
@@ -687,7 +682,6 @@ pub const Value = extern union {
.single_const_pointer_to_comptime_int_type,
.const_slice_u8_type,
.enum_literal_type,
- .anyframe_type,
.null_value,
.function,
.extern_fn,
@@ -774,7 +768,6 @@ pub const Value = extern union {
.single_const_pointer_to_comptime_int_type,
.const_slice_u8_type,
.enum_literal_type,
- .anyframe_type,
.null_value,
.function,
.extern_fn,
@@ -861,7 +854,6 @@ pub const Value = extern union {
.single_const_pointer_to_comptime_int_type,
.const_slice_u8_type,
.enum_literal_type,
- .anyframe_type,
.null_value,
.function,
.extern_fn,
@@ -975,7 +967,6 @@ pub const Value = extern union {
.single_const_pointer_to_comptime_int_type,
.const_slice_u8_type,
.enum_literal_type,
- .anyframe_type,
.null_value,
.function,
.extern_fn,
@@ -1067,7 +1058,6 @@ pub const Value = extern union {
.single_const_pointer_to_comptime_int_type,
.const_slice_u8_type,
.enum_literal_type,
- .anyframe_type,
.null_value,
.function,
.extern_fn,
@@ -1224,7 +1214,6 @@ pub const Value = extern union {
.single_const_pointer_to_comptime_int_type,
.const_slice_u8_type,
.enum_literal_type,
- .anyframe_type,
.bool_true,
.bool_false,
.null_value,
@@ -1308,7 +1297,6 @@ pub const Value = extern union {
.single_const_pointer_to_comptime_int_type,
.const_slice_u8_type,
.enum_literal_type,
- .anyframe_type,
.null_value,
.function,
.extern_fn,
@@ -1460,7 +1448,6 @@ pub const Value = extern union {
.single_const_pointer_to_comptime_int_type,
.const_slice_u8_type,
.enum_literal_type,
- .anyframe_type,
.ty,
=> {
// Directly return Type.hash, toType can only fail for .int_type and .error_set.
@@ -1618,7 +1605,6 @@ pub const Value = extern union {
.single_const_pointer_to_comptime_int_type,
.const_slice_u8_type,
.enum_literal_type,
- .anyframe_type,
.zero,
.one,
.bool_true,
@@ -1705,7 +1691,6 @@ pub const Value = extern union {
.single_const_pointer_to_comptime_int_type,
.const_slice_u8_type,
.enum_literal_type,
- .anyframe_type,
.zero,
.one,
.bool_true,
@@ -1809,7 +1794,6 @@ pub const Value = extern union {
.single_const_pointer_to_comptime_int_type,
.const_slice_u8_type,
.enum_literal_type,
- .anyframe_type,
.zero,
.one,
.empty_array,
@@ -1891,7 +1875,6 @@ pub const Value = extern union {
.single_const_pointer_to_comptime_int_type,
.const_slice_u8_type,
.enum_literal_type,
- .anyframe_type,
.zero,
.one,
.null_value,
@@ -1993,7 +1976,6 @@ pub const Value = extern union {
.single_const_pointer_to_comptime_int_type,
.const_slice_u8_type,
.enum_literal_type,
- .anyframe_type,
.error_set,
=> true,
src/zir.zig
@@ -161,7 +161,6 @@ pub const Const = enum {
single_const_pointer_to_comptime_int_type,
const_slice_u8_type,
enum_literal_type,
- anyframe_type,
/// `undefined` (untyped)
undef,
@@ -343,10 +342,6 @@ pub const const_inst_list = std.enums.directEnumArray(Const, TypedValue, 0, .{
.ty = Type.initTag(.type),
.val = Value.initTag(.enum_literal_type),
},
- .anyframe_type = .{
- .ty = Type.initTag(.type),
- .val = Value.initTag(.anyframe_type),
- },
.undef = .{
.ty = Type.initTag(.@"undefined"),
@@ -409,9 +404,6 @@ pub const Inst = struct {
alloc_inferred,
/// Same as `alloc_inferred` except mutable.
alloc_inferred_mut,
- /// Create an `anyframe->T`.
- /// Uses the `un_node` field. AST node is the `anyframe->T` syntax. Operand is the type.
- anyframe_type,
/// Array concatenation. `a ++ b`
/// Uses the `pl_node` union field. Payload is `Bin`.
array_cat,
@@ -441,8 +433,6 @@ pub const Inst = struct {
/// Inline assembly with the volatile attribute.
/// Uses the `pl_node` union field. Payload is `Asm`. AST node is the assembly node.
asm_volatile,
- /// `await x` syntax. Uses the `un_node` union field.
- @"await",
/// Bitwise AND. `&`
bit_and,
/// TODO delete this instruction, it has no purpose.
@@ -495,10 +485,6 @@ pub const Inst = struct {
/// Function call with modifier `.auto`.
/// Uses `pl_node`. AST node is the function call. Payload is `Call`.
call,
- /// Same as `call` but with modifier `.async_kw`.
- call_async_kw,
- /// Same as `call` but with modifier `.no_async`.
- call_no_async,
/// Same as `call` but with modifier `.compile_time`.
call_compile_time,
/// Function call with modifier `.auto`, empty parameter list.
@@ -666,8 +652,6 @@ pub const Inst = struct {
/// Twos complement wrapping integer multiplication.
/// Uses the `pl_node` union field. Payload is `Bin`.
mulwrap,
- /// An await inside a nosuspend scope.
- nosuspend_await,
/// Given a reference to a function and a parameter index, returns the
/// type of the parameter. The only usage of this instruction is for the
/// result location of parameters of function calls. In the case of a function's
@@ -686,8 +670,6 @@ pub const Inst = struct {
/// instruction.
/// Uses the `un_tok` union field.
ref,
- /// Resume an async function.
- @"resume",
/// Obtains a pointer to the return value.
/// Uses the `node` union field.
ret_ptr,
@@ -841,12 +823,6 @@ pub const Inst = struct {
/// An enum literal 8 or fewer bytes. No source location.
/// Uses the `small_str` field.
enum_literal_small,
- /// Suspend an async function. The suspend block has 0 or 1 statements in it.
- /// Uses the `un_node` union field.
- suspend_block_one,
- /// Suspend an async function. The suspend block has any number of statements in it.
- /// Uses the `pl_node` union field. Payload is `MultiOp`.
- suspend_block,
// /// A switch expression.
// /// lhs is target, SwitchBr[rhs]
// /// All prongs of target handled.
@@ -918,8 +894,6 @@ pub const Inst = struct {
.bool_or,
.breakpoint,
.call,
- .call_async_kw,
- .call_no_async,
.call_compile_time,
.call_none,
.cmp_lt,
@@ -997,7 +971,6 @@ pub const Inst = struct {
.enum_literal,
.enum_literal_small,
.merge_error_sets,
- .anyframe_type,
.error_union_type,
.bit_not,
.error_set,
@@ -1010,9 +983,6 @@ pub const Inst = struct {
.resolve_inferred_alloc,
.set_eval_branch_quota,
.compile_log,
- .@"resume",
- .@"await",
- .nosuspend_await,
.elided,
=> false,
@@ -1025,8 +995,6 @@ pub const Inst = struct {
.ret_coerce,
.@"unreachable",
.loop,
- .suspend_block,
- .suspend_block_one,
=> true,
};
}
@@ -1347,9 +1315,7 @@ const Writer = struct {
.alloc_mut,
.alloc_inferred,
.alloc_inferred_mut,
- .anyframe_type,
.indexable_ptr_len,
- .@"await",
.bit_not,
.bool_not,
.negate,
@@ -1364,7 +1330,6 @@ const Writer = struct {
.ret_node,
.set_eval_branch_quota,
.resolve_inferred_alloc,
- .suspend_block_one,
.optional_type,
.optional_type_from_ptr_elem,
.optional_payload_safe,
@@ -1409,8 +1374,6 @@ const Writer = struct {
.block_comptime,
.block_comptime_flat,
.call,
- .call_async_kw,
- .call_no_async,
.call_compile_time,
.compile_log,
.condbr,
@@ -1426,7 +1389,6 @@ const Writer = struct {
.slice_end,
.slice_sentinel,
.typeof_peer,
- .suspend_block,
=> try self.writePlNode(stream, inst),
.add,
@@ -1481,8 +1443,6 @@ const Writer = struct {
.bitcast_result_ptr,
.error_union_type,
.error_set,
- .nosuspend_await,
- .@"resume",
.store,
.store_to_block_ptr,
.store_to_inferred_ptr,