--- /dev/null
+MODULE m
+ IMPLICIT NONE
+
+ TYPE :: t
+ CHARACTER :: c
+ CONTAINS
+ PROCEDURE :: write_formatted
+ GENERIC :: WRITE(FORMATTED) => write_formatted
+ END TYPE t
+CONTAINS
+ SUBROUTINE write_formatted(dtv, unit, iotype, v_list, iostat, iomsg)
+ CLASS(t), INTENT(IN) :: dtv
+ INTEGER, INTENT(IN) :: unit
+ CHARACTER(*), INTENT(IN) :: iotype
+ INTEGER, INTENT(IN) :: v_list(:)
+ INTEGER, INTENT(OUT) :: iostat
+ CHARACTER(*), INTENT(INOUT) :: iomsg
+
+ WRITE (unit, "(A)", IOSTAT=iostat, IOMSG=iomsg) iotype
+ END SUBROUTINE write_formatted
+END MODULE m
+
+PROGRAM p
+ USE m
+ IMPLICIT NONE
+ CHARACTER(25) :: str
+
+ TYPE(t) :: x
+ WRITE (str, "(DT'a''b')") x
+ if (str.ne."DTa'b") call abort
+END PROGRAM p
+2016-12-16 Jerry DeLisle <jvdelisle@gcc.gnu.org>
+
+ PR fortran/78622
+ * io/transfer.c (get_dt_format): New static function to alloc
+ and set the DT iotype string, handling doubled quotes.
+ (formatted_transfer_scalar_read,
+ formatted_transfer_scalar_write): Use new function.
+
2016-12-12 Rainer Orth <ro@CeBiTec.Uni-Bielefeld.DE>
* configure.ac: Call GCC_CHECK_LINKER_HWCAP.
return 1;
}
+static char *
+get_dt_format (char *p, gfc_charlen_type *length)
+{
+ char delim = p[-1]; /* The delimiter is always the first character back. */
+ char c, *q, *res;
+ gfc_charlen_type len = *length; /* This length already correct, less 'DT'. */
+
+ res = q = xmalloc (len + 2);
+
+ /* Set the beginning of the string to 'DT', length adjusted below. */
+ *q++ = 'D';
+ *q++ = 'T';
+
+ /* The string may contain doubled quotes so scan and skip as needed. */
+ for (; len > 0; len--)
+ {
+ c = *q++ = *p++;
+ if (c == delim)
+ p++; /* Skip the doubled delimiter. */
+ }
+
+ /* Adjust the string length by two now that we are done. */
+ *length += 2;
+
+ return res;
+}
+
/* This function is in the main loop for a formatted data transfer
statement. It would be natural to implement this as a coroutine
gfc_charlen_type child_iomsg_len;
int noiostat;
int *child_iostat = NULL;
- char *iotype = f->u.udf.string;
+ char *iotype;
gfc_charlen_type iotype_len = f->u.udf.string_len;
/* Build the iotype string. */
iotype = dt;
}
else
- {
- iotype_len += 2;
- iotype = xmalloc (iotype_len);
- iotype[0] = dt[0];
- iotype[1] = dt[1];
- memcpy (iotype + 2, f->u.udf.string, f->u.udf.string_len);
- }
+ iotype = get_dt_format (f->u.udf.string, &iotype_len);
/* Set iostat, intent(out). */
noiostat = 0;
gfc_charlen_type child_iomsg_len;
int noiostat;
int *child_iostat = NULL;
- char *iotype = f->u.udf.string;
+ char *iotype;
gfc_charlen_type iotype_len = f->u.udf.string_len;
/* Build the iotype string. */
iotype = dt;
}
else
- {
- iotype_len += 2;
- iotype = xmalloc (iotype_len);
- iotype[0] = dt[0];
- iotype[1] = dt[1];
- memcpy (iotype + 2, f->u.udf.string, f->u.udf.string_len);
- }
+ iotype = get_dt_format (f->u.udf.string, &iotype_len);
/* Set iostat, intent(out). */
noiostat = 0;