Skip to content

Commit 22830e6

Browse files
klauslerjeanPerier
authored andcommitted
[flang] Implement READ(SIZE=) and INQUIRE(IOLENGTH=) in runtime
Count input characters corresponding to formatted edit descriptors for READ(SIZE=); count output bytes for INQUIRE(IOLENGTH=). The I/O APIs GetSize() and GetLength() were adjusted to return std::size_t as function results. Basic unit tests were added (and others fixed). Differential Revision: https://reviews.llvm.org/D110291
1 parent a3a918a commit 22830e6

File tree

7 files changed

+107
-15
lines changed

7 files changed

+107
-15
lines changed

flang/include/flang/Runtime/io-api.h

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -283,10 +283,10 @@ bool IONAME(SetFile)(Cookie, const char *, std::size_t chars);
283283
bool IONAME(GetNewUnit)(Cookie, int &, int kind = 4);
284284

285285
// READ(SIZE=), after all input items
286-
bool IONAME(GetSize)(Cookie, std::int64_t, int kind = 8);
286+
std::size_t IONAME(GetSize)(Cookie);
287287

288288
// INQUIRE(IOLENGTH=), after all output items
289-
bool IONAME(GetIoLength)(Cookie, std::int64_t, int kind = 8);
289+
std::size_t IONAME(GetIoLength)(Cookie);
290290

291291
// GetIoMsg() does not modify its argument unless an error or
292292
// end-of-record/file condition is present.

flang/runtime/descriptor-io.h

