aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
authorMathias Magnusson <mathias@magnusson.space>2025-07-29 18:39:46 +0200
committerMathias Magnusson <mathias@magnusson.space>2025-07-29 18:39:46 +0200
commit9f728121a17cbb997c18752d01d7529539966e94 (patch)
treec557e4fccf50832fc30a5eab190e36678e22222d /src
parent15984567e8187f529fbe649109ef83bba309a2d8 (diff)
downloadhuginn-9f728121a17cbb997c18752d01d7529539966e94.tar.gz
make parameters usable
Diffstat (limited to 'src')
-rw-r--r--src/codegen.zig18
-rw-r--r--src/compile.zig58
-rw-r--r--src/parse.zig52
3 files changed, 85 insertions, 43 deletions
diff --git a/src/codegen.zig b/src/codegen.zig
index 0e70a0b..97e160c 100644
--- a/src/codegen.zig
+++ b/src/codegen.zig
@@ -585,6 +585,7 @@ const ProcedureContext = struct {
register_allocator: RegisterAllocator(compile.VReg),
lvar_allocator: RegisterAllocator(compile.LVar),
ctx: *Context,
+ proc: compile.Procedure,
// Current stuff that changes often, basically here to avoid prop drilling.
block: ?*const compile.BasicBlock = null,
@@ -664,7 +665,7 @@ const ProcedureContext = struct {
}
}
- fn genProcCall(self: *Self, call: compile.Instr.ProcCall) !void {
+ fn genCall(self: *Self, call: compile.Instr.Call) !void {
const arg = self.register_allocator.get(call.arg);
try self.freeUnusedVRegs();
@@ -752,17 +753,25 @@ const ProcedureContext = struct {
fn prologue(self: *Self) !void {
try self.emit(.addi(.sp, .sp, -8));
try self.emit(.sd(.sp, 0, .ra));
+
+ if (self.proc.param_reg) |reg| {
+ const param = try self.register_allocator.allocate(reg);
+ try self.emit(.addi(param, .a0, 0));
+ }
}
fn epilogue(self: *Self) !void {
+ if (self.proc.param_reg) |reg| {
+ self.register_allocator.free(reg);
+ }
try self.emit(.ld(.ra, .sp, 0));
try self.emit(.addi(.sp, .sp, 8));
try self.emit(.jalr(.zero, .ra, 0));
}
- fn codegenProc(self: *Self, proc: compile.Procedure) !void {
+ fn codegenProc(self: *Self) !void {
var first = true;
- for (proc.blocks) |block| {
+ for (self.proc.blocks) |block| {
try self.ctx.block_addrs.putNoClobber(block.ref, self.ctx.instructions.items.len);
if (first) {
try self.prologue();
@@ -866,10 +875,11 @@ pub fn create_elf(allocator: Allocator, mod: compile.Module) ![]u8 {
.register_allocator = try .init(allocator, &.{ .t6, .t5, .t4, .t3, .t2, .t1, .t0 }),
.lvar_allocator = try .init(allocator, &.{ .s11, .s10, .s9, .s8, .s7, .s6, .s5, .s4, .s3, .s2, .s1, .s0 }),
.ctx = &ctx,
+ .proc = proc,
};
defer proc_ctx.deinit();
- try proc_ctx.codegenProc(proc);
+ try proc_ctx.codegenProc();
std.debug.assert(proc_ctx.register_allocator.allocated.count() == 0);
}
diff --git a/src/compile.zig b/src/compile.zig
index c84b2cc..80a9a17 100644
--- a/src/compile.zig
+++ b/src/compile.zig
@@ -41,24 +41,36 @@ pub const Module = struct {
for (self.procedures) |proc| {
try writer.print("{}", .{proc});
}
+ for ([_]struct { []const u8, BlockRef }{
+ .{ "print", self.print_block },
+ .{ "read_int", self.read_int_block },
+ .{ "exit", self.exit_block },
+ }) |builtin| {
+ const name, const block = builtin;
+ try writer.print("{s}:\n ${}: @builtin\n\n", .{ name, @intFromEnum(block) });
+ }
}
};
pub const Procedure = struct {
name: []const u8,
blocks: []BasicBlock,
+ param_reg: ?VReg,
- fn init(allocator: Allocator, name: []const u8, blocks: []BasicBlock) !Procedure {
+ fn init(allocator: Allocator, name: []const u8, blocks: []BasicBlock, param_reg: ?VReg) !Procedure {
for (blocks) |*block| {
try block.finalize(allocator);
+ if (param_reg) |p| _ = block.vreg_last_use.remove(p);
}
- return .{ .name = name, .blocks = blocks };
+ return .{ .name = name, .blocks = blocks, .param_reg = param_reg };
}
pub fn format(self: Procedure, comptime fmt: []const u8, options: std.fmt.FormatOptions, writer: anytype) !void {
_ = .{ fmt, options };
- try writer.print("{s}:\n", .{self.name});
+ try writer.print("{s}(", .{self.name});
+ if (self.param_reg) |reg| try writer.print("%{}", .{@intFromEnum(reg)});
+ try writer.print("):\n", .{});
for (self.blocks) |block| {
try writer.print("{}", .{block});
}
@@ -111,7 +123,7 @@ pub const Instr = struct {
pub const Type = union(enum) {
constant: Constant,
bin_op: BinOp,
- proc_call: ProcCall,
+ call: Call,
branch: Branch,
jump: Jump,
assign_local: AssignLocal,
@@ -148,12 +160,12 @@ pub const Instr = struct {
}
};
- pub const ProcCall = struct {
+ pub const Call = struct {
dest: VReg,
arg: VReg,
proc: BlockRef,
- pub fn sources(self: ProcCall) Sources {
+ pub fn sources(self: Call) Sources {
return Sources.fromSlice(&.{self.arg}) catch unreachable;
}
};
@@ -216,7 +228,7 @@ pub const Instr = struct {
pub fn dest(self: *const Instr) ?VReg {
return switch (self.type) {
- inline .constant, .bin_op, .proc_call, .get_local => |s| s.dest,
+ inline .constant, .bin_op, .call, .get_local => |s| s.dest,
.branch, .jump, .ret, .assign_local => null,
};
}
@@ -240,12 +252,12 @@ pub const Instr = struct {
@intFromEnum(bin_op.rhs),
},
),
- .proc_call => |proc_call| try writer.print(
+ .call => |call| try writer.print(
"%{} = call ${}(%{})",
.{
- @intFromEnum(proc_call.dest),
- @intFromEnum(proc_call.proc),
- @intFromEnum(proc_call.arg),
+ @intFromEnum(call.dest),
+ @intFromEnum(call.proc),
+ @intFromEnum(call.arg),
},
),
.branch => |branch| {
@@ -264,7 +276,6 @@ pub const Instr = struct {
.get_local => |get_local| {
try writer.print("%{} = @{}", .{ @intFromEnum(get_local.dest), @intFromEnum(get_local.local) });
},
-
.ret => |ret| try writer.print("return %{}", .{@intFromEnum(ret.val)}),
}
}
@@ -341,9 +352,16 @@ fn compileProcedure(
.vreg_ctr = .init,
.lvar_ctr = .init,
.scope = .{ .locals = .empty, .parent = null },
+ .param = .{ .name = "", .reg = undefined },
.blocks = try .init(ctx.allocator, &.{first_block}, &.{.{ .ref = first_block }}),
.current_block = first_block,
};
+ const param_reg = if (proc.param) |param| blk: {
+ const reg = pctx.vreg_ctr.get();
+ const param_name = param.getIdent(ctx.source);
+ pctx.param = .{ .name = param_name, .reg = reg };
+ break :blk reg;
+ } else null;
try pctx.compileBlock(proc.body);
const proc_res = pctx.vreg_ctr.get();
try pctx.addInstr(.{
@@ -361,7 +379,7 @@ fn compileProcedure(
std.debug.assert(kv.key_ptr.* == kv.value_ptr.ref);
blocks[i] = kv.value_ptr.*;
}
- return try .init(ctx.allocator, name.getIdent(ctx.source), blocks);
+ return try .init(ctx.allocator, name.getIdent(ctx.source), blocks, param_reg);
}
const ProcedureContext = struct {
@@ -371,6 +389,7 @@ const ProcedureContext = struct {
lvar_ctr: IdCounter(LVar),
scope: Scope,
+ param: struct { name: []const u8, reg: VReg },
blocks: std.AutoArrayHashMapUnmanaged(BlockRef, BasicBlock),
current_block: BlockRef,
@@ -407,7 +426,10 @@ const ProcedureContext = struct {
while (scope) |s| : (scope = s.parent) {
if (s.locals.get(assign_var.ident.getIdent(self.ctx.source))) |local|
break :blk local;
- } else return error.UnknownVariable;
+ } else {
+ std.log.debug("{s}", .{assign_var.ident.getIdent(self.ctx.source)});
+ return error.UnknownVariable;
+ }
};
const val = try self.compileExpr(assign_var.value);
@@ -488,7 +510,7 @@ const ProcedureContext = struct {
const arg = try self.compileExpr(call.arg);
try self.addInstr(.{
.loc = expr.loc,
- .type = .{ .proc_call = .{
+ .type = .{ .call = .{
.dest = dest,
.arg = arg,
.proc = proc,
@@ -496,10 +518,14 @@ const ProcedureContext = struct {
});
},
.identifier => {
+ const ident = expr.loc.getIdent(self.ctx.source);
+ if (std.mem.eql(u8, ident, self.param.name)) {
+ return self.param.reg;
+ }
var scope: ?*Scope = &self.scope;
const local: LVar = blk: {
while (scope) |s| : (scope = s.parent) {
- if (s.locals.get(expr.loc.getIdent(self.ctx.source))) |local| {
+ if (s.locals.get(ident)) |local| {
break :blk local;
}
}
diff --git a/src/parse.zig b/src/parse.zig
index 451b050..1aa5d07 100644
--- a/src/parse.zig
+++ b/src/parse.zig
@@ -3,7 +3,8 @@ const Allocator = std.mem.Allocator;
const root = @import("root");
const Lexer = root.Lexer;
-const Token = root.Lexer.Token;
+const Token = Lexer.Token;
+const Location = Lexer.Location;
fn Fmt(T: type) type {
return std.fmt.Formatter(struct {
@@ -27,7 +28,7 @@ pub const File = struct {
decls: []Decl,
const Decl = struct {
- loc: Lexer.Location,
+ loc: Location,
inner: Stmt.Type.AssignVar,
};
@@ -44,7 +45,7 @@ pub const File = struct {
};
pub const Block = struct {
- loc: Lexer.Location,
+ loc: Location,
stmts: []Stmt,
fn format(self: Block, writer: anytype, source: []const u8, indent: usize) !void {
@@ -58,7 +59,7 @@ pub const Block = struct {
};
pub const Stmt = struct {
- loc: Lexer.Location,
+ loc: Location,
type: Type,
pub const Type = union(enum) {
@@ -68,7 +69,7 @@ pub const Stmt = struct {
@"while": While,
pub const AssignVar = struct {
- ident: Lexer.Location,
+ ident: Location,
is_decl: bool,
value: *const Expr,
};
@@ -98,7 +99,7 @@ pub const Stmt = struct {
};
pub const Expr = struct {
- loc: Lexer.Location,
+ loc: Location,
type: Type,
pub const Type = union(enum) {
@@ -148,6 +149,7 @@ pub const Expr = struct {
pub const Proc = struct {
body: Block,
+ param: ?Location,
};
};
@@ -183,7 +185,6 @@ const ParseError = error{
UnexpectedToken,
InvalidAssignTarget,
ExprStatementMustBeCall,
- ExpectedCOmmaOrIdentifier,
};
pub fn file(allocator: Allocator, lexer: *Lexer) !File {
@@ -274,24 +275,18 @@ fn parseProc(allocator: Allocator, lexer: *Lexer) ParseError!*Expr {
if (lexer.peek().type != .proc) return parseComparisons(allocator, lexer);
const proc = try mustEat(lexer, .proc);
_ = try mustEat(lexer, .left_paren);
- var params: std.ArrayList(Lexer.Location) = .init(allocator);
- while (true) {
- const tok = lexer.next();
- switch (tok.type) {
- .right_paren => break,
- .identifier => {
- try params.append(tok.loc);
- if (lexer.peek().type == .right_paren) continue;
- _ = try mustEat(lexer, .comma);
- },
- else => return error.ExpectedCOmmaOrIdentifier,
- }
- }
+ const param_tok = lexer.next();
+ const param: ?Location = switch (param_tok.type) {
+ .identifier => param_tok.loc,
+ .right_paren => null,
+ else => |ty| return expected(&.{ .identifier, .right_paren }, ty),
+ };
+ if (param != null) _ = try mustEat(lexer, .right_paren);
const body = try parseBlock(allocator, lexer);
return allocate(Expr, allocator, .{
.loc = proc.loc.combine(body.loc),
- .type = .{ .proc = .{ .body = body } },
+ .type = .{ .proc = .{ .body = body, .param = param } },
});
}
@@ -390,10 +385,21 @@ fn parsePrimaryExpr(allocator: Allocator, lexer: *Lexer) !*Expr {
});
}
-fn mustEat(lexer: *Lexer, ty: Lexer.Token.Type) !Lexer.Token {
+fn expected(one_of: []const Token.Type, got: Token.Type) error{UnexpectedToken} {
+ for (one_of) |ty|
+ std.debug.assert(ty != got);
+ std.debug.print("Expected ", .{});
+ for (0.., one_of) |i, ty| {
+ std.debug.print("{s}{s}", .{ if (i == 0) "" else " or ", @tagName(ty) });
+ }
+ std.debug.print(". Got {s}.\n", .{@tagName(got)});
+ return error.UnexpectedToken;
+}
+
+fn mustEat(lexer: *Lexer, ty: Token.Type) !Token {
const token = lexer.next();
if (token.type != ty) {
- std.debug.print("Expected {}. Got {}\n", .{ ty, token.type });
+ std.debug.print("Expected {s}. Got {s} at {}.\n", .{ @tagName(ty), @tagName(token.type), token.loc });
return error.UnexpectedToken;
}
return token;