diff --git a/gcc/testsuite/gfortran.dg/pr105456.f90 b/gcc/testsuite/gfortran.dg/pr105456.f90
index 188323847a7aeb71c66b5a99387d234d3e7f50b0..60cd3b6f3e86bd022e2cc3829f1fd9a6fa0e53f2 100644
--- a/gcc/testsuite/gfortran.dg/pr105456.f90
+++ b/gcc/testsuite/gfortran.dg/pr105456.f90
@@ -19,7 +19,7 @@ contains
     character :: ch
     read (unit,fmt='(A1)', advance="no", iostat=piostat, iomsg=piomsg) ch
     piostat = 42
-    piomsg="The users message"
+    piomsg="The users message containing % and %% and %s and other stuff"
     dtv%ch = ch
   end subroutine read_formatted
 end module sk1
@@ -35,4 +35,4 @@ program skip1
   write (*,'(10(A))') "Read: '",x%ch,"'"
 end program skip1
 ! { dg-output ".*(unit = 10, file = .*)" }
-! { dg-output "Fortran runtime error: The users message" }
+! { dg-output "Fortran runtime error: The users message containing % and %% and %s and other stuff" }
diff --git a/libgfortran/io/list_read.c b/libgfortran/io/list_read.c
index 707afaeb8dcb994b997165f1363ce98b339f5aa9..e38e9a84976545e799bc677ef3fc49ef6f6d6832 100644
--- a/libgfortran/io/list_read.c
+++ b/libgfortran/io/list_read.c
@@ -2268,9 +2268,10 @@ list_formatted_read_scalar (st_parameter_dt *dtp, bt type, void *p,
 	      !(dtp->common.flags & IOPARM_HAS_IOSTAT))
 	    {
 	      char message[IOMSG_LEN + 1];
-	      child_iomsg_len = string_len_trim (IOMSG_LEN, child_iomsg) + 1;
+	      child_iomsg_len = string_len_trim (IOMSG_LEN, child_iomsg);
 	      free_line (dtp);
-	      snprintf (message, child_iomsg_len, child_iomsg);
+	      fstrcpy (message, child_iomsg_len, child_iomsg, child_iomsg_len);
+	      message[child_iomsg_len] = '\0';
 	      generate_error (&dtp->common, dtp->u.p.child_saved_iostat,
 			      message);
 	    }