Lines changed: 6 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -315,7 +315,9 @@ static bool UnformattedDescriptorIO(
315315
// Regular derived type unformatted I/O, not user-defined
316316
auto *externalUnf{io.get_if<ExternalUnformattedIoStatementState<DIR>>()};
317317
auto *childUnf{io.get_if<ChildUnformattedIoStatementState<DIR>>()};
318-
RUNTIME_CHECK(handler, externalUnf != nullptr || childUnf != nullptr);
318+
auto *inq{
319+
DIR == Direction::Output ? io.get_if<InquireIOLengthState>() : nullptr};
320+
RUNTIME_CHECK(handler, externalUnf || childUnf || inq);
319321
std::size_t elementBytes{descriptor.ElementBytes()};
320322
std::size_t numElements{descriptor.Elements()};
321323
SubscriptValue subscripts[maxRank];
@@ -326,7 +328,8 @@ static bool UnformattedDescriptorIO(
326328
std::size_t elementBytes) -> bool {
327329
if constexpr (DIR == Direction::Output) {
328330
return externalUnf ? externalUnf->Emit(&x, totalBytes, elementBytes)
329-
: childUnf->Emit(&x, totalBytes, elementBytes);
331+
: childUnf ? childUnf->Emit(&x, totalBytes, elementBytes)
332+
: inq->Emit(&x, totalBytes, elementBytes);
330333
} else {
331334
return externalUnf ? externalUnf->Receive(&x, totalBytes, elementBytes)
332335
: childUnf->Receive(&x, totalBytes, elementBytes);
@@ -363,7 +366,7 @@ static bool DescriptorIO(IoStatementState &io, const Descriptor &descriptor) {
363366
return false;
364367
}
365368
}
366-
if (!io.get_if<FormattedIoStatementState>()) {
369+
if (!io.get_if<FormattedIoStatementState<DIR>>()) {
367370
return UnformattedDescriptorIO<DIR>(io, descriptor);
368371
}
369372
IoErrorHandler &handler{io.GetIoErrorHandler()};

flang/runtime/edit-input.cpp

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -56,6 +56,7 @@ static bool ScanNumericPrefix(IoStatementState &io, const DataEdit &edit,
5656
if (next) {
5757
negative = *next == '-';
5858
if (negative || *next == '+') {
59+
io.GotChar();
5960
io.SkipSpaces(remaining);
6061
next = io.NextInField(remaining);
6162
}
@@ -453,6 +454,7 @@ bool EditDefaultCharacterInput(
453454
next = io.NextInField(remaining)) {
454455
if (skip > 0) {
455456
--skip;
457+
io.GotChar(-1);
456458
} else {
457459
*x++ = *next;
458460
--length;

flang/runtime/io-api.cpp

Lines changed: 23 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -925,6 +925,8 @@ bool IONAME(OutputUnformattedBlock)(Cookie cookie, const char *x,
925925
if (auto *unf{io.get_if<
926926
ExternalUnformattedIoStatementState<Direction::Output>>()}) {
927927
return unf->Emit(x, length, elementBytes);
928+
} else if (auto *inq{io.get_if<InquireIOLengthState>()}) {
929+
return inq->Emit(x, length, elementBytes);
928930
}
929931
io.GetIoErrorHandler().Crash("OutputUnformattedBlock() called for an I/O "
930932
"statement that is not unformatted output");
@@ -1080,6 +1082,27 @@ bool IONAME(InputLogical)(Cookie cookie, bool &truth) {
10801082
return descr::DescriptorIO<Direction::Input>(*cookie, descriptor);
10811083
}
10821084

1085+
std::size_t IONAME(GetSize)(Cookie cookie) {
1086+
IoStatementState &io{*cookie};
1087+
if (const auto *formatted{
1088+
io.get_if<FormattedIoStatementState<Direction::Input>>()}) {
1089+
return formatted->GetEditDescriptorChars();
1090+
}
1091+
io.GetIoErrorHandler().Crash(
1092+
"GetIoSize() called for an I/O statement that is not a formatted READ()");
1093+
return 0;
1094+
}
1095+
1096+
std::size_t IONAME(GetIoLength)(Cookie cookie) {
1097+
IoStatementState &io{*cookie};
1098+
if (const auto *inq{io.get_if<InquireIOLengthState>()}) {
1099+
return inq->bytes();
1100+
}
1101+
io.GetIoErrorHandler().Crash("GetIoLength() called for an I/O statement that "
1102+
"is not INQUIRE(IOLENGTH=)");
1103+
return 0;
1104+
}
1105+
10831106
void IONAME(GetIoMsg)(Cookie cookie, char *msg, std::size_t length) {
10841107
IoErrorHandler &handler{cookie->GetIoErrorHandler()};
10851108
if (handler.InError()) { // leave "msg" alone when no error

flang/runtime/io-stmt.cpp

Lines changed: 42 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -521,6 +521,7 @@ std::optional<char32_t> IoStatementState::SkipSpaces(
521521
}
522522
HandleRelativePosition(1);
523523
if (remaining) {
524+
GotChar();
524525
--*remaining;
525526
}
526527
} else {
@@ -556,6 +557,7 @@ std::optional<char32_t> IoStatementState::NextInField(
556557
if (auto next{GetCurrentChar()}) {
557558
--*remaining;
558559
HandleRelativePosition(1);
560+
GotChar();
559561
return next;
560562
}
561563
const ConnectionState &connection{GetConnectionState()};
@@ -610,6 +612,25 @@ bool IoStatementState::Inquire(InquiryKeywordHash inquiry, std::int64_t &n) {
610612
return std::visit([&](auto &x) { return x.get().Inquire(inquiry, n); }, u_);
611613
}
612614

615+
void IoStatementState::GotChar(int n) {
616+
if (auto *formattedIn{
617+
get_if<FormattedIoStatementState<Direction::Input>>()}) {
618+
formattedIn->GotChar(n);
619+
} else {
620+
GetIoErrorHandler().Crash("IoStatementState::GotChar() called for "
621+
"statement that is not formatted input");
622+
}
623+
}
624+
625+
std::size_t
626+
FormattedIoStatementState<Direction::Input>::GetEditDescriptorChars() const {
627+
return chars_;
628+
}
629+
630+
void FormattedIoStatementState<Direction::Input>::GotChar(int n) {
631+
chars_ += n;
632+
}
633+
613634
bool ListDirectedStatementState<Direction::Output>::EmitLeadingSpaceOrAdvance(
614635
IoStatementState &io, std::size_t length, bool isCharacter) {
615636
if (length == 0) {
@@ -1325,4 +1346,25 @@ InquireIOLengthState::InquireIOLengthState(
13251346
const char *sourceFile, int sourceLine)
13261347
: NoUnitIoStatementState{sourceFile, sourceLine, *this} {}
13271348

1349+
bool InquireIOLengthState::Emit(
1350+
const char *, std::size_t n, std::size_t elementBytes) {
1351+
bytes_ += n * elementBytes;
1352+
return true;
1353+
}
1354+
1355+
bool InquireIOLengthState::Emit(const char *p, std::size_t n) {
1356+
bytes_ += sizeof *p * n;
1357+
return true;
1358+
}
1359+
1360+
bool InquireIOLengthState::Emit(const char16_t *p, std::size_t n) {
1361+
bytes_ += sizeof *p * n;
1362+
return true;
1363+
}
1364+
1365+
bool InquireIOLengthState::Emit(const char32_t *p, std::size_t n) {
1366+
bytes_ += sizeof *p * n;
1367+
return true;
1368+
}
1369+
13281370
} // namespace Fortran::runtime::io

flang/runtime/io-stmt.h

Lines changed: 26 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -52,7 +52,19 @@ struct OutputStatementState {};
5252
template <Direction D>
5353
using IoDirectionState = std::conditional_t<D == Direction::Input,
5454
InputStatementState, OutputStatementState>;
55-
struct FormattedIoStatementState {};
55+
56+
// Common state for all kinds of formatted I/O
57+
template <Direction D> class FormattedIoStatementState {};
58+
template <> class FormattedIoStatementState<Direction::Input> {
59+
public:
60+
std::size_t GetEditDescriptorChars() const;
61+
void GotChar(int);
62+
63+
private:
64+
// Account of characters read for edit descriptors (i.e., formatted I/O
65+
// with a FORMAT, not list-directed or NAMELIST), not including padding.
66+
std::size_t chars_{0}; // for READ(SIZE=)
67+
};
5668

5769
// The Cookie type in the I/O API is a pointer (for C) to this class.
5870
class IoStatementState {
@@ -83,6 +95,7 @@ class IoStatementState {
8395
bool Inquire(InquiryKeywordHash, bool &);
8496
bool Inquire(InquiryKeywordHash, std::int64_t, bool &); // PENDING=
8597
bool Inquire(InquiryKeywordHash, std::int64_t &);
98+
void GotChar(signed int = 1); // for READ(SIZE=); can be <0
8699

87100
MutableModes &mutableModes();
88101
ConnectionState &GetConnectionState();
@@ -115,8 +128,7 @@ class IoStatementState {
115128
std::optional<char32_t> GetNextNonBlank();
116129

117130
template <Direction D> void CheckFormattedStmtType(const char *name) {
118-
if (!get_if<FormattedIoStatementState>() ||
119-
!get_if<IoDirectionState<D>>()) {
131+
if (!get_if<FormattedIoStatementState<D>>()) {
120132
GetIoErrorHandler().Crash(
121133
"%s called for I/O statement that is not formatted %s", name,
122134
D == Direction::Output ? "output" : "input");
@@ -191,7 +203,7 @@ struct IoStatementBase : public IoErrorHandler {
191203
template <Direction> class ListDirectedStatementState;
192204
template <>
193205
class ListDirectedStatementState<Direction::Output>
194-
: public FormattedIoStatementState {
206+
: public FormattedIoStatementState<Direction::Output> {
195207
public:
196208
bool EmitLeadingSpaceOrAdvance(
197209
IoStatementState &, std::size_t = 1, bool isCharacter = false);
@@ -209,7 +221,7 @@ class ListDirectedStatementState<Direction::Output>
209221
};
210222
template <>
211223
class ListDirectedStatementState<Direction::Input>
212-
: public FormattedIoStatementState {
224+
: public FormattedIoStatementState<Direction::Input> {
213225
public:
214226
// Skips value separators, handles repetition and null values.
215227
// Vacant when '/' appears; present with descriptor == ListDirectedNullValue
@@ -269,7 +281,7 @@ class InternalIoStatementState : public IoStatementBase,
269281
template <Direction DIR, typename CHAR>
270282
class InternalFormattedIoStatementState
271283
: public InternalIoStatementState<DIR, CHAR>,
272-
public FormattedIoStatementState {
284+
public FormattedIoStatementState<DIR> {
273285
public:
274286
using CharType = CHAR;
275287
using typename InternalIoStatementState<DIR, CharType>::Buffer;
@@ -353,8 +365,9 @@ class ExternalIoStatementState : public ExternalIoStatementBase,
353365
};
354366

355367
template <Direction DIR, typename CHAR>
356-
class ExternalFormattedIoStatementState : public ExternalIoStatementState<DIR>,
357-
public FormattedIoStatementState {
368+
class ExternalFormattedIoStatementState
369+
: public ExternalIoStatementState<DIR>,
370+
public FormattedIoStatementState<DIR> {
358371
public:
359372
using CharType = CHAR;
360373
ExternalFormattedIoStatementState(ExternalFileUnit &, const CharType *format,
@@ -411,7 +424,7 @@ class ChildIoStatementState : public IoStatementBase,
411424

412425
template <Direction DIR, typename CHAR>
413426
class ChildFormattedIoStatementState : public ChildIoStatementState<DIR>,
414-
public FormattedIoStatementState {
427+
public FormattedIoStatementState<DIR> {
415428
public:
416429
using CharType = CHAR;
417430
ChildFormattedIoStatementState(ChildIo &, const CharType *format,
@@ -584,6 +597,10 @@ class InquireIOLengthState : public NoUnitIoStatementState,
584597
public:
585598
InquireIOLengthState(const char *sourceFile = nullptr, int sourceLine = 0);
586599
std::size_t bytes() const { return bytes_; }
600+
bool Emit(const char *, std::size_t, std::size_t elementBytes);
601+
bool Emit(const char *, std::size_t);
602+
bool Emit(const char16_t *, std::size_t chars);
603+
bool Emit(const char32_t *, std::size_t chars);
587604

588605
private:
589606
std::size_t bytes_{0};

flang/runtime/unit.cpp

Lines changed: 6 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -768,8 +768,13 @@ void ChildIo::EndIoStatement() {
768768

769769
bool ChildIo::CheckFormattingAndDirection(Terminator &terminator,
770770
const char *what, bool unformatted, Direction direction) {
771-
bool parentIsUnformatted{!parent_.get_if<FormattedIoStatementState>()};
772771
bool parentIsInput{!parent_.get_if<IoDirectionState<Direction::Output>>()};
772+
bool parentIsFormatted{parentIsInput
773+
? parent_.get_if<FormattedIoStatementState<Direction::Input>>() !=
774+
nullptr
775+
: parent_.get_if<FormattedIoStatementState<Direction::Output>>() !=
776+
nullptr};
777+
bool parentIsUnformatted{!parentIsFormatted};
773778
if (unformatted != parentIsUnformatted) {
774779
terminator.Crash("Child %s attempted on %s parent I/O unit", what,
775780
parentIsUnformatted ? "unformatted" : "formatted");

0 commit comments

Comments
 (0)