Skip to content

Commit 7c8ef76

Browse files
yiwu0b11Yi Wu
andauthored
[flang] add SYSTEM runtime and lowering intrinsics support (#74309)
Calls std::system() function and pass the command, cmd on Windows or shell on Linux. Command parameter is required, exitstatus is optional. call system(command) call system(command, exitstatus) It calls `execute_command_line` runtime function with `wait` set to true. --------- Co-authored-by: Yi Wu <[email protected]>
1 parent 1695536 commit 7c8ef76

File tree

7 files changed

+184
-1
lines changed

7 files changed

+184
-1
lines changed

flang/docs/Intrinsics.md

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -757,7 +757,7 @@ This phase currently supports all the intrinsic procedures listed above but the
757757
| Object characteristic inquiry functions | ALLOCATED, ASSOCIATED, EXTENDS_TYPE_OF, IS_CONTIGUOUS, PRESENT, RANK, SAME_TYPE, STORAGE_SIZE |
758758
| Type inquiry intrinsic functions | BIT_SIZE, DIGITS, EPSILON, HUGE, KIND, MAXEXPONENT, MINEXPONENT, NEW_LINE, PRECISION, RADIX, RANGE, TINY|
759759
| Non-standard intrinsic functions | AND, OR, XOR, SHIFT, ZEXT, IZEXT, COSD, SIND, TAND, ACOSD, ASIND, ATAND, ATAN2D, COMPL, EQV, NEQV, INT8, JINT, JNINT, KNINT, QCMPLX, DREAL, DFLOAT, QEXT, QFLOAT, QREAL, DNUM, NUM, JNUM, KNUM, QNUM, RNUM, RAN, RANF, ILEN, SIZEOF, MCLOCK, SECNDS, COTAN, IBCHNG, ISHA, ISHC, ISHL, IXOR, IARG, IARGC, NARGS, GETPID, NUMARG, BADDRESS, IADDR, CACHESIZE, EOF, FP_CLASS, INT_PTR_KIND, ISNAN, MALLOC |
760-
| Intrinsic subroutines |MVBITS (elemental), CPU_TIME, DATE_AND_TIME, EVENT_QUERY, EXECUTE_COMMAND_LINE, GET_COMMAND, GET_COMMAND_ARGUMENT, GET_ENVIRONMENT_VARIABLE, MOVE_ALLOC, RANDOM_INIT, RANDOM_NUMBER, RANDOM_SEED, SIGNAL, SLEEP, SYSTEM_CLOCK |
760+
| Intrinsic subroutines |MVBITS (elemental), CPU_TIME, DATE_AND_TIME, EVENT_QUERY, EXECUTE_COMMAND_LINE, GET_COMMAND, GET_COMMAND_ARGUMENT, GET_ENVIRONMENT_VARIABLE, MOVE_ALLOC, RANDOM_INIT, RANDOM_NUMBER, RANDOM_SEED, SIGNAL, SLEEP, SYSTEM, SYSTEM_CLOCK |
761761
| Atomic intrinsic subroutines | ATOMIC_ADD |
762762
| Collective intrinsic subroutines | CO_REDUCE |
763763
| Library subroutines | FDATE, GETLOG |

flang/include/flang/Optimizer/Builder/IntrinsicCall.h

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -343,6 +343,7 @@ struct IntrinsicLibrary {
343343
fir::ExtendedValue genSum(mlir::Type, llvm::ArrayRef<fir::ExtendedValue>);
344344
void genSignalSubroutine(llvm::ArrayRef<fir::ExtendedValue>);
345345
void genSleep(llvm::ArrayRef<fir::ExtendedValue>);
346+
void genSystem(mlir::ArrayRef<fir::ExtendedValue> args);
346347
void genSystemClock(llvm::ArrayRef<fir::ExtendedValue>);
347348
mlir::Value genTand(mlir::Type, llvm::ArrayRef<mlir::Value>);
348349
mlir::Value genTrailz(mlir::Type, llvm::ArrayRef<mlir::Value>);

flang/lib/Evaluate/intrinsics.cpp

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1396,6 +1396,11 @@ static const IntrinsicInterface intrinsicSubroutine[]{
13961396
{"get", DefaultInt, Rank::vector, Optionality::optional,
13971397
common::Intent::Out}},
13981398
{}, Rank::elemental, IntrinsicClass::impureSubroutine},
1399+
{"system",
1400+
{{"command", DefaultChar, Rank::scalar},
1401+
{"exitstat", DefaultInt, Rank::scalar, Optionality::optional,
1402+
common::Intent::Out}},
1403+
{}, Rank::elemental, IntrinsicClass::impureSubroutine},
13991404
{"system_clock",
14001405
{{"count", AnyInt, Rank::scalar, Optionality::optional,
14011406
common::Intent::Out},

flang/lib/Optimizer/Builder/IntrinsicCall.cpp

Lines changed: 36 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -578,6 +578,10 @@ static constexpr IntrinsicHandler handlers[]{
578578
{"dim", asValue},
579579
{"mask", asBox, handleDynamicOptional}}},
580580
/*isElemental=*/false},
581+
{"system",
582+
&I::genSystem,
583+
{{{"command", asBox}, {"exitstat", asBox, handleDynamicOptional}}},
584+
/*isElemental=*/false},
581585
{"system_clock",
582586
&I::genSystemClock,
583587
{{{"count", asAddr}, {"count_rate", asAddr}, {"count_max", asAddr}}},
@@ -5966,6 +5970,38 @@ IntrinsicLibrary::genSum(mlir::Type resultType,
59665970
resultType, args);
59675971
}
59685972

5973+
// SYSTEM
5974+
void IntrinsicLibrary::genSystem(llvm::ArrayRef<fir::ExtendedValue> args) {
5975+
assert(args.size() == 2);
5976+
mlir::Value command = fir::getBase(args[0]);
5977+
const fir::ExtendedValue &exitstat = args[1];
5978+
assert(command && "expected COMMAND parameter");
5979+
5980+
mlir::Type boxNoneTy = fir::BoxType::get(builder.getNoneType());
5981+
5982+
mlir::Value waitBool = builder.createBool(loc, true);
5983+
mlir::Value exitstatBox =
5984+
isStaticallyPresent(exitstat)
5985+
? fir::getBase(exitstat)
5986+
: builder.create<fir::AbsentOp>(loc, boxNoneTy).getResult();
5987+
5988+
// Create a dummmy cmdstat to prevent EXECUTE_COMMAND_LINE terminate itself
5989+
// when cmdstat is assigned with a non-zero value but not present
5990+
mlir::Value tempValue =
5991+
builder.createIntegerConstant(loc, builder.getI2Type(), 0);
5992+
mlir::Value temp = builder.createTemporary(loc, builder.getI16Type());
5993+
mlir::Value castVal =
5994+
builder.createConvert(loc, builder.getI16Type(), tempValue);
5995+
builder.create<fir::StoreOp>(loc, castVal, temp);
5996+
mlir::Value cmdstatBox = builder.createBox(loc, temp);
5997+
5998+
mlir::Value cmdmsgBox =
5999+
builder.create<fir::AbsentOp>(loc, boxNoneTy).getResult();
6000+
6001+
fir::runtime::genExecuteCommandLine(builder, loc, command, waitBool,
6002+
exitstatBox, cmdstatBox, cmdmsgBox);
6003+
}
6004+
59696005
// SYSTEM_CLOCK
59706006
void IntrinsicLibrary::genSystemClock(llvm::ArrayRef<fir::ExtendedValue> args) {
59716007
assert(args.size() == 3);
Lines changed: 34 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,34 @@
1+
! RUN: bbc -emit-hlfir %s -o - | FileCheck %s
2+
3+
! CHECK-LABEL: func.func @_QPall_args(
4+
! CHECK-SAME: %[[commandArg:.*]]: !fir.boxchar<1> {fir.bindc_name = "command", fir.optional},
5+
! CHECK-SAME: %[[exitstatArg:.*]]: !fir.ref<i32> {fir.bindc_name = "exitstat", fir.optional}) {
6+
subroutine all_args(command, exitstat)
7+
CHARACTER(*), OPTIONAL :: command
8+
INTEGER, OPTIONAL :: exitstat
9+
call system(command, exitstat)
10+
11+
! CHECK-NEXT: %[[cmdstatVal:.*]] = fir.alloca i16
12+
! CHECK-NEXT: %[[commandUnbox:.*]]:2 = fir.unboxchar %[[commandArg]] : (!fir.boxchar<1>) -> (!fir.ref<!fir.char<1,?>>, index)
13+
! CHECK-NEXT: %[[commandDeclare:.*]]:2 = hlfir.declare %[[commandUnbox]]#0 typeparams %[[commandUnbox]]#1 {fortran_attrs = #fir.var_attrs<optional>, uniq_name = "_QFall_argsEcommand"} : (!fir.ref<!fir.char<1,?>>, index) -> (!fir.boxchar<1>, !fir.ref<!fir.char<1,?>>)
14+
! CHECK-NEXT: %[[exitstatDeclare:.*]]:2 = hlfir.declare %[[exitstatArg]] {fortran_attrs = #fir.var_attrs<optional>, uniq_name = "_QFall_argsEexitstat"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
15+
! CHECK-NEXT: %[[exitstatIsPresent:.*]] = fir.is_present %[[exitstatDeclare]]#0 : (!fir.ref<i32>) -> i1
16+
! CHECK-NEXT: %[[commandBox:.*]] = fir.embox %[[commandDeclare]]#1 typeparams %[[commandUnbox]]#1 : (!fir.ref<!fir.char<1,?>>, index) -> !fir.box<!fir.char<1,?>>
17+
! CHECK-NEXT: %[[exitstatBox:.*]] = fir.embox %[[exitstatDeclare]]#1 : (!fir.ref<i32>) -> !fir.box<i32>
18+
! CHECK-NEXT: %[[absentIntBox:.*]] = fir.absent !fir.box<i32>
19+
! CHECK-NEXT: %[[exitstatRealBox:.*]] = arith.select %[[exitstatIsPresent]], %[[exitstatBox]], %[[absentIntBox]] : !fir.box<i32>
20+
! CHECK-NEXT: %[[true:.*]] = arith.constant true
21+
! CHECK-NEXT: %[[c0_i2:.*]] = arith.constant 0 : i2
22+
! CHECK-NEXT: %[[c0_i16:.*]] = fir.convert %[[c0_i2]] : (i2) -> i16
23+
! CHECK-NEXT: fir.store %[[c0_i16]] to %[[cmdstatVal]] : !fir.ref<i16>
24+
! CHECK-NEXT: %[[cmdstatBox:.*]] = fir.embox %[[cmdstatVal]] : (!fir.ref<i16>) -> !fir.box<i16>
25+
! CHECK-NEXT: %[[absentBox:.*]] = fir.absent !fir.box<none>
26+
! CHECK: %[[c9_i32:.*]] = arith.constant 9 : i32
27+
! CHECK-NEXT: %[[command:.*]] = fir.convert %[[commandBox]] : (!fir.box<!fir.char<1,?>>) -> !fir.box<none>
28+
! CHECK-NEXT: %[[exitstat:.*]] = fir.convert %[[exitstatRealBox]] : (!fir.box<i32>) -> !fir.box<none>
29+
! CHECK-NEXT: %[[cmdstat:.*]] = fir.convert %[[cmdstatBox]] : (!fir.box<i16>) -> !fir.box<none>
30+
! CHECK: %[[VAL_16:.*]] = fir.call @_FortranAExecuteCommandLine(%[[command]], %[[true]], %[[exitstat]], %[[cmdstat]], %[[absentBox]], %[[VAL_15:.*]], %[[c9_i32]]) fastmath<contract> : (!fir.box<none>, i1, !fir.box<none>, !fir.box<none>, !fir.box<none>, !fir.ref<i8>, i32) -> none
31+
! CHECK-NEXT: return
32+
! CHECK-NEXT: }
33+
34+
end subroutine all_args
Lines changed: 53 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,53 @@
1+
! RUN: bbc -emit-hlfir %s -o - | FileCheck %s
2+
3+
! CHECK-LABEL: func.func @_QPall_args(
4+
! CHECK-SAME: %[[commandArg:.*]]: !fir.boxchar<1> {fir.bindc_name = "command"},
5+
! CHECK-SAME: %[[exitstatArg:.*]]: !fir.ref<i32> {fir.bindc_name = "exitstat"}) {
6+
subroutine all_args(command, exitstat)
7+
CHARACTER(*) :: command
8+
INTEGER :: exitstat
9+
call system(command, exitstat)
10+
! CHECK-NEXT: %[[cmdstatVal:.*]] = fir.alloca i16
11+
! CHECK-NEXT: %[[commandUnbox:.*]]:2 = fir.unboxchar %[[commandArg]] : (!fir.boxchar<1>) -> (!fir.ref<!fir.char<1,?>>, index)
12+
! CHECK-NEXT: %[[commandDeclare:.*]]:2 = hlfir.declare %[[commandUnbox]]#0 typeparams %[[commandUnbox]]#1 {uniq_name = "_QFall_argsEcommand"} : (!fir.ref<!fir.char<1,?>>, index) -> (!fir.boxchar<1>, !fir.ref<!fir.char<1,?>>)
13+
! CHECK-NEXT: %[[exitstatDeclare:.*]]:2 = hlfir.declare %[[exitstatArg]] {uniq_name = "_QFall_argsEexitstat"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
14+
! CHECK-NEXT: %[[commandBox:.*]] = fir.embox %[[commandDeclare]]#1 typeparams %[[commandUnbox]]#1 : (!fir.ref<!fir.char<1,?>>, index) -> !fir.box<!fir.char<1,?>>
15+
! CHECK-NEXT: %[[exitstatBox:.*]] = fir.embox %[[exitstatDeclare]]#1 : (!fir.ref<i32>) -> !fir.box<i32>
16+
! CHECK-NEXT: %[[true:.*]] = arith.constant true
17+
! CHECK-NEXT: %[[c0_i2:.*]] = arith.constant 0 : i2
18+
! CHECK-NEXT: %[[c0_i16:.*]] = fir.convert %[[c0_i2]] : (i2) -> i16
19+
! CHECK-NEXT: fir.store %[[c0_i16]] to %[[cmdstatVal]] : !fir.ref<i16>
20+
! CHECK-NEXT: %[[cmdstatBox:.*]] = fir.embox %[[cmdstatVal]] : (!fir.ref<i16>) -> !fir.box<i16>
21+
! CHECK-NEXT: %[[absentBox:.*]] = fir.absent !fir.box<none>
22+
! CHECK: %[[c9_i32:.*]] = arith.constant 9 : i32
23+
! CHECK-NEXT: %[[command:.*]] = fir.convert %[[commandBox]] : (!fir.box<!fir.char<1,?>>) -> !fir.box<none>
24+
! CHECK-NEXT: %[[exitstat:.*]] = fir.convert %[[exitstatBox]] : (!fir.box<i32>) -> !fir.box<none>
25+
! CHECK-NEXT: %[[cmdstat:.*]] = fir.convert %[[cmdstatBox]] : (!fir.box<i16>) -> !fir.box<none>
26+
! CHECK: %[[VAL_13:.*]] = fir.call @_FortranAExecuteCommandLine(%[[command]], %[[true]], %[[exitstat]], %[[cmdstat]], %[[absentBox]], %[[VAL_12:.*]], %[[c9_i32]]) fastmath<contract> : (!fir.box<none>, i1, !fir.box<none>, !fir.box<none>, !fir.box<none>, !fir.ref<i8>, i32) -> none
27+
! CHECK-NEXT: return
28+
! CHECK-NEXT: }
29+
end subroutine all_args
30+
31+
! CHECK-LABEL: func.func @_QPonly_command(
32+
! CHECK-SAME: %[[commandArg:.*]]: !fir.boxchar<1> {fir.bindc_name = "command"}) {
33+
subroutine only_command(command)
34+
CHARACTER(*) :: command
35+
call system(command)
36+
! CHECK-NEXT: %[[cmdstatVal:.*]] = fir.alloca i16
37+
! CHECK-NEXT: %[[commandUnbox:.*]]:2 = fir.unboxchar %arg0 : (!fir.boxchar<1>) -> (!fir.ref<!fir.char<1,?>>, index)
38+
! CHECK-NEXT: %[[commandDeclare:.*]]:2 = hlfir.declare %[[commandUnbox]]#0 typeparams %[[commandUnbox]]#1 {uniq_name = "_QFonly_commandEcommand"} : (!fir.ref<!fir.char<1,?>>, index) -> (!fir.boxchar<1>, !fir.ref<!fir.char<1,?>>)
39+
! CHECK-NEXT: %[[commandBox:.*]] = fir.embox %[[commandDeclare]]#1 typeparams %[[commandUnbox]]#1 : (!fir.ref<!fir.char<1,?>>, index) -> !fir.box<!fir.char<1,?>>
40+
! CHECK-NEXT: %[[true:.*]] = arith.constant true
41+
! CHECK-NEXT: %[[absentBox:.*]] = fir.absent !fir.box<none>
42+
! CHECK-NEXT: %[[c0_i2:.*]] = arith.constant 0 : i2
43+
! CHECK-NEXT: %[[c0_i16:.*]] = fir.convert %[[c0_i2]] : (i2) -> i16
44+
! CHECK-NEXT: fir.store %[[c0_i16]] to %[[cmdstatVal]] : !fir.ref<i16>
45+
! CHECK-NEXT: %[[cmdstatBox:.*]] = fir.embox %[[cmdstatVal]] : (!fir.ref<i16>) -> !fir.box<i16>
46+
! CHECK-NEXT: %[[absentBox2:.*]] = fir.absent !fir.box<none>
47+
! CHECK: %[[c35_i32:.*]] = arith.constant 35 : i32
48+
! CHECK-NEXT: %[[command:.*]] = fir.convert %[[commandBox]] : (!fir.box<!fir.char<1,?>>) -> !fir.box<none>
49+
! CHECK-NEXT: %[[cmdstat:.*]] = fir.convert %[[cmdstatBox]] : (!fir.box<i16>) -> !fir.box<none>
50+
! CHECK: %[[VAL_12:.*]] = fir.call @_FortranAExecuteCommandLine(%[[command]], %[[true]], %[[absentBox]], %[[cmdstat]], %[[absentBox2]], %[[VAL_11:.*]], %[[c35_i32]]) fastmath<contract> : (!fir.box<none>, i1, !fir.box<none>, !fir.box<none>, !fir.box<none>, !fir.ref<i8>, i32) -> none
51+
! CHECK-NEXT: return
52+
! CHECK-NEXT: }
53+
end subroutine only_command

flang/unittests/Runtime/CommandTest.cpp

Lines changed: 54 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -422,6 +422,60 @@ TEST_F(ZeroArguments, ECLInvalidCommandAsyncDontAffectAsync) {
422422
*command.get(), false, nullptr, nullptr, nullptr));
423423
}
424424

425+
TEST_F(ZeroArguments, SystemValidCommandExitStat) {
426+
// envrionment setup for SYSTEM from EXECUTE_COMMAND_LINE runtime
427+
OwningPtr<Descriptor> cmdStat{IntDescriptor(202)};
428+
bool wait{true};
429+
// setup finished
430+
431+
OwningPtr<Descriptor> command{CharDescriptor("echo hi")};
432+
OwningPtr<Descriptor> exitStat{EmptyIntDescriptor()};
433+
434+
RTNAME(ExecuteCommandLine)
435+
(*command.get(), wait, exitStat.get(), cmdStat.get(), nullptr);
436+
CheckDescriptorEqInt<std::int64_t>(exitStat.get(), 0);
437+
}
438+
439+
TEST_F(ZeroArguments, SystemInvalidCommandExitStat) {
440+
// envrionment setup for SYSTEM from EXECUTE_COMMAND_LINE runtime
441+
OwningPtr<Descriptor> cmdStat{IntDescriptor(202)};
442+
bool wait{true};
443+
// setup finished
444+
445+
OwningPtr<Descriptor> command{CharDescriptor("InvalidCommand")};
446+
OwningPtr<Descriptor> exitStat{EmptyIntDescriptor()};
447+
448+
RTNAME(ExecuteCommandLine)
449+
(*command.get(), wait, exitStat.get(), cmdStat.get(), nullptr);
450+
#ifdef _WIN32
451+
CheckDescriptorEqInt<std::int64_t>(exitStat.get(), 1);
452+
#else
453+
CheckDescriptorEqInt<std::int64_t>(exitStat.get(), 127);
454+
#endif
455+
}
456+
457+
TEST_F(ZeroArguments, SystemValidCommandOptionalExitStat) {
458+
// envrionment setup for SYSTEM from EXECUTE_COMMAND_LINE runtime
459+
OwningPtr<Descriptor> cmdStat{IntDescriptor(202)};
460+
bool wait{true};
461+
// setup finished
462+
463+
OwningPtr<Descriptor> command{CharDescriptor("echo hi")};
464+
EXPECT_NO_FATAL_FAILURE(RTNAME(ExecuteCommandLine)(
465+
*command.get(), wait, nullptr, cmdStat.get(), nullptr));
466+
}
467+
468+
TEST_F(ZeroArguments, SystemInvalidCommandOptionalExitStat) {
469+
// envrionment setup for SYSTEM from EXECUTE_COMMAND_LINE runtime
470+
OwningPtr<Descriptor> cmdStat{IntDescriptor(202)};
471+
bool wait{true};
472+
// setup finished
473+
474+
OwningPtr<Descriptor> command{CharDescriptor("InvalidCommand")};
475+
EXPECT_NO_FATAL_FAILURE(RTNAME(ExecuteCommandLine)(
476+
*command.get(), wait, nullptr, cmdStat.get(), nullptr););
477+
}
478+
425479
static const char *oneArgArgv[]{"aProgram", "anArgumentOfLength20"};
426480
class OneArgument : public CommandFixture {
427481
protected:

0 commit comments

Comments
 (0)