Skip to content

Commit 0792de9

Browse files
authored
Remove indirection and fix clang-tidy problems
1 parent 404f1b2 commit 0792de9

File tree

2 files changed

+39
-51
lines changed

2 files changed

+39
-51
lines changed

flang/include/flang/Optimizer/Dialect/FIROps.td

Lines changed: 9 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -134,15 +134,16 @@ def fir_AllocaOp : fir_Op<"alloca", [AttrSizedOperandSegments,
134134
);
135135
let results = (outs fir_ReferenceType);
136136

137-
let parser = "return parseAlloca(parser, result);";
138-
let printer = "printAlloca(p, *this);";
137+
let parser =
138+
"return parseAllocatableOp(wrapAllocaResultType, parser, result);";
139+
let printer = "printAllocatableOp(p, (*this));";
139140

140141
let builders = [
141-
OpBuilder<(ins "mlir::Type":$in_type, "llvm::StringRef":$uniq_name,
142-
"llvm::StringRef":$bindc_name, CArg<"mlir::ValueRange", "{}">:$typeparams,
142+
OpBuilder<(ins "mlir::Type":$inType, "llvm::StringRef":$uniqName,
143+
"llvm::StringRef":$bindcName, CArg<"mlir::ValueRange", "{}">:$typeparams,
143144
CArg<"mlir::ValueRange", "{}">:$shape,
144145
CArg<"llvm::ArrayRef<mlir::NamedAttribute>", "{}">:$attributes)>,
145-
OpBuilder<(ins "mlir::Type":$in_type, "llvm::StringRef":$uniq_name,
146+
OpBuilder<(ins "mlir::Type":$inType, "llvm::StringRef":$uniqName,
146147
CArg<"mlir::ValueRange", "{}">:$typeparams,
147148
CArg<"mlir::ValueRange", "{}">:$shape,
148149
CArg<"llvm::ArrayRef<mlir::NamedAttribute>", "{}">:$attributes)>,
@@ -191,8 +192,9 @@ def fir_AllocMemOp : fir_Op<"allocmem",
191192
);
192193
let results = (outs fir_HeapType);
193194

194-
let parser = "return parseAllocMem(parser, result);";
195-
let printer = "printAllocMem(p, *this);";
195+
let parser =
196+
"return parseAllocatableOp(wrapAllocMemResultType, parser, result);";
197+
let printer = "printAllocatableOp(p, (*this));";
196198

197199
let builders = [
198200
OpBuilder<(ins "mlir::Type":$in_type, "llvm::StringRef":$uniq_name,

flang/lib/Optimizer/Dialect/FIROps.cpp

Lines changed: 30 additions & 44 deletions
Original file line numberDiff line numberDiff line change
@@ -75,7 +75,11 @@ static bool verifyTypeParamCount(mlir::Type inType, unsigned numParams) {
7575
return false;
7676
}
7777

78-
// Parser shared by Alloca and Allocmem
78+
/// Parser shared by Alloca and Allocmem
79+
///
80+
/// operation ::= %res = (`fir.alloca` | `fir.allocmem`) $in_type
81+
/// ( `(` $typeparams `)` )? ( `,` $shape )?
82+
/// attr-dict-without-keyword
7983
template <typename FN>
8084
static mlir::ParseResult parseAllocatableOp(FN wrapResultType,
8185
mlir::OpAsmParser &parser,
@@ -151,15 +155,6 @@ static mlir::Type wrapAllocaResultType(mlir::Type intype) {
151155
return ReferenceType::get(intype);
152156
}
153157

154-
static mlir::ParseResult parseAlloca(mlir::OpAsmParser &parser,
155-
mlir::OperationState &result) {
156-
return parseAllocatableOp(wrapAllocaResultType, parser, result);
157-
}
158-
159-
static void printAlloca(mlir::OpAsmPrinter &p, fir::AllocaOp &op) {
160-
printAllocatableOp(p, op);
161-
}
162-
163158
mlir::Type fir::AllocaOp::getAllocatedType() {
164159
return getType().cast<ReferenceType>().getEleTy();
165160
}
@@ -169,35 +164,35 @@ mlir::Type fir::AllocaOp::getRefTy(mlir::Type ty) {
169164
}
170165

171166
void fir::AllocaOp::build(mlir::OpBuilder &builder,
172-
mlir::OperationState &result, mlir::Type in_type,
173-
llvm::StringRef uniq_name,
174-
mlir::ValueRange typeparams, mlir::ValueRange shape,
167+
mlir::OperationState &result, mlir::Type inType,
168+
llvm::StringRef uniqName, mlir::ValueRange typeparams,
169+
mlir::ValueRange shape,
175170
llvm::ArrayRef<mlir::NamedAttribute> attributes) {
176-
auto nameAttr = builder.getStringAttr(uniq_name);
177-
build(builder, result, wrapAllocaResultType(in_type), in_type, nameAttr, {},
171+
auto nameAttr = builder.getStringAttr(uniqName);
172+
build(builder, result, wrapAllocaResultType(inType), inType, nameAttr, {},
178173
typeparams, shape);
179174
result.addAttributes(attributes);
180175
}
181176

182177
void fir::AllocaOp::build(mlir::OpBuilder &builder,
183-
mlir::OperationState &result, mlir::Type in_type,
184-
llvm::StringRef uniq_name, llvm::StringRef bindc_name,
178+
mlir::OperationState &result, mlir::Type inType,
179+
llvm::StringRef uniqName, llvm::StringRef bindcName,
185180
mlir::ValueRange typeparams, mlir::ValueRange shape,
186181
llvm::ArrayRef<mlir::NamedAttribute> attributes) {
187182
auto nameAttr =
188-
uniq_name.empty() ? mlir::StringAttr{} : builder.getStringAttr(uniq_name);
189-
auto bindcAttr = bindc_name.empty() ? mlir::StringAttr{}
190-
: builder.getStringAttr(bindc_name);
191-
build(builder, result, wrapAllocaResultType(in_type), in_type, nameAttr,
183+
uniqName.empty() ? mlir::StringAttr{} : builder.getStringAttr(uniqName);
184+
auto bindcAttr =
185+
bindcName.empty() ? mlir::StringAttr{} : builder.getStringAttr(bindcName);
186+
build(builder, result, wrapAllocaResultType(inType), inType, nameAttr,
192187
bindcAttr, typeparams, shape);
193188
result.addAttributes(attributes);
194189
}
195190

196191
void fir::AllocaOp::build(mlir::OpBuilder &builder,
197-
mlir::OperationState &result, mlir::Type in_type,
192+
mlir::OperationState &result, mlir::Type inType,
198193
mlir::ValueRange typeparams, mlir::ValueRange shape,
199194
llvm::ArrayRef<mlir::NamedAttribute> attributes) {
200-
build(builder, result, wrapAllocaResultType(in_type), in_type, {}, {},
195+
build(builder, result, wrapAllocaResultType(inType), inType, {}, {},
201196
typeparams, shape);
202197
result.addAttributes(attributes);
203198
}
@@ -231,15 +226,6 @@ static mlir::Type wrapAllocMemResultType(mlir::Type intype) {
231226
return HeapType::get(intype);
232227
}
233228

234-
static mlir::ParseResult parseAllocMem(mlir::OpAsmParser &parser,
235-
mlir::OperationState &result) {
236-
return parseAllocatableOp(wrapAllocMemResultType, parser, result);
237-
}
238-
239-
static void printAllocMem(mlir::OpAsmPrinter &p, fir::AllocMemOp &op) {
240-
printAllocatableOp(p, op);
241-
}
242-
243229
mlir::Type fir::AllocMemOp::getAllocatedType() {
244230
return getType().cast<HeapType>().getEleTy();
245231
}
@@ -249,34 +235,34 @@ mlir::Type fir::AllocMemOp::getRefTy(mlir::Type ty) {
249235
}
250236

251237
void fir::AllocMemOp::build(mlir::OpBuilder &builder,
252-
mlir::OperationState &result, mlir::Type in_type,
253-
llvm::StringRef uniq_name,
238+
mlir::OperationState &result, mlir::Type inType,
239+
llvm::StringRef uniqName,
254240
mlir::ValueRange typeparams, mlir::ValueRange shape,
255241
llvm::ArrayRef<mlir::NamedAttribute> attributes) {
256-
auto nameAttr = builder.getStringAttr(uniq_name);
257-
build(builder, result, wrapAllocMemResultType(in_type), in_type, nameAttr, {},
242+
auto nameAttr = builder.getStringAttr(uniqName);
243+
build(builder, result, wrapAllocMemResultType(inType), inType, nameAttr, {},
258244
typeparams, shape);
259245
result.addAttributes(attributes);
260246
}
261247

262248
void fir::AllocMemOp::build(mlir::OpBuilder &builder,
263-
mlir::OperationState &result, mlir::Type in_type,
264-
llvm::StringRef uniq_name,
265-
llvm::StringRef bindc_name,
249+
mlir::OperationState &result, mlir::Type inType,
250+
llvm::StringRef uniqName,
251+
llvm::StringRef bindcName,
266252
mlir::ValueRange typeparams, mlir::ValueRange shape,
267253
llvm::ArrayRef<mlir::NamedAttribute> attributes) {
268-
auto nameAttr = builder.getStringAttr(uniq_name);
269-
auto bindcAttr = builder.getStringAttr(bindc_name);
270-
build(builder, result, wrapAllocMemResultType(in_type), in_type, nameAttr,
254+
auto nameAttr = builder.getStringAttr(uniqName);
255+
auto bindcAttr = builder.getStringAttr(bindcName);
256+
build(builder, result, wrapAllocMemResultType(inType), inType, nameAttr,
271257
bindcAttr, typeparams, shape);
272258
result.addAttributes(attributes);
273259
}
274260

275261
void fir::AllocMemOp::build(mlir::OpBuilder &builder,
276-
mlir::OperationState &result, mlir::Type in_type,
262+
mlir::OperationState &result, mlir::Type inType,
277263
mlir::ValueRange typeparams, mlir::ValueRange shape,
278264
llvm::ArrayRef<mlir::NamedAttribute> attributes) {
279-
build(builder, result, wrapAllocMemResultType(in_type), in_type, {}, {},
265+
build(builder, result, wrapAllocMemResultType(inType), inType, {}, {},
280266
typeparams, shape);
281267
result.addAttributes(attributes);
282268
}

0 commit comments

Comments
 (0)