@@ -3082,8 +3083,9 @@ nml_read_obj (st_parameter_dt *dtp, namelist_info *nl, index_type offset,
 		    !(dtp->common.flags & IOPARM_HAS_IOSTAT))
 		  {
 		    char message[IOMSG_LEN + 1];
-		    child_iomsg_len = string_len_trim (IOMSG_LEN, child_iomsg) + 1;
-		    snprintf (message, child_iomsg_len, child_iomsg);
+		    child_iomsg_len = string_len_trim (IOMSG_LEN, child_iomsg);
+		    fstrcpy (message, child_iomsg_len, child_iomsg, child_iomsg_len);
+		    message[child_iomsg_len] = '\0';
 		    generate_error (&dtp->common, dtp->u.p.child_saved_iostat,
 				    message);
 		    goto nml_err_ret;
diff --git a/libgfortran/io/transfer.c b/libgfortran/io/transfer.c
index 9523a14c4bf0122fb4b90d60a10b1114d0f43ae0..a86099d46f5645dd2f4068412536ef22156d5b5d 100644
--- a/libgfortran/io/transfer.c
+++ b/libgfortran/io/transfer.c
@@ -1128,8 +1128,9 @@ unformatted_read (st_parameter_dt *dtp, bt type,
 	      !(dtp->common.flags & IOPARM_HAS_IOSTAT))
 	    {
 	      char message[IOMSG_LEN + 1];
-	      child_iomsg_len = string_len_trim (IOMSG_LEN, child_iomsg) + 1;
-	      snprintf (message, child_iomsg_len, child_iomsg);
+	      child_iomsg_len = string_len_trim (IOMSG_LEN, child_iomsg);
+	      fstrcpy (message, child_iomsg_len, child_iomsg, child_iomsg_len);
+	      message[child_iomsg_len] = '\0';
 	      generate_error (&dtp->common, dtp->u.p.child_saved_iostat,
 			      message);
 	    }
@@ -1271,8 +1272,9 @@ unformatted_write (st_parameter_dt *dtp, bt type,
 	      !(dtp->common.flags & IOPARM_HAS_IOSTAT))
 	    {
 	      char message[IOMSG_LEN + 1];
-	      child_iomsg_len = string_len_trim (IOMSG_LEN, child_iomsg) + 1;
-	      snprintf (message, child_iomsg_len, child_iomsg);
+	      child_iomsg_len = string_len_trim (IOMSG_LEN, child_iomsg);
+	      fstrcpy (message, child_iomsg_len, child_iomsg, child_iomsg_len);
+	      message[child_iomsg_len] = '\0';
 	      generate_error (&dtp->common, dtp->u.p.child_saved_iostat,
 			      message);
 	    }
@@ -1763,8 +1765,9 @@ formatted_transfer_scalar_read (st_parameter_dt *dtp, bt type, void *p, int kind
 	      !(dtp->common.flags & IOPARM_HAS_IOSTAT))
 	    {
 	      char message[IOMSG_LEN + 1];
-	      child_iomsg_len = string_len_trim (IOMSG_LEN, child_iomsg) + 1;
-	      snprintf (message, child_iomsg_len, child_iomsg);
+	      child_iomsg_len = string_len_trim (IOMSG_LEN, child_iomsg);
+	      fstrcpy (message, child_iomsg_len, child_iomsg, child_iomsg_len);
+	      message[child_iomsg_len] = '\0';
 	      generate_error (&dtp->common, dtp->u.p.child_saved_iostat,
 			      message);
 	    }
@@ -2259,8 +2262,9 @@ formatted_transfer_scalar_write (st_parameter_dt *dtp, bt type, void *p, int kin
 	      !(dtp->common.flags & IOPARM_HAS_IOSTAT))
 	    {
 	      char message[IOMSG_LEN + 1];
-	      child_iomsg_len = string_len_trim (IOMSG_LEN, child_iomsg) + 1;
-	      snprintf (message, child_iomsg_len, child_iomsg);
+	      child_iomsg_len = string_len_trim (IOMSG_LEN, child_iomsg);
+	      fstrcpy (message, child_iomsg_len, child_iomsg, child_iomsg_len);
+	      message[child_iomsg_len] = '\0';
 	      generate_error (&dtp->common, dtp->u.p.child_saved_iostat,
 			      message);
 	    }
diff --git a/libgfortran/io/write.c b/libgfortran/io/write.c
index cdcaf8decb66e171298d9e85a3f6e6e82c9535e1..91d1da2007ae57991b161c42dbee6f16f959f5bf 100644
--- a/libgfortran/io/write.c
+++ b/libgfortran/io/write.c
@@ -1999,8 +1999,9 @@ list_formatted_write_scalar (st_parameter_dt *dtp, bt type, void *p, int kind,
 	      !(dtp->common.flags & IOPARM_HAS_IOSTAT))
 	    {
 	      char message[IOMSG_LEN + 1];
-	      child_iomsg_len = string_len_trim (IOMSG_LEN, child_iomsg) + 1;
-	      snprintf (message, child_iomsg_len, child_iomsg);
+	      child_iomsg_len = string_len_trim (IOMSG_LEN, child_iomsg);
+	      fstrcpy (message, child_iomsg_len, child_iomsg, child_iomsg_len);
+	      message[child_iomsg_len] = '\0';
 	      generate_error (&dtp->common, dtp->u.p.child_saved_iostat,
 			      message);
 	    }
@@ -2352,8 +2353,9 @@ nml_write_obj (st_parameter_dt *dtp, namelist_info *obj, index_type offset,
 		      char message[IOMSG_LEN + 1];
 
 		      /* Trim trailing spaces from the message.  */
-		      child_iomsg_len = string_len_trim (IOMSG_LEN, child_iomsg) + 1;
-		      snprintf (message, child_iomsg_len, child_iomsg);
+		      child_iomsg_len = string_len_trim (IOMSG_LEN, child_iomsg);
+		      fstrcpy (message, child_iomsg_len, child_iomsg, child_iomsg_len);
+		      message[child_iomsg_len] = '\0';
 		      generate_error (&dtp->common, dtp->u.p.child_saved_iostat,
 				      message);
 		    }