diff --git a/gcc/testsuite/gfortran.dg/bound_11.f90 b/gcc/testsuite/gfortran.dg/bound_11.f90
new file mode 100644
index 0000000000000000000000000000000000000000..170eba4ddfd4c2d963c24ebc5bb215be59abe5bd
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/bound_11.f90
@@ -0,0 +1,588 @@
+! { dg-do run }
+!
+! PR fortran/112371
+! The library used to incorrectly set an extent of zero for the first
+! dimension of the resulting array of a reduction function if that array was
+! empty.
+
+program p
+  implicit none
+  call check_iparity
+  call check_sum
+  call check_minloc_int
+  call check_minloc_char
+  call check_maxloc_char4
+  call check_minval_char
+  call check_maxval_char4
+  call check_any
+  call check_count4
+  call check_findloc_int
+  call check_findloc_char
+contains
+  subroutine check_iparity
+    integer :: a(9,3,0,7)
+    logical :: m1(9,3,0,7)
+    logical(kind=4) :: m4
+    integer :: i
+    integer, allocatable :: r(:,:,:)
+    a  = reshape((/ integer:: /), shape(a))
+    m1 = reshape((/ logical:: /), shape(m1))
+    m4 = .false.
+    i = 1
+    r = iparity(a, dim=i)
+    if (any(shape(r) /= (/ 3, 0, 7 /))) stop 111
+    if (any(ubound(r) /= (/ 3, 0, 7 /))) stop 112
+    i = 2
+    r = iparity(a, dim=i)
+    if (any(shape(r) /= (/ 9, 0, 7 /))) stop 113
+    if (any(ubound(r) /= (/ 9, 0, 7 /))) stop 114
+    i = 3
+    r = iparity(a, dim=i)
+    if (any(shape(r) /= (/ 9, 3, 7 /))) stop 115
+    if (any(ubound(r) /= (/ 9, 3, 7 /))) stop 116
+    i = 4
+    r = iparity(a, dim=i)
+    if (any(shape(r) /= (/ 9, 3, 0 /))) stop 117
+    if (any(ubound(r) /= (/ 9, 3, 0 /))) stop 118
+    i = 1
+    r = iparity(a, dim=i, mask=m1)
+    if (any(shape(r) /= (/ 3, 0, 7 /))) stop 121
+    if (any(ubound(r) /= (/ 3, 0, 7 /))) stop 122
+    i = 2
+    r = iparity(a, dim=i, mask=m1)
+    if (any(shape(r) /= (/ 9, 0, 7 /))) stop 123
+    if (any(ubound(r) /= (/ 9, 0, 7 /))) stop 124
+    i = 3
+    r = iparity(a, dim=i, mask=m1)
+    if (any(shape(r) /= (/ 9, 3, 7 /))) stop 125
+    if (any(ubound(r) /= (/ 9, 3, 7 /))) stop 126
+    i = 4
+    r = iparity(a, dim=i, mask=m1)
+    if (any(shape(r) /= (/ 9, 3, 0 /))) stop 127
+    if (any(ubound(r) /= (/ 9, 3, 0 /))) stop 128
+    i = 1
+    r = iparity(a, dim=i, mask=m4)
+    if (any(shape(r) /= (/ 3, 0, 7 /))) stop 131
+    if (any(ubound(r) /= (/ 3, 0, 7 /))) stop 132
+    i = 2
+    r = iparity(a, dim=i, mask=m4)
+    if (any(shape(r) /= (/ 9, 0, 7 /))) stop 133
+    if (any(ubound(r) /= (/ 9, 0, 7 /))) stop 134
+    i = 3
+    r = iparity(a, dim=i, mask=m4)
+    if (any(shape(r) /= (/ 9, 3, 7 /))) stop 135
+    if (any(ubound(r) /= (/ 9, 3, 7 /))) stop 136
+    i = 4
+    r = iparity(a, dim=i, mask=m4)
+    if (any(shape(r) /= (/ 9, 3, 0 /))) stop 137
+    if (any(ubound(r) /= (/ 9, 3, 0 /))) stop 138
+  end subroutine
+  subroutine check_sum
+    integer :: a(9,3,0,7)
+    logical :: m1(9,3,0,7)
+    logical(kind=4) :: m4
+    integer :: i
+    integer, allocatable :: r(:,:,:)
+    a  = reshape((/ integer:: /), shape(a))
+    m1 = reshape((/ logical:: /), shape(m1))
+    m4 = .false.
+    i = 1
+    r = sum(a, dim=i)
+    if (any(shape(r) /= (/ 3, 0, 7 /))) stop 211
+    if (any(ubound(r) /= (/ 3, 0, 7 /))) stop 212
+    i = 2
+    r = sum(a, dim=i)
+    if (any(shape(r) /= (/ 9, 0, 7 /))) stop 213
+    if (any(ubound(r) /= (/ 9, 0, 7 /))) stop 214
+    i = 3
+    r = sum(a, dim=i)
+    if (any(shape(r) /= (/ 9, 3, 7 /))) stop 215
+    if (any(ubound(r) /= (/ 9, 3, 7 /))) stop 216
+    i = 4
+    r = sum(a, dim=i)
+    if (any(shape(r) /= (/ 9, 3, 0 /))) stop 217
+    if (any(ubound(r) /= (/ 9, 3, 0 /))) stop 218
+    i = 1
+    r = sum(a, dim=i, mask=m1)
+    if (any(shape(r) /= (/ 3, 0, 7 /))) stop 221
+    if (any(ubound(r) /= (/ 3, 0, 7 /))) stop 222
+    i = 2
+    r = sum(a, dim=i, mask=m1)
+    if (any(shape(r) /= (/ 9, 0, 7 /))) stop 223
+    if (any(ubound(r) /= (/ 9, 0, 7 /))) stop 224
+    i = 3
+    r = sum(a, dim=i, mask=m1)
+    if (any(shape(r) /= (/ 9, 3, 7 /))) stop 225
+    if (any(ubound(r) /= (/ 9, 3, 7 /))) stop 226
+    i = 4
+    r = sum(a, dim=i, mask=m1)
+    if (any(shape(r) /= (/ 9, 3, 0 /))) stop 227
+    if (any(ubound(r) /= (/ 9, 3, 0 /))) stop 228
+    i = 1
+    r = sum(a, dim=i, mask=m4)
+    if (any(shape(r) /= (/ 3, 0, 7 /))) stop 231
+    if (any(ubound(r) /= (/ 3, 0, 7 /))) stop 232
+    i = 2
+    r = sum(a, dim=i, mask=m4)
+    if (any(shape(r) /= (/ 9, 0, 7 /))) stop 233
+    if (any(ubound(r) /= (/ 9, 0, 7 /))) stop 234
+    i = 3
+    r = sum(a, dim=i, mask=m4)
+    if (any(shape(r) /= (/ 9, 3, 7 /))) stop 235
+    if (any(ubound(r) /= (/ 9, 3, 7 /))) stop 236
+    i = 4
+    r = sum(a, dim=i, mask=m4)
+    if (any(shape(r) /= (/ 9, 3, 0 /))) stop 237
+    if (any(ubound(r) /= (/ 9, 3, 0 /))) stop 238
+  end subroutine
+  subroutine check_minloc_int
+    integer :: a(9,3,0,7)
+    logical :: m1(9,3,0,7)
+    logical(kind=4) :: m4
+    integer :: i
+    integer, allocatable :: r(:,:,:)
+    a  = reshape((/ integer:: /), shape(a))
+    m1 = reshape((/ logical:: /), shape(m1))
+    m4 = .false.
+    i = 1
+    r = minloc(a, dim=i)
+    if (any(shape(r) /= (/ 3, 0, 7 /))) stop 311
+    if (any(ubound(r) /= (/ 3, 0, 7 /))) stop 312
+    i = 2
+    r = minloc(a, dim=i)
+    if (any(shape(r) /= (/ 9, 0, 7 /))) stop 313
+    if (any(ubound(r) /= (/ 9, 0, 7 /))) stop 314
+    i = 3
+    r = minloc(a, dim=i)
+    if (any(shape(r) /= (/ 9, 3, 7 /))) stop 315
+    if (any(ubound(r) /= (/ 9, 3, 7 /))) stop 316
+    i = 4
+    r = minloc(a, dim=i)
+    if (any(shape(r) /= (/ 9, 3, 0 /))) stop 317
+    if (any(ubound(r) /= (/ 9, 3, 0 /))) stop 318
+    i = 1
+    r = minloc(a, dim=i, mask=m1)
+    if (any(shape(r) /= (/ 3, 0, 7 /))) stop 321
+    if (any(ubound(r) /= (/ 3, 0, 7 /))) stop 322
+    i = 2
+    r = minloc(a, dim=i, mask=m1)
+    if (any(shape(r) /= (/ 9, 0, 7 /))) stop 323
+    if (any(ubound(r) /= (/ 9, 0, 7 /))) stop 324
+    i = 3
+    r = minloc(a, dim=i, mask=m1)
+    if (any(shape(r) /= (/ 9, 3, 7 /))) stop 325
+    if (any(ubound(r) /= (/ 9, 3, 7 /))) stop 326
+    i = 4
+    r = minloc(a, dim=i, mask=m1)
+    if (any(shape(r) /= (/ 9, 3, 0 /))) stop 327
+    if (any(ubound(r) /= (/ 9, 3, 0 /))) stop 328
+    i = 1
+    r = minloc(a, dim=i, mask=m4)
+    if (any(shape(r) /= (/ 3, 0, 7 /))) stop 331
+    if (any(ubound(r) /= (/ 3, 0, 7 /))) stop 332
+    i = 2
+    r = minloc(a, dim=i, mask=m4)
+    if (any(shape(r) /= (/ 9, 0, 7 /))) stop 333
+    if (any(ubound(r) /= (/ 9, 0, 7 /))) stop 334
+    i = 3
+    r = minloc(a, dim=i, mask=m4)
+    if (any(shape(r) /= (/ 9, 3, 7 /))) stop 335
+    if (any(ubound(r) /= (/ 9, 3, 7 /))) stop 336
+    i = 4
+    r = minloc(a, dim=i, mask=m4)
+    if (any(shape(r) /= (/ 9, 3, 0 /))) stop 337
+    if (any(ubound(r) /= (/ 9, 3, 0 /))) stop 338
+  end subroutine
+  subroutine check_minloc_char
+    character :: a(9,3,0,7)
+    logical :: m1(9,3,0,7)
+    logical(kind=4) :: m4
+    integer :: i
+    integer, allocatable :: r(:,:,:)
+    a  = reshape((/ character:: /), shape(a))
+    m1 = reshape((/ logical:: /), shape(m1))
+    m4 = .false.
+    i = 1
+    r = minloc(a, dim=i)
+    if (any(shape(r) /= (/ 3, 0, 7 /))) stop 411
+    if (any(ubound(r) /= (/ 3, 0, 7 /))) stop 412
+    i = 2
+    r = minloc(a, dim=i)
+    if (any(shape(r) /= (/ 9, 0, 7 /))) stop 413
+    if (any(ubound(r) /= (/ 9, 0, 7 /))) stop 414
+    i = 3
+    r = minloc(a, dim=i)
+    if (any(shape(r) /= (/ 9, 3, 7 /))) stop 415
+    if (any(ubound(r) /= (/ 9, 3, 7 /))) stop 416
+    i = 4
+    r = minloc(a, dim=i)
+    if (any(shape(r) /= (/ 9, 3, 0 /))) stop 417
+    if (any(ubound(r) /= (/ 9, 3, 0 /))) stop 418
+    i = 1
+    r = minloc(a, dim=i, mask=m1)
+    if (any(shape(r) /= (/ 3, 0, 7 /))) stop 421
+    if (any(ubound(r) /= (/ 3, 0, 7 /))) stop 422
+    i = 2
+    r = minloc(a, dim=i, mask=m1)
+    if (any(shape(r) /= (/ 9, 0, 7 /))) stop 423
+    if (any(ubound(r) /= (/ 9, 0, 7 /))) stop 424
+    i = 3
+    r = minloc(a, dim=i, mask=m1)
+    if (any(shape(r) /= (/ 9, 3, 7 /))) stop 425
+    if (any(ubound(r) /= (/ 9, 3, 7 /))) stop 426
+    i = 4
+    r = minloc(a, dim=i, mask=m1)
+    if (any(shape(r) /= (/ 9, 3, 0 /))) stop 427
+    if (any(ubound(r) /= (/ 9, 3, 0 /))) stop 428
+    i = 1
+    r = minloc(a, dim=i, mask=m4)
+    if (any(shape(r) /= (/ 3, 0, 7 /))) stop 431
+    if (any(ubound(r) /= (/ 3, 0, 7 /))) stop 432
+    i = 2
+    r = minloc(a, dim=i, mask=m4)
+    if (any(shape(r) /= (/ 9, 0, 7 /))) stop 433
+    if (any(ubound(r) /= (/ 9, 0, 7 /))) stop 434
+    i = 3
+    r = minloc(a, dim=i, mask=m4)
+    if (any(shape(r) /= (/ 9, 3, 7 /))) stop 435
+    if (any(ubound(r) /= (/ 9, 3, 7 /))) stop 436
+    i = 4
+    r = minloc(a, dim=i, mask=m4)
+    if (any(shape(r) /= (/ 9, 3, 0 /))) stop 437
+    if (any(ubound(r) /= (/ 9, 3, 0 /))) stop 438
+  end subroutine
+  subroutine check_maxloc_char4
+    character(kind=4) :: a(9,3,0,7)
+    logical :: m1(9,3,0,7)
+    logical(kind=4) :: m4
+    integer :: i
+    integer, allocatable :: r(:,:,:)
+    a  = reshape((/ character(kind=4):: /), shape(a))
+    m1 = reshape((/ logical:: /), shape(m1))
+    m4 = .false.
+    i = 1
+    r = maxloc(a, dim=i)
+    if (any(shape(r) /= (/ 3, 0, 7 /))) stop 511
+    if (any(ubound(r) /= (/ 3, 0, 7 /))) stop 512
+    i = 2
+    r = maxloc(a, dim=i)
+    if (any(shape(r) /= (/ 9, 0, 7 /))) stop 513
+    if (any(ubound(r) /= (/ 9, 0, 7 /))) stop 514
+    i = 3
+    r = maxloc(a, dim=i)
+    if (any(shape(r) /= (/ 9, 3, 7 /))) stop 515
+    if (any(ubound(r) /= (/ 9, 3, 7 /))) stop 516
+    i = 4
+    r = maxloc(a, dim=i)
+    if (any(shape(r) /= (/ 9, 3, 0 /))) stop 517
+    if (any(ubound(r) /= (/ 9, 3, 0 /))) stop 518
+    i = 1
+    r = maxloc(a, dim=i, mask=m1)
+    if (any(shape(r) /= (/ 3, 0, 7 /))) stop 521
+    if (any(ubound(r) /= (/ 3, 0, 7 /))) stop 522
+    i = 2
+    r = maxloc(a, dim=i, mask=m1)
+    if (any(shape(r) /= (/ 9, 0, 7 /))) stop 523
+    if (any(ubound(r) /= (/ 9, 0, 7 /))) stop 524
+    i = 3
+    r = maxloc(a, dim=i, mask=m1)
+    if (any(shape(r) /= (/ 9, 3, 7 /))) stop 525
+    if (any(ubound(r) /= (/ 9, 3, 7 /))) stop 526
+    i = 4
+    r = maxloc(a, dim=i, mask=m1)
+    if (any(shape(r) /= (/ 9, 3, 0 /))) stop 527
+    if (any(ubound(r) /= (/ 9, 3, 0 /))) stop 528
+    i = 1
+    r = maxloc(a, dim=i, mask=m4)
+    if (any(shape(r) /= (/ 3, 0, 7 /))) stop 531
+    if (any(ubound(r) /= (/ 3, 0, 7 /))) stop 532
+    i = 2
+    r = maxloc(a, dim=i, mask=m4)
+    if (any(shape(r) /= (/ 9, 0, 7 /))) stop 533
+    if (any(ubound(r) /= (/ 9, 0, 7 /))) stop 534
+    i = 3
+    r = maxloc(a, dim=i, mask=m4)
+    if (any(shape(r) /= (/ 9, 3, 7 /))) stop 535
+    if (any(ubound(r) /= (/ 9, 3, 7 /))) stop 536
+    i = 4
+    r = maxloc(a, dim=i, mask=m4)
+    if (any(shape(r) /= (/ 9, 3, 0 /))) stop 537
+    if (any(ubound(r) /= (/ 9, 3, 0 /))) stop 538
+  end subroutine
+  subroutine check_minval_char
+    character :: a(9,3,0,7)
+    logical :: m1(9,3,0,7)
+    logical(kind=4) :: m4
+    integer :: i
+    character, allocatable :: r(:,:,:)
+    a  = reshape((/ character:: /), shape(a))
+    m1 = reshape((/ logical:: /), shape(m1))
+    m4 = .false.
+    i = 1
+    r = minval(a, dim=i)
+    if (any(shape(r) /= (/ 3, 0, 7 /))) stop 611
+    if (any(ubound(r) /= (/ 3, 0, 7 /))) stop 612
+    i = 2
+    r = minval(a, dim=i)
+    if (any(shape(r) /= (/ 9, 0, 7 /))) stop 613
+    if (any(ubound(r) /= (/ 9, 0, 7 /))) stop 614
+    i = 3
+    r = minval(a, dim=i)
+    if (any(shape(r) /= (/ 9, 3, 7 /))) stop 615
+    if (any(ubound(r) /= (/ 9, 3, 7 /))) stop 616
+    i = 4
+    r = minval(a, dim=i)
+    if (any(shape(r) /= (/ 9, 3, 0 /))) stop 617
+    if (any(ubound(r) /= (/ 9, 3, 0 /))) stop 618
+    i = 1
+    r = minval(a, dim=i, mask=m1)
+    if (any(shape(r) /= (/ 3, 0, 7 /))) stop 621
+    if (any(ubound(r) /= (/ 3, 0, 7 /))) stop 622
+    i = 2
+    r = minval(a, dim=i, mask=m1)
+    if (any(shape(r) /= (/ 9, 0, 7 /))) stop 623
+    if (any(ubound(r) /= (/ 9, 0, 7 /))) stop 624
+    i = 3
+    r = minval(a, dim=i, mask=m1)
+    if (any(shape(r) /= (/ 9, 3, 7 /))) stop 625
+    if (any(ubound(r) /= (/ 9, 3, 7 /))) stop 626
+    i = 4
+    r = minval(a, dim=i, mask=m1)
+    if (any(shape(r) /= (/ 9, 3, 0 /))) stop 627
+    if (any(ubound(r) /= (/ 9, 3, 0 /))) stop 628
+    i = 1
+    r = minval(a, dim=i, mask=m4)
+    if (any(shape(r) /= (/ 3, 0, 7 /))) stop 631
+    if (any(ubound(r) /= (/ 3, 0, 7 /))) stop 632
+    i = 2
+    r = minval(a, dim=i, mask=m4)
+    if (any(shape(r) /= (/ 9, 0, 7 /))) stop 633
+    if (any(ubound(r) /= (/ 9, 0, 7 /))) stop 634
+    i = 3
+    r = minval(a, dim=i, mask=m4)
+    if (any(shape(r) /= (/ 9, 3, 7 /))) stop 635
+    if (any(ubound(r) /= (/ 9, 3, 7 /))) stop 636
+    i = 4
+    r = minval(a, dim=i, mask=m4)
+    if (any(shape(r) /= (/ 9, 3, 0 /))) stop 637
+    if (any(ubound(r) /= (/ 9, 3, 0 /))) stop 638
+  end subroutine
+  subroutine check_maxval_char4
+    character(kind=4) :: a(9,3,0,7)
+    logical :: m1(9,3,0,7)
+    logical(kind=4) :: m4
+    integer :: i
+    character(kind=4), allocatable :: r(:,:,:)
+    a  = reshape((/ character(kind=4):: /), shape(a))
+    m1 = reshape((/ logical:: /), shape(m1))
+    m4 = .false.
+    i = 1
+    r = maxval(a, dim=i)
+    if (any(shape(r) /= (/ 3, 0, 7 /))) stop 711
+    if (any(ubound(r) /= (/ 3, 0, 7 /))) stop 712
+    i = 2
+    r = maxval(a, dim=i)
+    if (any(shape(r) /= (/ 9, 0, 7 /))) stop 713
+    if (any(ubound(r) /= (/ 9, 0, 7 /))) stop 714
+    i = 3
+    r = maxval(a, dim=i)
+    if (any(shape(r) /= (/ 9, 3, 7 /))) stop 715
+    if (any(ubound(r) /= (/ 9, 3, 7 /))) stop 716
+    i = 4
+    r = maxval(a, dim=i)
+    if (any(shape(r) /= (/ 9, 3, 0 /))) stop 717
+    if (any(ubound(r) /= (/ 9, 3, 0 /))) stop 718
+    i = 1
+    r = maxval(a, dim=i, mask=m1)
+    if (any(shape(r) /= (/ 3, 0, 7 /))) stop 721
+    if (any(ubound(r) /= (/ 3, 0, 7 /))) stop 722
+    i = 2
+    r = maxval(a, dim=i, mask=m1)
+    if (any(shape(r) /= (/ 9, 0, 7 /))) stop 723
+    if (any(ubound(r) /= (/ 9, 0, 7 /))) stop 724
+    i = 3
+    r = maxval(a, dim=i, mask=m1)
+    if (any(shape(r) /= (/ 9, 3, 7 /))) stop 725
+    if (any(ubound(r) /= (/ 9, 3, 7 /))) stop 726
+    i = 4
+    r = maxval(a, dim=i, mask=m1)
+    if (any(shape(r) /= (/ 9, 3, 0 /))) stop 727
+    if (any(ubound(r) /= (/ 9, 3, 0 /))) stop 728
+    i = 1
+    r = maxval(a, dim=i, mask=m4)
+    if (any(shape(r) /= (/ 3, 0, 7 /))) stop 731
+    if (any(ubound(r) /= (/ 3, 0, 7 /))) stop 732
+    i = 2
+    r = maxval(a, dim=i, mask=m4)
+    if (any(shape(r) /= (/ 9, 0, 7 /))) stop 733
+    if (any(ubound(r) /= (/ 9, 0, 7 /))) stop 734
+    i = 3
+    r = maxval(a, dim=i, mask=m4)
+    if (any(shape(r) /= (/ 9, 3, 7 /))) stop 735
+    if (any(ubound(r) /= (/ 9, 3, 7 /))) stop 736
+    i = 4
+    r = maxval(a, dim=i, mask=m4)
+    if (any(shape(r) /= (/ 9, 3, 0 /))) stop 737
+    if (any(ubound(r) /= (/ 9, 3, 0 /))) stop 738
+  end subroutine
+  subroutine check_any
+    logical :: a(9,3,0,7)
+    integer :: i
+    logical, allocatable :: r(:,:,:)
+    a  = reshape((/ logical:: /), shape(a))
+    i = 1
+    r = any(a, dim=i)
+    if (any(shape(r) /= (/ 3, 0, 7 /))) stop 811
+    if (any(ubound(r) /= (/ 3, 0, 7 /))) stop 812
+    i = 2
+    r = any(a, dim=i)
+    if (any(shape(r) /= (/ 9, 0, 7 /))) stop 813
+    if (any(ubound(r) /= (/ 9, 0, 7 /))) stop 814
+    i = 3
+    r = any(a, dim=i)
+    if (any(shape(r) /= (/ 9, 3, 7 /))) stop 815
+    if (any(ubound(r) /= (/ 9, 3, 7 /))) stop 816
+    i = 4
+    r = any(a, dim=i)
+    if (any(shape(r) /= (/ 9, 3, 0 /))) stop 817
+    if (any(ubound(r) /= (/ 9, 3, 0 /))) stop 818
+  end subroutine
+  subroutine check_count4
+    logical(kind=4) :: a(9,3,0,7)
+    integer :: i
+    integer, allocatable :: r(:,:,:)
+    a  = reshape((/ logical(kind=4):: /), shape(a))
+    i = 1
+    r = count(a, dim=i)
+    if (any(shape(r) /= (/ 3, 0, 7 /))) stop 911
+    if (any(ubound(r) /= (/ 3, 0, 7 /))) stop 912
+    i = 2
+    r = count(a, dim=i)
+    if (any(shape(r) /= (/ 9, 0, 7 /))) stop 913
+    if (any(ubound(r) /= (/ 9, 0, 7 /))) stop 914
+    i = 3
+    r = count(a, dim=i)
+    if (any(shape(r) /= (/ 9, 3, 7 /))) stop 915
+    if (any(ubound(r) /= (/ 9, 3, 7 /))) stop 916
+    i = 4
+    r = count(a, dim=i)
+    if (any(shape(r) /= (/ 9, 3, 0 /))) stop 917
+    if (any(ubound(r) /= (/ 9, 3, 0 /))) stop 918
+  end subroutine
+  subroutine check_findloc_int
+    integer :: a(9,3,0,7)
+    logical :: m1(9,3,0,7)
+    logical(kind=4) :: m4
+    integer :: i
+    integer, allocatable :: r(:,:,:)
+    a  = reshape((/ integer:: /), shape(a))
+    m1 = reshape((/ logical:: /), shape(m1))
+    m4 = .false.
+    i = 1
+    r = findloc(a, 10, dim=i)
+    if (any(shape(r) /= (/ 3, 0, 7 /))) stop 1011
+    if (any(ubound(r) /= (/ 3, 0, 7 /))) stop 1012
+    i = 2
+    r = findloc(a, 10, dim=i)
+    if (any(shape(r) /= (/ 9, 0, 7 /))) stop 1013
+    if (any(ubound(r) /= (/ 9, 0, 7 /))) stop 1014
+    i = 3
+    r = findloc(a, 10, dim=i)
+    if (any(shape(r) /= (/ 9, 3, 7 /))) stop 1015
+    if (any(ubound(r) /= (/ 9, 3, 7 /))) stop 1016
+    i = 4
+    r = findloc(a, 10, dim=i)
+    if (any(shape(r) /= (/ 9, 3, 0 /))) stop 1017
+    if (any(ubound(r) /= (/ 9, 3, 0 /))) stop 1018
+    i = 1
+    r = findloc(a, 10, dim=i, mask=m1)
+    if (any(shape(r) /= (/ 3, 0, 7 /))) stop 1021
+    if (any(ubound(r) /= (/ 3, 0, 7 /))) stop 1022
+    i = 2
+    r = findloc(a, 10, dim=i, mask=m1)
+    if (any(shape(r) /= (/ 9, 0, 7 /))) stop 1023
+    if (any(ubound(r) /= (/ 9, 0, 7 /))) stop 1024
+    i = 3
+    r = findloc(a, 10, dim=i, mask=m1)
+    if (any(shape(r) /= (/ 9, 3, 7 /))) stop 1025
+    if (any(ubound(r) /= (/ 9, 3, 7 /))) stop 1026
+    i = 4
+    r = findloc(a, 10, dim=i, mask=m1)
+    if (any(shape(r) /= (/ 9, 3, 0 /))) stop 1027
+    if (any(ubound(r) /= (/ 9, 3, 0 /))) stop 1028
+    i = 1
+    r = findloc(a, 10, dim=i, mask=m4)
+    if (any(shape(r) /= (/ 3, 0, 7 /))) stop 1031
+    if (any(ubound(r) /= (/ 3, 0, 7 /))) stop 1032
+    i = 2
+    r = findloc(a, 10, dim=i, mask=m4)
+    if (any(shape(r) /= (/ 9, 0, 7 /))) stop 1033
+    if (any(ubound(r) /= (/ 9, 0, 7 /))) stop 1034
+    i = 3
+    r = findloc(a, 10, dim=i, mask=m4)
+    if (any(shape(r) /= (/ 9, 3, 7 /))) stop 1035
+    if (any(ubound(r) /= (/ 9, 3, 7 /))) stop 1036
+    i = 4
+    r = findloc(a, 10, dim=i, mask=m4)
+    if (any(shape(r) /= (/ 9, 3, 0 /))) stop 1037
+    if (any(ubound(r) /= (/ 9, 3, 0 /))) stop 1038
+  end subroutine
+  subroutine check_findloc_char
+    character :: a(9,3,0,7)
+    logical :: m1(9,3,0,7)
+    logical(kind=4) :: m4
+    integer :: i
+    integer, allocatable :: r(:,:,:)
+    a  = reshape((/ character:: /), shape(a))
+    m1 = reshape((/ logical:: /), shape(m1))
+    m4 = .false.
+    i = 1
+    r = findloc(a, "a", dim=i)
+    if (any(shape(r) /= (/ 3, 0, 7 /))) stop 1111
+    if (any(ubound(r) /= (/ 3, 0, 7 /))) stop 1112
+    i = 2
+    r = findloc(a, "a", dim=i)
+    if (any(shape(r) /= (/ 9, 0, 7 /))) stop 1113
+    if (any(ubound(r) /= (/ 9, 0, 7 /))) stop 1114
+    i = 3
+    r = findloc(a, "a", dim=i)
+    if (any(shape(r) /= (/ 9, 3, 7 /))) stop 1115
+    if (any(ubound(r) /= (/ 9, 3, 7 /))) stop 1116
+    i = 4
+    r = findloc(a, "a", dim=i)
+    if (any(shape(r) /= (/ 9, 3, 0 /))) stop 1117
+    if (any(ubound(r) /= (/ 9, 3, 0 /))) stop 1118
+    i = 1
+    r = findloc(a, "a", dim=i, mask=m1)
+    if (any(shape(r) /= (/ 3, 0, 7 /))) stop 1121
+    if (any(ubound(r) /= (/ 3, 0, 7 /))) stop 1122
+    i = 2
+    r = findloc(a, "a", dim=i, mask=m1)
+    if (any(shape(r) /= (/ 9, 0, 7 /))) stop 1123
+    if (any(ubound(r) /= (/ 9, 0, 7 /))) stop 1124
+    i = 3
+    r = findloc(a, "a", dim=i, mask=m1)
+    if (any(shape(r) /= (/ 9, 3, 7 /))) stop 1125
+    if (any(ubound(r) /= (/ 9, 3, 7 /))) stop 1126
+    i = 4
+    r = findloc(a, "a", dim=i, mask=m1)
+    if (any(shape(r) /= (/ 9, 3, 0 /))) stop 1127
+    if (any(ubound(r) /= (/ 9, 3, 0 /))) stop 1128
+    i = 1
+    r = findloc(a, "a", dim=i, mask=m4)
+    if (any(shape(r) /= (/ 3, 0, 7 /))) stop 1131
+    if (any(ubound(r) /= (/ 3, 0, 7 /))) stop 1132
+    i = 2
+    r = findloc(a, "a", dim=i, mask=m4)
+    if (any(shape(r) /= (/ 9, 0, 7 /))) stop 1133
+    if (any(ubound(r) /= (/ 9, 0, 7 /))) stop 1134
+    i = 3
+    r = findloc(a, "a", dim=i, mask=m4)
+    if (any(shape(r) /= (/ 9, 3, 7 /))) stop 1135
+    if (any(ubound(r) /= (/ 9, 3, 7 /))) stop 1136
+    i = 4
+    r = findloc(a, "a", dim=i, mask=m4)
+    if (any(shape(r) /= (/ 9, 3, 0 /))) stop 1137
+    if (any(ubound(r) /= (/ 9, 3, 0 /))) stop 1138
+  end subroutine
+end program
diff --git a/libgfortran/generated/all_l1.c b/libgfortran/generated/all_l1.c
index e494281146127b0f8c8f186166b318d2ebe5f645..aacc5ac0793a161ba12c51912f83da58e30d5f8e 100644
--- a/libgfortran/generated/all_l1.c
+++ b/libgfortran/generated/all_l1.c
@@ -103,11 +103,7 @@ all_l1 (gfc_array_l1 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_LOGICAL_1));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/all_l16.c b/libgfortran/generated/all_l16.c
index 1fc45bfd97c05c23fb176c1c1327f21d72bd4123..e1b2e157c37845bd71f0094b67e3957600909b92 100644
--- a/libgfortran/generated/all_l16.c
+++ b/libgfortran/generated/all_l16.c
@@ -103,11 +103,7 @@ all_l16 (gfc_array_l16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_LOGICAL_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/all_l2.c b/libgfortran/generated/all_l2.c
index f6dbf1c456dcf13f7ada13d3610e8e7ca00a0ee9..045196eb13b48b6d7a346c5249e15a1216e812e4 100644
--- a/libgfortran/generated/all_l2.c
+++ b/libgfortran/generated/all_l2.c
@@ -103,11 +103,7 @@ all_l2 (gfc_array_l2 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_LOGICAL_2));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/all_l4.c b/libgfortran/generated/all_l4.c
index 7f915ef9c615f5390d7d343e565dbc9995a40d6e..7783d966697a663439b0417bed109a0ab81c32c0 100644
--- a/libgfortran/generated/all_l4.c
+++ b/libgfortran/generated/all_l4.c
@@ -103,11 +103,7 @@ all_l4 (gfc_array_l4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_LOGICAL_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/all_l8.c b/libgfortran/generated/all_l8.c
index 3fa8147c1a1535f5f32c98beea5eb3c25b2a9532..a9571003b48c295ddd49ce1a587fec8069aae6ad 100644
--- a/libgfortran/generated/all_l8.c
+++ b/libgfortran/generated/all_l8.c
@@ -103,11 +103,7 @@ all_l8 (gfc_array_l8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_LOGICAL_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/any_l1.c b/libgfortran/generated/any_l1.c
index 236e4100ec2340e37e4e991b52e8cbd4f6c6549b..ce38a9761cb7490d67ff481ce1f0266e8b7b441b 100644
--- a/libgfortran/generated/any_l1.c
+++ b/libgfortran/generated/any_l1.c
@@ -103,11 +103,7 @@ any_l1 (gfc_array_l1 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_LOGICAL_1));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/any_l16.c b/libgfortran/generated/any_l16.c
index 7290d66667e8c0a2c124ba4ba385a1172bb02989..771c6fcbc2e0b50d564a0a32c0812cfff946df44 100644
--- a/libgfortran/generated/any_l16.c
+++ b/libgfortran/generated/any_l16.c
@@ -103,11 +103,7 @@ any_l16 (gfc_array_l16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_LOGICAL_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/any_l2.c b/libgfortran/generated/any_l2.c
index d54e78fda0c728925b98fac23c1e8deebe773e68..69a0d4745769e0cc6dc5dba5ba04e47d20ac9c49 100644
--- a/libgfortran/generated/any_l2.c
+++ b/libgfortran/generated/any_l2.c
@@ -103,11 +103,7 @@ any_l2 (gfc_array_l2 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_LOGICAL_2));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/any_l4.c b/libgfortran/generated/any_l4.c
index a577bc5821383a02b2e1a86f15419e82d8827663..08e4cff945e6950b524cf63bfcdadbb89e96e514 100644
--- a/libgfortran/generated/any_l4.c
+++ b/libgfortran/generated/any_l4.c
@@ -103,11 +103,7 @@ any_l4 (gfc_array_l4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_LOGICAL_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/any_l8.c b/libgfortran/generated/any_l8.c
index 0af302746f58571e171a9eb970008960020e296f..259bd30f780fab4f5de57f805469d057edcb692a 100644
--- a/libgfortran/generated/any_l8.c
+++ b/libgfortran/generated/any_l8.c
@@ -103,11 +103,7 @@ any_l8 (gfc_array_l8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_LOGICAL_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/count_16_l.c b/libgfortran/generated/count_16_l.c
index 89f4f753d1a57f5a61a55679c0c0ee4336ddda73..f7319d0e84b076d2c4097b810bb881959ad1d4ae 100644
--- a/libgfortran/generated/count_16_l.c
+++ b/libgfortran/generated/count_16_l.c
@@ -103,11 +103,7 @@ count_16_l (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/count_1_l.c b/libgfortran/generated/count_1_l.c
index 05b8b898e9411ac725572067f0d7fa7a4427ead2..919388ff18a21988bdeafa6009294923aa9fb277 100644
--- a/libgfortran/generated/count_1_l.c
+++ b/libgfortran/generated/count_1_l.c
@@ -103,11 +103,7 @@ count_1_l (gfc_array_i1 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_1));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/count_2_l.c b/libgfortran/generated/count_2_l.c
index 654b21589d00a429fe205a4d2bdb876d5228e7e7..493cd15e5d2464578d505499d313eb15dd457738 100644
--- a/libgfortran/generated/count_2_l.c
+++ b/libgfortran/generated/count_2_l.c
@@ -103,11 +103,7 @@ count_2_l (gfc_array_i2 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_2));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/count_4_l.c b/libgfortran/generated/count_4_l.c
index 8f40ea1c0be827e2ff8f15e88d4aaaa045ea2f46..a308bd7014fdbe8315cbd36ffa8c720176e24248 100644
--- a/libgfortran/generated/count_4_l.c
+++ b/libgfortran/generated/count_4_l.c
@@ -103,11 +103,7 @@ count_4_l (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/count_8_l.c b/libgfortran/generated/count_8_l.c
index ab64c08580347c0d6b2a822ba97a4d010e6d5f51..e23081d00caebc539dc722f578dd83ea911d4f1f 100644
--- a/libgfortran/generated/count_8_l.c
+++ b/libgfortran/generated/count_8_l.c
@@ -103,11 +103,7 @@ count_8_l (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/findloc1_c10.c b/libgfortran/generated/findloc1_c10.c
index 0b7905a101c889b5f440460dd3253fa634b113ff..fa68971ff3856061ae37126e8b838984ad25995c 100644
--- a/libgfortran/generated/findloc1_c10.c
+++ b/libgfortran/generated/findloc1_c10.c
@@ -105,11 +105,7 @@ findloc1_c10 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -293,11 +289,7 @@ mfindloc1_c10 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +458,7 @@ sfindloc1_c10 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/findloc1_c16.c b/libgfortran/generated/findloc1_c16.c
index 1cbe1fc5b26acdb1eb80b26c3a5ee1fb12304be1..13e2209dc32ef489b4ec3161050130d80133adbf 100644
--- a/libgfortran/generated/findloc1_c16.c
+++ b/libgfortran/generated/findloc1_c16.c
@@ -105,11 +105,7 @@ findloc1_c16 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -293,11 +289,7 @@ mfindloc1_c16 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +458,7 @@ sfindloc1_c16 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/findloc1_c17.c b/libgfortran/generated/findloc1_c17.c
index fea16286bf8f7f79ba3696f4302f5c7bf7acf048..03c651e9c196511ad279c8eb770a07ec0b10de66 100644
--- a/libgfortran/generated/findloc1_c17.c
+++ b/libgfortran/generated/findloc1_c17.c
@@ -105,11 +105,7 @@ findloc1_c17 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -293,11 +289,7 @@ mfindloc1_c17 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +458,7 @@ sfindloc1_c17 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/findloc1_c4.c b/libgfortran/generated/findloc1_c4.c
index 2c800aa4a7773b95881c7cffd43544ae8156931f..6c3fe7cd537e195bfab3a2b4db9dfe789c7537cb 100644
--- a/libgfortran/generated/findloc1_c4.c
+++ b/libgfortran/generated/findloc1_c4.c
@@ -105,11 +105,7 @@ findloc1_c4 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -293,11 +289,7 @@ mfindloc1_c4 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +458,7 @@ sfindloc1_c4 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/findloc1_c8.c b/libgfortran/generated/findloc1_c8.c
index 9f14e631c9ea2b6bf280d911dd85a5b84d7d0e42..2b4b84b522c14b476e9726ff45a3b47320ca42f4 100644
--- a/libgfortran/generated/findloc1_c8.c
+++ b/libgfortran/generated/findloc1_c8.c
@@ -105,11 +105,7 @@ findloc1_c8 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -293,11 +289,7 @@ mfindloc1_c8 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +458,7 @@ sfindloc1_c8 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/findloc1_i1.c b/libgfortran/generated/findloc1_i1.c
index 90896ac92a6bfc5d225b6d332cc6d60ac92534f1..5175198a2953bfaf3a20b52ae84b02a98d7eec70 100644
--- a/libgfortran/generated/findloc1_i1.c
+++ b/libgfortran/generated/findloc1_i1.c
@@ -105,11 +105,7 @@ findloc1_i1 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -293,11 +289,7 @@ mfindloc1_i1 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +458,7 @@ sfindloc1_i1 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/findloc1_i16.c b/libgfortran/generated/findloc1_i16.c
index 699320dffcd5fd12cab1639b4b62ffcb1c8c229e..c3fcf8b5a2c4aec4dc475c32802dba69553cca4c 100644
--- a/libgfortran/generated/findloc1_i16.c
+++ b/libgfortran/generated/findloc1_i16.c
@@ -105,11 +105,7 @@ findloc1_i16 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -293,11 +289,7 @@ mfindloc1_i16 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +458,7 @@ sfindloc1_i16 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/findloc1_i2.c b/libgfortran/generated/findloc1_i2.c
index d3ebdab8f23b9961880249d52d9825aba7aa2c17..c00f7b5c2446b19e9eeb162eafc260a4957de4b0 100644
--- a/libgfortran/generated/findloc1_i2.c
+++ b/libgfortran/generated/findloc1_i2.c
@@ -105,11 +105,7 @@ findloc1_i2 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -293,11 +289,7 @@ mfindloc1_i2 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +458,7 @@ sfindloc1_i2 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/findloc1_i4.c b/libgfortran/generated/findloc1_i4.c
index e030e6bee60e8f53d701e0143f982067ad07a4b6..d1d0247b6561019c77cebf2ebad31f43040b7e13 100644
--- a/libgfortran/generated/findloc1_i4.c
+++ b/libgfortran/generated/findloc1_i4.c
@@ -105,11 +105,7 @@ findloc1_i4 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -293,11 +289,7 @@ mfindloc1_i4 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +458,7 @@ sfindloc1_i4 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/findloc1_i8.c b/libgfortran/generated/findloc1_i8.c
index 678e65161052cd6dfabc7cd35a7213d2060c5f08..02f219bcc1e8f43b1dcb65057a6cc88eb6dd0286 100644
--- a/libgfortran/generated/findloc1_i8.c
+++ b/libgfortran/generated/findloc1_i8.c
@@ -105,11 +105,7 @@ findloc1_i8 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -293,11 +289,7 @@ mfindloc1_i8 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +458,7 @@ sfindloc1_i8 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/findloc1_r10.c b/libgfortran/generated/findloc1_r10.c
index b416fdd0e008df85dd2e39abf74c9bf04f905e8f..1b824c7d78b6bcdfdf197412524d94e4e1b78a7f 100644
--- a/libgfortran/generated/findloc1_r10.c
+++ b/libgfortran/generated/findloc1_r10.c
@@ -105,11 +105,7 @@ findloc1_r10 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -293,11 +289,7 @@ mfindloc1_r10 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +458,7 @@ sfindloc1_r10 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/findloc1_r16.c b/libgfortran/generated/findloc1_r16.c
index d03b34fbc0bcbecc31566c66f314e7d951ec0d74..9a42849c989a8fdedaea3a3fda14535b8901f8c1 100644
--- a/libgfortran/generated/findloc1_r16.c
+++ b/libgfortran/generated/findloc1_r16.c
@@ -105,11 +105,7 @@ findloc1_r16 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -293,11 +289,7 @@ mfindloc1_r16 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +458,7 @@ sfindloc1_r16 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/findloc1_r17.c b/libgfortran/generated/findloc1_r17.c
index 2b72e90506ac1fb1ee1d5d990b30cc20372d7bcd..7b95da2b6e7639e581a8ea4266a0fcc5b7b6ab57 100644
--- a/libgfortran/generated/findloc1_r17.c
+++ b/libgfortran/generated/findloc1_r17.c
@@ -105,11 +105,7 @@ findloc1_r17 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -293,11 +289,7 @@ mfindloc1_r17 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +458,7 @@ sfindloc1_r17 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/findloc1_r4.c b/libgfortran/generated/findloc1_r4.c
index fa216cca481504b851fd63f952aa3d44ee11447b..8b527728cb0afb72dd5e033ee6c07211c42f30be 100644
--- a/libgfortran/generated/findloc1_r4.c
+++ b/libgfortran/generated/findloc1_r4.c
@@ -105,11 +105,7 @@ findloc1_r4 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -293,11 +289,7 @@ mfindloc1_r4 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +458,7 @@ sfindloc1_r4 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/findloc1_r8.c b/libgfortran/generated/findloc1_r8.c
index 7f1e044f8e1a2aeea44c2d447a21fb6b2b20b1c4..0ac3fd6e73a1acec379cd570a0ce182f985416e9 100644
--- a/libgfortran/generated/findloc1_r8.c
+++ b/libgfortran/generated/findloc1_r8.c
@@ -105,11 +105,7 @@ findloc1_r8 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -293,11 +289,7 @@ mfindloc1_r8 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +458,7 @@ sfindloc1_r8 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/findloc1_s1.c b/libgfortran/generated/findloc1_s1.c
index 2fb81c414af9b9f342a1e5d2a045643fb6d27384..85b13bd7c5f49c3313ed95a304a4bde829b5a705 100644
--- a/libgfortran/generated/findloc1_s1.c
+++ b/libgfortran/generated/findloc1_s1.c
@@ -107,11 +107,7 @@ findloc1_s1 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -295,11 +291,7 @@ mfindloc1_s1 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -468,11 +460,7 @@ sfindloc1_s1 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/findloc1_s4.c b/libgfortran/generated/findloc1_s4.c
index 641ca7fa58a7c12e08ea701815118ab166934e80..7b5a020d3147b089ee78ce962abe7971773ef5cf 100644
--- a/libgfortran/generated/findloc1_s4.c
+++ b/libgfortran/generated/findloc1_s4.c
@@ -107,11 +107,7 @@ findloc1_s4 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -295,11 +291,7 @@ mfindloc1_s4 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -468,11 +460,7 @@ sfindloc1_s4 (gfc_array_index_type * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/iall_i1.c b/libgfortran/generated/iall_i1.c
index 2236f044e650299ffb34d28b1dac198504844db9..2a3e52b99838773bac8a4485f22b37d5327b4c5d 100644
--- a/libgfortran/generated/iall_i1.c
+++ b/libgfortran/generated/iall_i1.c
@@ -106,12 +106,7 @@ iall_i1 (gfc_array_i1 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_1));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ miall_i1 (gfc_array_i1 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_1));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ siall_i1 (gfc_array_i1 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_1));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/iall_i16.c b/libgfortran/generated/iall_i16.c
index 96ca5a57c9ce6813d9801043b813f386d5ad227e..d7bdc55623af4ed7073b2e8361902003bec58753 100644
--- a/libgfortran/generated/iall_i16.c
+++ b/libgfortran/generated/iall_i16.c
@@ -106,12 +106,7 @@ iall_i16 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ miall_i16 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ siall_i16 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/iall_i2.c b/libgfortran/generated/iall_i2.c
index 4d895db2b35650109734c1720ded8e282c3e7a3c..ceaaf153efe7cb02aa0b62d335b03fb8abd47424 100644
--- a/libgfortran/generated/iall_i2.c
+++ b/libgfortran/generated/iall_i2.c
@@ -106,12 +106,7 @@ iall_i2 (gfc_array_i2 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_2));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ miall_i2 (gfc_array_i2 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_2));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ siall_i2 (gfc_array_i2 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_2));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/iall_i4.c b/libgfortran/generated/iall_i4.c
index 673e98094831f9ca536fbf7895170e0520b1c8c0..face5d95cc12b6fbbf8cfdbbed532c6bb011c0b6 100644
--- a/libgfortran/generated/iall_i4.c
+++ b/libgfortran/generated/iall_i4.c
@@ -106,12 +106,7 @@ iall_i4 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ miall_i4 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ siall_i4 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/iall_i8.c b/libgfortran/generated/iall_i8.c
index 4de6ff1782df3635b059d1dcbcd7350cb8f0b2f1..7e47c3b8663cb4bbfe55dc033b04a5dd94b67f06 100644
--- a/libgfortran/generated/iall_i8.c
+++ b/libgfortran/generated/iall_i8.c
@@ -106,12 +106,7 @@ iall_i8 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ miall_i8 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ siall_i8 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/iany_i1.c b/libgfortran/generated/iany_i1.c
index ab191d6bdd278994df80dc3ee5368a3bb5b562dc..e152ffe85da6f0db1e456a2f68c1a988c597b600 100644
--- a/libgfortran/generated/iany_i1.c
+++ b/libgfortran/generated/iany_i1.c
@@ -106,12 +106,7 @@ iany_i1 (gfc_array_i1 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_1));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ miany_i1 (gfc_array_i1 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_1));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ siany_i1 (gfc_array_i1 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_1));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/iany_i16.c b/libgfortran/generated/iany_i16.c
index 8fda0efea828c15d81ae60fdab850f6df468fae9..bd775b8216b0a62cae521a43af9c78cb69fee604 100644
--- a/libgfortran/generated/iany_i16.c
+++ b/libgfortran/generated/iany_i16.c
@@ -106,12 +106,7 @@ iany_i16 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ miany_i16 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ siany_i16 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/iany_i2.c b/libgfortran/generated/iany_i2.c
index 43080b8599229c9163bc790b8457a30ba0cea9fa..956fbdb47974941613b6463729cf2d5b7e94f458 100644
--- a/libgfortran/generated/iany_i2.c
+++ b/libgfortran/generated/iany_i2.c
@@ -106,12 +106,7 @@ iany_i2 (gfc_array_i2 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_2));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ miany_i2 (gfc_array_i2 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_2));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ siany_i2 (gfc_array_i2 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_2));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/iany_i4.c b/libgfortran/generated/iany_i4.c
index d8430ca4e9053bc8b4c99636899d100e7a288525..fef7d65b69176dd1bbc80e55177c013ce453f7d6 100644
--- a/libgfortran/generated/iany_i4.c
+++ b/libgfortran/generated/iany_i4.c
@@ -106,12 +106,7 @@ iany_i4 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ miany_i4 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ siany_i4 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/iany_i8.c b/libgfortran/generated/iany_i8.c
index 7d3ac16412dab1bf0b2a1f41bea872774354bf44..5ddca1f8642ec1130ab16af0e218fbf4726070a4 100644
--- a/libgfortran/generated/iany_i8.c
+++ b/libgfortran/generated/iany_i8.c
@@ -106,12 +106,7 @@ iany_i8 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ miany_i8 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ siany_i8 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/iparity_i1.c b/libgfortran/generated/iparity_i1.c
index 53b15cbb73fbb5826ba88a1c3cab826a83b71a7c..8076d05ebd6f76d603d7699b4210f884cfaa94e9 100644
--- a/libgfortran/generated/iparity_i1.c
+++ b/libgfortran/generated/iparity_i1.c
@@ -106,12 +106,7 @@ iparity_i1 (gfc_array_i1 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_1));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ miparity_i1 (gfc_array_i1 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_1));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ siparity_i1 (gfc_array_i1 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_1));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/iparity_i16.c b/libgfortran/generated/iparity_i16.c
index 848ac6284fbc3606a1dd7f156f2cb4097281f33b..49907fe7cf42be722fbb3923ad4be067634d2069 100644
--- a/libgfortran/generated/iparity_i16.c
+++ b/libgfortran/generated/iparity_i16.c
@@ -106,12 +106,7 @@ iparity_i16 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ miparity_i16 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ siparity_i16 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/iparity_i2.c b/libgfortran/generated/iparity_i2.c
index f435fd27edd9a89f573d906612e87553479e5446..58703bc991b8751cc16c02add0f939ccbcef7f60 100644
--- a/libgfortran/generated/iparity_i2.c
+++ b/libgfortran/generated/iparity_i2.c
@@ -106,12 +106,7 @@ iparity_i2 (gfc_array_i2 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_2));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ miparity_i2 (gfc_array_i2 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_2));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ siparity_i2 (gfc_array_i2 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_2));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/iparity_i4.c b/libgfortran/generated/iparity_i4.c
index ea876bdd31adc2307f4e407e838d1a30d593015f..051dd360c1a235fe7f65a918ad241974addebdfd 100644
--- a/libgfortran/generated/iparity_i4.c
+++ b/libgfortran/generated/iparity_i4.c
@@ -106,12 +106,7 @@ iparity_i4 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ miparity_i4 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ siparity_i4 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/iparity_i8.c b/libgfortran/generated/iparity_i8.c
index 0fee2e5025d8f8704a32e8eaefc89cf9adc99cf1..90f444e6f96a29970a5a67f743962cfec24bcdc5 100644
--- a/libgfortran/generated/iparity_i8.c
+++ b/libgfortran/generated/iparity_i8.c
@@ -106,12 +106,7 @@ iparity_i8 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ miparity_i8 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ siparity_i8 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxloc1_16_i1.c b/libgfortran/generated/maxloc1_16_i1.c
index bc0643cde1e1040006bb5c05c9b829420b1a72a7..3a00cd538a0aac3263229d40ec16128b75a9b586 100644
--- a/libgfortran/generated/maxloc1_16_i1.c
+++ b/libgfortran/generated/maxloc1_16_i1.c
@@ -109,12 +109,7 @@ maxloc1_16_i1 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -331,11 +326,7 @@ mmaxloc1_16_i1 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -537,11 +528,7 @@ smaxloc1_16_i1 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxloc1_16_i16.c b/libgfortran/generated/maxloc1_16_i16.c
index 5dca85c4bc023c4e1c2073dafcd0b537ec32a0a2..bfb3e6f69e92ee0a4c7dc4154d82ec5a8ef9df2b 100644
--- a/libgfortran/generated/maxloc1_16_i16.c
+++ b/libgfortran/generated/maxloc1_16_i16.c
@@ -109,12 +109,7 @@ maxloc1_16_i16 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -331,11 +326,7 @@ mmaxloc1_16_i16 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -537,11 +528,7 @@ smaxloc1_16_i16 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxloc1_16_i2.c b/libgfortran/generated/maxloc1_16_i2.c
index 118d7c527a148282bbd635bb2f2658405df88583..abe0b89df01cc14eae79f21a7407332bbf679ad9 100644
--- a/libgfortran/generated/maxloc1_16_i2.c
+++ b/libgfortran/generated/maxloc1_16_i2.c
@@ -109,12 +109,7 @@ maxloc1_16_i2 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -331,11 +326,7 @@ mmaxloc1_16_i2 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -537,11 +528,7 @@ smaxloc1_16_i2 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxloc1_16_i4.c b/libgfortran/generated/maxloc1_16_i4.c
index 858dfc0e8509fb797f2ada6edbce46bd235c0a4d..46507045035fa293e9e0a5491e539a5950fa5a1e 100644
--- a/libgfortran/generated/maxloc1_16_i4.c
+++ b/libgfortran/generated/maxloc1_16_i4.c
@@ -109,12 +109,7 @@ maxloc1_16_i4 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -331,11 +326,7 @@ mmaxloc1_16_i4 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -537,11 +528,7 @@ smaxloc1_16_i4 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxloc1_16_i8.c b/libgfortran/generated/maxloc1_16_i8.c
index 36469e49797e0093ef764a01c31f83582c701b65..83ac6a56a6e78129e13a63013d1f22ca712896e6 100644
--- a/libgfortran/generated/maxloc1_16_i8.c
+++ b/libgfortran/generated/maxloc1_16_i8.c
@@ -109,12 +109,7 @@ maxloc1_16_i8 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -331,11 +326,7 @@ mmaxloc1_16_i8 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -537,11 +528,7 @@ smaxloc1_16_i8 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxloc1_16_r10.c b/libgfortran/generated/maxloc1_16_r10.c
index dfc55681b1fb8e535349cbba27a7d9280eaafaca..0dec2116b153b0f05b08dc486b1cbac51fc9a8d0 100644
--- a/libgfortran/generated/maxloc1_16_r10.c
+++ b/libgfortran/generated/maxloc1_16_r10.c
@@ -109,12 +109,7 @@ maxloc1_16_r10 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -331,11 +326,7 @@ mmaxloc1_16_r10 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -537,11 +528,7 @@ smaxloc1_16_r10 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxloc1_16_r16.c b/libgfortran/generated/maxloc1_16_r16.c
index 17daa796afcc195cdfda0d1e03172cdf7cc95453..1f75f4471ef9229b4facf1b837ab7d14b46f6fac 100644
--- a/libgfortran/generated/maxloc1_16_r16.c
+++ b/libgfortran/generated/maxloc1_16_r16.c
@@ -109,12 +109,7 @@ maxloc1_16_r16 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -331,11 +326,7 @@ mmaxloc1_16_r16 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -537,11 +528,7 @@ smaxloc1_16_r16 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxloc1_16_r17.c b/libgfortran/generated/maxloc1_16_r17.c
index 46fd4ab320c45aaa96a20d88c8db1171c36f219c..31ff83bab4d78f489c00b853af2ac6f0f5ff9d25 100644
--- a/libgfortran/generated/maxloc1_16_r17.c
+++ b/libgfortran/generated/maxloc1_16_r17.c
@@ -109,12 +109,7 @@ maxloc1_16_r17 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -331,11 +326,7 @@ mmaxloc1_16_r17 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -537,11 +528,7 @@ smaxloc1_16_r17 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxloc1_16_r4.c b/libgfortran/generated/maxloc1_16_r4.c
index b52932f70bf0a6e057c87f4aebadddaadcedc36d..fea7580b82e188d41563d09dafccbb3819a976d4 100644
--- a/libgfortran/generated/maxloc1_16_r4.c
+++ b/libgfortran/generated/maxloc1_16_r4.c
@@ -109,12 +109,7 @@ maxloc1_16_r4 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -331,11 +326,7 @@ mmaxloc1_16_r4 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -537,11 +528,7 @@ smaxloc1_16_r4 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxloc1_16_r8.c b/libgfortran/generated/maxloc1_16_r8.c
index c26c4b4ed0af1fec4fe0ee7832e0351b2fd0d1ca..4f2acd645dd5c006dce87e7d55cb053ab87e0f38 100644
--- a/libgfortran/generated/maxloc1_16_r8.c
+++ b/libgfortran/generated/maxloc1_16_r8.c
@@ -109,12 +109,7 @@ maxloc1_16_r8 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -331,11 +326,7 @@ mmaxloc1_16_r8 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -537,11 +528,7 @@ smaxloc1_16_r8 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxloc1_16_s1.c b/libgfortran/generated/maxloc1_16_s1.c
index 54f57238367d9dea07c59733ff96fb72acf628fd..44a27ca565ac4579c1485639c7581f88349ad05c 100644
--- a/libgfortran/generated/maxloc1_16_s1.c
+++ b/libgfortran/generated/maxloc1_16_s1.c
@@ -121,12 +121,7 @@ maxloc1_16_s1 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -324,11 +319,7 @@ mmaxloc1_16_s1 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -503,11 +494,7 @@ smaxloc1_16_s1 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxloc1_16_s4.c b/libgfortran/generated/maxloc1_16_s4.c
index eb015eabef2aabda6c8219f1ee452dc3c0ab34b8..c4686a7d56f23610061ec26cf4c515214081ed82 100644
--- a/libgfortran/generated/maxloc1_16_s4.c
+++ b/libgfortran/generated/maxloc1_16_s4.c
@@ -121,12 +121,7 @@ maxloc1_16_s4 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -324,11 +319,7 @@ mmaxloc1_16_s4 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -503,11 +494,7 @@ smaxloc1_16_s4 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxloc1_4_i1.c b/libgfortran/generated/maxloc1_4_i1.c
index 4b0bd56a60bd68a8634eca9e58420e0ff31a5921..0e4c644fc49f7e2db1bc2d79dddc926eef6eea79 100644
--- a/libgfortran/generated/maxloc1_4_i1.c
+++ b/libgfortran/generated/maxloc1_4_i1.c
@@ -109,12 +109,7 @@ maxloc1_4_i1 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -331,11 +326,7 @@ mmaxloc1_4_i1 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -537,11 +528,7 @@ smaxloc1_4_i1 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxloc1_4_i16.c b/libgfortran/generated/maxloc1_4_i16.c
index d976d2d4b8e66085b1aff6e6173f634d79b5c8c6..4094c010342b57480aeaf34464ae24603e48cef5 100644
--- a/libgfortran/generated/maxloc1_4_i16.c
+++ b/libgfortran/generated/maxloc1_4_i16.c
@@ -109,12 +109,7 @@ maxloc1_4_i16 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -331,11 +326,7 @@ mmaxloc1_4_i16 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -537,11 +528,7 @@ smaxloc1_4_i16 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxloc1_4_i2.c b/libgfortran/generated/maxloc1_4_i2.c
index ba8228925d46c822d6e248f6bef5468b4afe56dd..c552d902243094565b29b247c5310c6d0f0bce9d 100644
--- a/libgfortran/generated/maxloc1_4_i2.c
+++ b/libgfortran/generated/maxloc1_4_i2.c
@@ -109,12 +109,7 @@ maxloc1_4_i2 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -331,11 +326,7 @@ mmaxloc1_4_i2 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -537,11 +528,7 @@ smaxloc1_4_i2 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxloc1_4_i4.c b/libgfortran/generated/maxloc1_4_i4.c
index 644e48e547fb9c2664788aa002b09489e952057a..76a71219ff523cbb87e112d3962768038e7b3fdc 100644
--- a/libgfortran/generated/maxloc1_4_i4.c
+++ b/libgfortran/generated/maxloc1_4_i4.c
@@ -109,12 +109,7 @@ maxloc1_4_i4 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -331,11 +326,7 @@ mmaxloc1_4_i4 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -537,11 +528,7 @@ smaxloc1_4_i4 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxloc1_4_i8.c b/libgfortran/generated/maxloc1_4_i8.c
index fd5d31b5162498e2fe09a0b9cee18eb009a917b4..49a05188db4b8c6b3420891b866dbf14e6351c51 100644
--- a/libgfortran/generated/maxloc1_4_i8.c
+++ b/libgfortran/generated/maxloc1_4_i8.c
@@ -109,12 +109,7 @@ maxloc1_4_i8 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -331,11 +326,7 @@ mmaxloc1_4_i8 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -537,11 +528,7 @@ smaxloc1_4_i8 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxloc1_4_r10.c b/libgfortran/generated/maxloc1_4_r10.c
index 00c90fa3c66a5aab18bd28ad2f7ebfdb013a23d9..4f1a8e88f16491b8d96c8d0e792d4917091a261f 100644
--- a/libgfortran/generated/maxloc1_4_r10.c
+++ b/libgfortran/generated/maxloc1_4_r10.c
@@ -109,12 +109,7 @@ maxloc1_4_r10 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -331,11 +326,7 @@ mmaxloc1_4_r10 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -537,11 +528,7 @@ smaxloc1_4_r10 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxloc1_4_r16.c b/libgfortran/generated/maxloc1_4_r16.c
index 92372b8d83756de592345f48db9f09541cef4ce5..ecb9c2cca034c906878fbaa820930ced8d73ca2b 100644
--- a/libgfortran/generated/maxloc1_4_r16.c
+++ b/libgfortran/generated/maxloc1_4_r16.c
@@ -109,12 +109,7 @@ maxloc1_4_r16 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -331,11 +326,7 @@ mmaxloc1_4_r16 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -537,11 +528,7 @@ smaxloc1_4_r16 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxloc1_4_r17.c b/libgfortran/generated/maxloc1_4_r17.c
index 10c6875218853888a8d6236e74bf972b691e8cf9..a0e43b50b9677ced5f26ae6d029399dd5238142e 100644
--- a/libgfortran/generated/maxloc1_4_r17.c
+++ b/libgfortran/generated/maxloc1_4_r17.c
@@ -109,12 +109,7 @@ maxloc1_4_r17 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -331,11 +326,7 @@ mmaxloc1_4_r17 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -537,11 +528,7 @@ smaxloc1_4_r17 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxloc1_4_r4.c b/libgfortran/generated/maxloc1_4_r4.c
index b0750c19361a2886e192e4376aa257398d02d67f..f79c7ffc4e080b39978ebdbe441f7de4a1832024 100644
--- a/libgfortran/generated/maxloc1_4_r4.c
+++ b/libgfortran/generated/maxloc1_4_r4.c
@@ -109,12 +109,7 @@ maxloc1_4_r4 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -331,11 +326,7 @@ mmaxloc1_4_r4 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -537,11 +528,7 @@ smaxloc1_4_r4 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxloc1_4_r8.c b/libgfortran/generated/maxloc1_4_r8.c
index 3be87685eed7d02f6704fec0ddcef6f76a3983c7..c77b72074b3434b847b705e9a251bb2f2385fa3b 100644
--- a/libgfortran/generated/maxloc1_4_r8.c
+++ b/libgfortran/generated/maxloc1_4_r8.c
@@ -109,12 +109,7 @@ maxloc1_4_r8 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -331,11 +326,7 @@ mmaxloc1_4_r8 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -537,11 +528,7 @@ smaxloc1_4_r8 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxloc1_4_s1.c b/libgfortran/generated/maxloc1_4_s1.c
index 91628645d1cbdf5d9bd58a7f56fc0f20a101b459..d1657b82cd86c9039b0156336a91b68979645fb4 100644
--- a/libgfortran/generated/maxloc1_4_s1.c
+++ b/libgfortran/generated/maxloc1_4_s1.c
@@ -121,12 +121,7 @@ maxloc1_4_s1 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -324,11 +319,7 @@ mmaxloc1_4_s1 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -503,11 +494,7 @@ smaxloc1_4_s1 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxloc1_4_s4.c b/libgfortran/generated/maxloc1_4_s4.c
index 7cb056ea10b1ac6fab2bd50c01ca490c5ce5827e..7727c21847c070e4e90d1a71bf4cb812a5a68011 100644
--- a/libgfortran/generated/maxloc1_4_s4.c
+++ b/libgfortran/generated/maxloc1_4_s4.c
@@ -121,12 +121,7 @@ maxloc1_4_s4 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -324,11 +319,7 @@ mmaxloc1_4_s4 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -503,11 +494,7 @@ smaxloc1_4_s4 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxloc1_8_i1.c b/libgfortran/generated/maxloc1_8_i1.c
index 42b113b1d0cfd133ec6b98fe9bf2d628a294ea43..4ab9d741f150159d55e1274eb69dd2bed7d914e7 100644
--- a/libgfortran/generated/maxloc1_8_i1.c
+++ b/libgfortran/generated/maxloc1_8_i1.c
@@ -109,12 +109,7 @@ maxloc1_8_i1 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -331,11 +326,7 @@ mmaxloc1_8_i1 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -537,11 +528,7 @@ smaxloc1_8_i1 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxloc1_8_i16.c b/libgfortran/generated/maxloc1_8_i16.c
index 594c735ad77e7d49f7197a4f43db546eec050cc0..817a7770130f7dce844236ca7737224593e2e12a 100644
--- a/libgfortran/generated/maxloc1_8_i16.c
+++ b/libgfortran/generated/maxloc1_8_i16.c
@@ -109,12 +109,7 @@ maxloc1_8_i16 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -331,11 +326,7 @@ mmaxloc1_8_i16 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -537,11 +528,7 @@ smaxloc1_8_i16 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxloc1_8_i2.c b/libgfortran/generated/maxloc1_8_i2.c
index 9e141af3ecd4cbe8ae304fe9bd5eed74873801f6..57d40b5b52c1efd6889c3e2b4ecad106c80e0b80 100644
--- a/libgfortran/generated/maxloc1_8_i2.c
+++ b/libgfortran/generated/maxloc1_8_i2.c
@@ -109,12 +109,7 @@ maxloc1_8_i2 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -331,11 +326,7 @@ mmaxloc1_8_i2 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -537,11 +528,7 @@ smaxloc1_8_i2 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxloc1_8_i4.c b/libgfortran/generated/maxloc1_8_i4.c
index b94c627dfd6742c688fd0f33dec404b6c3d8b49c..451f860495cec651721e8c15027d9bc1fba45714 100644
--- a/libgfortran/generated/maxloc1_8_i4.c
+++ b/libgfortran/generated/maxloc1_8_i4.c
@@ -109,12 +109,7 @@ maxloc1_8_i4 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -331,11 +326,7 @@ mmaxloc1_8_i4 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -537,11 +528,7 @@ smaxloc1_8_i4 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxloc1_8_i8.c b/libgfortran/generated/maxloc1_8_i8.c
index 18e45033b40a73b9f775aaee3f29d371677c6750..5f5dbd4831116f4b08281a2ebc7cefc2671c0cee 100644
--- a/libgfortran/generated/maxloc1_8_i8.c
+++ b/libgfortran/generated/maxloc1_8_i8.c
@@ -109,12 +109,7 @@ maxloc1_8_i8 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -331,11 +326,7 @@ mmaxloc1_8_i8 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -537,11 +528,7 @@ smaxloc1_8_i8 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxloc1_8_r10.c b/libgfortran/generated/maxloc1_8_r10.c
index 22cd8c26e1bba5cdcc3e1c9531a5e6170e25d03a..78928f83937d3d9547167717d7d65bc89a661584 100644
--- a/libgfortran/generated/maxloc1_8_r10.c
+++ b/libgfortran/generated/maxloc1_8_r10.c
@@ -109,12 +109,7 @@ maxloc1_8_r10 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -331,11 +326,7 @@ mmaxloc1_8_r10 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -537,11 +528,7 @@ smaxloc1_8_r10 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxloc1_8_r16.c b/libgfortran/generated/maxloc1_8_r16.c
index 646fe18a97505d702ed9d23e73fabcb053d5c9ac..5eb1e51d6b26836c5486c94922096d4c1a2336f3 100644
--- a/libgfortran/generated/maxloc1_8_r16.c
+++ b/libgfortran/generated/maxloc1_8_r16.c
@@ -109,12 +109,7 @@ maxloc1_8_r16 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -331,11 +326,7 @@ mmaxloc1_8_r16 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -537,11 +528,7 @@ smaxloc1_8_r16 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxloc1_8_r17.c b/libgfortran/generated/maxloc1_8_r17.c
index cc6bb86546c1392071b6bdb572874a9d802cdbb2..3662425c36b352d3064728887c4fcaf2d00340bf 100644
--- a/libgfortran/generated/maxloc1_8_r17.c
+++ b/libgfortran/generated/maxloc1_8_r17.c
@@ -109,12 +109,7 @@ maxloc1_8_r17 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -331,11 +326,7 @@ mmaxloc1_8_r17 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -537,11 +528,7 @@ smaxloc1_8_r17 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxloc1_8_r4.c b/libgfortran/generated/maxloc1_8_r4.c
index 2c482bc8ed4c1b8c2ad1e7c6683c2a3876a54927..8d697713705a2343ed93d720105ba82af7984454 100644
--- a/libgfortran/generated/maxloc1_8_r4.c
+++ b/libgfortran/generated/maxloc1_8_r4.c
@@ -109,12 +109,7 @@ maxloc1_8_r4 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -331,11 +326,7 @@ mmaxloc1_8_r4 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -537,11 +528,7 @@ smaxloc1_8_r4 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxloc1_8_r8.c b/libgfortran/generated/maxloc1_8_r8.c
index 32452d49ff3c377b4ccfed05ba4cfd1650bb02e3..72651d0667667ae980bf0d33c2cfbae4949b7f52 100644
--- a/libgfortran/generated/maxloc1_8_r8.c
+++ b/libgfortran/generated/maxloc1_8_r8.c
@@ -109,12 +109,7 @@ maxloc1_8_r8 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -331,11 +326,7 @@ mmaxloc1_8_r8 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -537,11 +528,7 @@ smaxloc1_8_r8 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxloc1_8_s1.c b/libgfortran/generated/maxloc1_8_s1.c
index 96ac1ac0bd4aea1e29e1a96e2486fcb5c4e42657..97fe4890df6a3af6b21fa4305d6a08c2eaf65a85 100644
--- a/libgfortran/generated/maxloc1_8_s1.c
+++ b/libgfortran/generated/maxloc1_8_s1.c
@@ -121,12 +121,7 @@ maxloc1_8_s1 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -324,11 +319,7 @@ mmaxloc1_8_s1 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -503,11 +494,7 @@ smaxloc1_8_s1 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxloc1_8_s4.c b/libgfortran/generated/maxloc1_8_s4.c
index 068c4ff7a725cae353ae27e7b3ee904a6d51f43a..519e4cb6c11c32c80ab11bc2d7ed1c30a1bfb347 100644
--- a/libgfortran/generated/maxloc1_8_s4.c
+++ b/libgfortran/generated/maxloc1_8_s4.c
@@ -121,12 +121,7 @@ maxloc1_8_s4 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -324,11 +319,7 @@ mmaxloc1_8_s4 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -503,11 +494,7 @@ smaxloc1_8_s4 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxval1_s1.c b/libgfortran/generated/maxval1_s1.c
index 6ad5366b8f36efec0ddda4ce07d21195cfc1aa98..19579023e2944849d702588df1250297338e1efb 100644
--- a/libgfortran/generated/maxval1_s1.c
+++ b/libgfortran/generated/maxval1_s1.c
@@ -121,12 +121,7 @@ maxval1_s1 (gfc_array_s1 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_UINTEGER_1));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -320,11 +315,7 @@ mmaxval1_s1 (gfc_array_s1 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_UINTEGER_1));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -496,11 +487,7 @@ smaxval1_s1 (gfc_array_s1 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_UINTEGER_1));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxval1_s4.c b/libgfortran/generated/maxval1_s4.c
index 6337b043a3ef62e59651cb9fcf19cd149c53969f..501e605b0333f29937bc7f28d75ad11c6b5f33b1 100644
--- a/libgfortran/generated/maxval1_s4.c
+++ b/libgfortran/generated/maxval1_s4.c
@@ -121,12 +121,7 @@ maxval1_s4 (gfc_array_s4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_UINTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -320,11 +315,7 @@ mmaxval1_s4 (gfc_array_s4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_UINTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -496,11 +487,7 @@ smaxval1_s4 (gfc_array_s4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_UINTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxval_i1.c b/libgfortran/generated/maxval_i1.c
index 19feced686187fe77a25f1b11704e218dc608ec0..a500d5dd4ff3154804da334406563315440389a4 100644
--- a/libgfortran/generated/maxval_i1.c
+++ b/libgfortran/generated/maxval_i1.c
@@ -106,12 +106,7 @@ maxval_i1 (gfc_array_i1 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_1));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -317,11 +312,7 @@ mmaxval_i1 (gfc_array_i1 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_1));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -508,11 +499,7 @@ smaxval_i1 (gfc_array_i1 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_1));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxval_i16.c b/libgfortran/generated/maxval_i16.c
index cd75603b0660bcfdc0105b521d0822e14744bd69..9833337b5530ae17a11926fc6cc5a14e3cc3d792 100644
--- a/libgfortran/generated/maxval_i16.c
+++ b/libgfortran/generated/maxval_i16.c
@@ -106,12 +106,7 @@ maxval_i16 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -317,11 +312,7 @@ mmaxval_i16 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -508,11 +499,7 @@ smaxval_i16 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxval_i2.c b/libgfortran/generated/maxval_i2.c
index 9c7eb7702e3edf781112ac26cbd9b0dc661eaa77..d3d4b6adbcb4864a02ca841de66f1ecb2b608647 100644
--- a/libgfortran/generated/maxval_i2.c
+++ b/libgfortran/generated/maxval_i2.c
@@ -106,12 +106,7 @@ maxval_i2 (gfc_array_i2 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_2));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -317,11 +312,7 @@ mmaxval_i2 (gfc_array_i2 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_2));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -508,11 +499,7 @@ smaxval_i2 (gfc_array_i2 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_2));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxval_i4.c b/libgfortran/generated/maxval_i4.c
index 40bf1ce97ab2ef26570a571ae0ac97e199a031fa..b6c6504825bf1a5cbb4531b09dd72dfc8017690e 100644
--- a/libgfortran/generated/maxval_i4.c
+++ b/libgfortran/generated/maxval_i4.c
@@ -106,12 +106,7 @@ maxval_i4 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -317,11 +312,7 @@ mmaxval_i4 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -508,11 +499,7 @@ smaxval_i4 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxval_i8.c b/libgfortran/generated/maxval_i8.c
index 0b6b9f671ee96d27c0b5f619d9031e56e25c046f..418b5b684eb80e24353a79063c86de84935ed91c 100644
--- a/libgfortran/generated/maxval_i8.c
+++ b/libgfortran/generated/maxval_i8.c
@@ -106,12 +106,7 @@ maxval_i8 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -317,11 +312,7 @@ mmaxval_i8 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -508,11 +499,7 @@ smaxval_i8 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxval_r10.c b/libgfortran/generated/maxval_r10.c
index f83c4e9965a042da0e1e52ce9948ae9a8dad74f1..486c16c2f297a7fbb68fb26d8509de9648b3d251 100644
--- a/libgfortran/generated/maxval_r10.c
+++ b/libgfortran/generated/maxval_r10.c
@@ -106,12 +106,7 @@ maxval_r10 (gfc_array_r10 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_10));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -317,11 +312,7 @@ mmaxval_r10 (gfc_array_r10 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_10));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -508,11 +499,7 @@ smaxval_r10 (gfc_array_r10 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_10));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxval_r16.c b/libgfortran/generated/maxval_r16.c
index ec2d7a92be58fc323f4257714a6b0fe8e1aad5e5..dd9b42754949ff881c67c7bc2f13d2344a276fab 100644
--- a/libgfortran/generated/maxval_r16.c
+++ b/libgfortran/generated/maxval_r16.c
@@ -106,12 +106,7 @@ maxval_r16 (gfc_array_r16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -317,11 +312,7 @@ mmaxval_r16 (gfc_array_r16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -508,11 +499,7 @@ smaxval_r16 (gfc_array_r16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxval_r17.c b/libgfortran/generated/maxval_r17.c
index 442e2b3a387548c3779e2c653f00c409340e6774..feda95e35d0c12de8cfb4da8756af048f7a48028 100644
--- a/libgfortran/generated/maxval_r17.c
+++ b/libgfortran/generated/maxval_r17.c
@@ -106,12 +106,7 @@ maxval_r17 (gfc_array_r17 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_17));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -317,11 +312,7 @@ mmaxval_r17 (gfc_array_r17 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_17));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -508,11 +499,7 @@ smaxval_r17 (gfc_array_r17 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_17));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxval_r4.c b/libgfortran/generated/maxval_r4.c
index 6c08b342752a216453214dcd8bf6291e728683ab..6e1b4fa61d584c78327fe490255f7121c147fd8d 100644
--- a/libgfortran/generated/maxval_r4.c
+++ b/libgfortran/generated/maxval_r4.c
@@ -106,12 +106,7 @@ maxval_r4 (gfc_array_r4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -317,11 +312,7 @@ mmaxval_r4 (gfc_array_r4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -508,11 +499,7 @@ smaxval_r4 (gfc_array_r4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/maxval_r8.c b/libgfortran/generated/maxval_r8.c
index 30d259f7708a8b2e7e3b380f132db141296ebac4..2f78627e5e8320f47e9a54c154aa568869e87deb 100644
--- a/libgfortran/generated/maxval_r8.c
+++ b/libgfortran/generated/maxval_r8.c
@@ -106,12 +106,7 @@ maxval_r8 (gfc_array_r8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -317,11 +312,7 @@ mmaxval_r8 (gfc_array_r8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -508,11 +499,7 @@ smaxval_r8 (gfc_array_r8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minloc1_16_i1.c b/libgfortran/generated/minloc1_16_i1.c
index 80abb3cf8e06235db476ec0165767ae6d64ba4dd..bf3daefbcf950e9adca49c68c03187ffc8e25948 100644
--- a/libgfortran/generated/minloc1_16_i1.c
+++ b/libgfortran/generated/minloc1_16_i1.c
@@ -109,12 +109,7 @@ minloc1_16_i1 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -341,11 +336,7 @@ mminloc1_16_i1 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -547,11 +538,7 @@ sminloc1_16_i1 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minloc1_16_i16.c b/libgfortran/generated/minloc1_16_i16.c
index 388a8f912084d23170a1661b169ce25cd5d4d5ab..7a7e3433d640b4e9349d755b79b02b80ae7fa104 100644
--- a/libgfortran/generated/minloc1_16_i16.c
+++ b/libgfortran/generated/minloc1_16_i16.c
@@ -109,12 +109,7 @@ minloc1_16_i16 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -341,11 +336,7 @@ mminloc1_16_i16 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -547,11 +538,7 @@ sminloc1_16_i16 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minloc1_16_i2.c b/libgfortran/generated/minloc1_16_i2.c
index 51ae92b91fba794d5668c8980699efc92213763e..c66d21fdc811d4db5c278959ba00cd0cf4ef19de 100644
--- a/libgfortran/generated/minloc1_16_i2.c
+++ b/libgfortran/generated/minloc1_16_i2.c
@@ -109,12 +109,7 @@ minloc1_16_i2 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -341,11 +336,7 @@ mminloc1_16_i2 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -547,11 +538,7 @@ sminloc1_16_i2 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minloc1_16_i4.c b/libgfortran/generated/minloc1_16_i4.c
index 675fc333d52cc634ffad046005ac08f67642d7f9..9138ec417d1bea4e3e72a3491c35ea2cb25ce071 100644
--- a/libgfortran/generated/minloc1_16_i4.c
+++ b/libgfortran/generated/minloc1_16_i4.c
@@ -109,12 +109,7 @@ minloc1_16_i4 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -341,11 +336,7 @@ mminloc1_16_i4 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -547,11 +538,7 @@ sminloc1_16_i4 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minloc1_16_i8.c b/libgfortran/generated/minloc1_16_i8.c
index 6a417880a12b44859fc21b91ab90f4b52a245945..c974954e86b7bc5e316282b87b42416df0f73384 100644
--- a/libgfortran/generated/minloc1_16_i8.c
+++ b/libgfortran/generated/minloc1_16_i8.c
@@ -109,12 +109,7 @@ minloc1_16_i8 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -341,11 +336,7 @@ mminloc1_16_i8 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -547,11 +538,7 @@ sminloc1_16_i8 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minloc1_16_r10.c b/libgfortran/generated/minloc1_16_r10.c
index f5d9c347ef950f063422b421b409055ac084e99c..3f6c59a8532ef4f5f980ca19fcbe11dae1bf4d88 100644
--- a/libgfortran/generated/minloc1_16_r10.c
+++ b/libgfortran/generated/minloc1_16_r10.c
@@ -109,12 +109,7 @@ minloc1_16_r10 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -341,11 +336,7 @@ mminloc1_16_r10 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -547,11 +538,7 @@ sminloc1_16_r10 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minloc1_16_r16.c b/libgfortran/generated/minloc1_16_r16.c
index 3405c0e4befe343686cf27a1ccebe22adec5b7df..18cd4c6155ec3df9c825227316d9cb15b4f12be8 100644
--- a/libgfortran/generated/minloc1_16_r16.c
+++ b/libgfortran/generated/minloc1_16_r16.c
@@ -109,12 +109,7 @@ minloc1_16_r16 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -341,11 +336,7 @@ mminloc1_16_r16 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -547,11 +538,7 @@ sminloc1_16_r16 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minloc1_16_r17.c b/libgfortran/generated/minloc1_16_r17.c
index e3d0d417e5de6776089199d92d75170133475dcc..02b252b64e7d34ac19b06d6b27cfdef3b3fa78ed 100644
--- a/libgfortran/generated/minloc1_16_r17.c
+++ b/libgfortran/generated/minloc1_16_r17.c
@@ -109,12 +109,7 @@ minloc1_16_r17 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -341,11 +336,7 @@ mminloc1_16_r17 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -547,11 +538,7 @@ sminloc1_16_r17 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minloc1_16_r4.c b/libgfortran/generated/minloc1_16_r4.c
index 8af09702f5ca4f1d289c7c3e29163b39f6019862..b6d5e53c8fe00d2c40ac931165b877d2def2fbe3 100644
--- a/libgfortran/generated/minloc1_16_r4.c
+++ b/libgfortran/generated/minloc1_16_r4.c
@@ -109,12 +109,7 @@ minloc1_16_r4 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -341,11 +336,7 @@ mminloc1_16_r4 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -547,11 +538,7 @@ sminloc1_16_r4 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minloc1_16_r8.c b/libgfortran/generated/minloc1_16_r8.c
index 9397dc6ff917076c2c9cc72b4e0f3543e4596ad2..6b879bf7c9d9c17aa87a87e304b60d87c3d15cbd 100644
--- a/libgfortran/generated/minloc1_16_r8.c
+++ b/libgfortran/generated/minloc1_16_r8.c
@@ -109,12 +109,7 @@ minloc1_16_r8 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -341,11 +336,7 @@ mminloc1_16_r8 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -547,11 +538,7 @@ sminloc1_16_r8 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minloc1_16_s1.c b/libgfortran/generated/minloc1_16_s1.c
index c6d8861a5f48eadb1e9d6f2889ad4b82cb9ba2c5..d6c41c967ab362d31aa985f470413d3da5f84520 100644
--- a/libgfortran/generated/minloc1_16_s1.c
+++ b/libgfortran/generated/minloc1_16_s1.c
@@ -121,12 +121,7 @@ minloc1_16_s1 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -324,11 +319,7 @@ mminloc1_16_s1 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -503,11 +494,7 @@ sminloc1_16_s1 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minloc1_16_s4.c b/libgfortran/generated/minloc1_16_s4.c
index 0f5eb2db869638c6741fe60721c4f9886ff0bbcf..ef67757329ffaee6b839f78050919e72bf3ce463 100644
--- a/libgfortran/generated/minloc1_16_s4.c
+++ b/libgfortran/generated/minloc1_16_s4.c
@@ -121,12 +121,7 @@ minloc1_16_s4 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -324,11 +319,7 @@ mminloc1_16_s4 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -503,11 +494,7 @@ sminloc1_16_s4 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minloc1_4_i1.c b/libgfortran/generated/minloc1_4_i1.c
index 4274e70dc921aa49c2d673f905342c942607c96a..79843660216eb74cde8bd2a0feddf0ab630804d8 100644
--- a/libgfortran/generated/minloc1_4_i1.c
+++ b/libgfortran/generated/minloc1_4_i1.c
@@ -109,12 +109,7 @@ minloc1_4_i1 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -341,11 +336,7 @@ mminloc1_4_i1 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -547,11 +538,7 @@ sminloc1_4_i1 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minloc1_4_i16.c b/libgfortran/generated/minloc1_4_i16.c
index ded68f0b0fb5a00b28a3384c221a7607ca35cd09..0c1170a2234fc0ff643be3879922261cfcd7c4f0 100644
--- a/libgfortran/generated/minloc1_4_i16.c
+++ b/libgfortran/generated/minloc1_4_i16.c
@@ -109,12 +109,7 @@ minloc1_4_i16 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -341,11 +336,7 @@ mminloc1_4_i16 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -547,11 +538,7 @@ sminloc1_4_i16 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minloc1_4_i2.c b/libgfortran/generated/minloc1_4_i2.c
index a053dd352e56657100263c4c8821b9774094f421..3bc567c44ebfa3e1669759cb2f735c0937e917f0 100644
--- a/libgfortran/generated/minloc1_4_i2.c
+++ b/libgfortran/generated/minloc1_4_i2.c
@@ -109,12 +109,7 @@ minloc1_4_i2 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -341,11 +336,7 @@ mminloc1_4_i2 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -547,11 +538,7 @@ sminloc1_4_i2 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minloc1_4_i4.c b/libgfortran/generated/minloc1_4_i4.c
index 6292fc2d9b77a59266047e3f897fcae9b056a877..7d82a18d757e16f2884681024e8746391737916b 100644
--- a/libgfortran/generated/minloc1_4_i4.c
+++ b/libgfortran/generated/minloc1_4_i4.c
@@ -109,12 +109,7 @@ minloc1_4_i4 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -341,11 +336,7 @@ mminloc1_4_i4 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -547,11 +538,7 @@ sminloc1_4_i4 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minloc1_4_i8.c b/libgfortran/generated/minloc1_4_i8.c
index 9240e3fe5bda7bacdb1c2b4cac070b2d64f27cbf..cb6836bb32b042a6520291eb7d86e139946e3e92 100644
--- a/libgfortran/generated/minloc1_4_i8.c
+++ b/libgfortran/generated/minloc1_4_i8.c
@@ -109,12 +109,7 @@ minloc1_4_i8 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -341,11 +336,7 @@ mminloc1_4_i8 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -547,11 +538,7 @@ sminloc1_4_i8 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minloc1_4_r10.c b/libgfortran/generated/minloc1_4_r10.c
index 42a9de0b6d0426675017230dccc925b791ac9daa..e7f1a1cd446ab41f335610b18e6f991dbf360574 100644
--- a/libgfortran/generated/minloc1_4_r10.c
+++ b/libgfortran/generated/minloc1_4_r10.c
@@ -109,12 +109,7 @@ minloc1_4_r10 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -341,11 +336,7 @@ mminloc1_4_r10 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -547,11 +538,7 @@ sminloc1_4_r10 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minloc1_4_r16.c b/libgfortran/generated/minloc1_4_r16.c
index 06193f13598ed7373ed2dfff8d04e1cfa66c5a22..c0938cd715eb308dcc90f07f3c82aa81064a4df0 100644
--- a/libgfortran/generated/minloc1_4_r16.c
+++ b/libgfortran/generated/minloc1_4_r16.c
@@ -109,12 +109,7 @@ minloc1_4_r16 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -341,11 +336,7 @@ mminloc1_4_r16 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -547,11 +538,7 @@ sminloc1_4_r16 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minloc1_4_r17.c b/libgfortran/generated/minloc1_4_r17.c
index d021d46b9fadfc1d73061ebe49e8bd588a9d5783..a2b8ad2fb030e63bd259430802fdd6f90371e918 100644
--- a/libgfortran/generated/minloc1_4_r17.c
+++ b/libgfortran/generated/minloc1_4_r17.c
@@ -109,12 +109,7 @@ minloc1_4_r17 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -341,11 +336,7 @@ mminloc1_4_r17 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -547,11 +538,7 @@ sminloc1_4_r17 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minloc1_4_r4.c b/libgfortran/generated/minloc1_4_r4.c
index e6990c6e70e06a2e3bad3f42f8b54b3ffb7c0ef9..c55ab25d2f2cf0d5fb096e3a61189521dccb04a0 100644
--- a/libgfortran/generated/minloc1_4_r4.c
+++ b/libgfortran/generated/minloc1_4_r4.c
@@ -109,12 +109,7 @@ minloc1_4_r4 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -341,11 +336,7 @@ mminloc1_4_r4 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -547,11 +538,7 @@ sminloc1_4_r4 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minloc1_4_r8.c b/libgfortran/generated/minloc1_4_r8.c
index fd1574f64139654972d1c82e21dc3c9f9b07140e..8c149a87ef60a588baa41817c7cc3fcdf5edf0cf 100644
--- a/libgfortran/generated/minloc1_4_r8.c
+++ b/libgfortran/generated/minloc1_4_r8.c
@@ -109,12 +109,7 @@ minloc1_4_r8 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -341,11 +336,7 @@ mminloc1_4_r8 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -547,11 +538,7 @@ sminloc1_4_r8 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minloc1_4_s1.c b/libgfortran/generated/minloc1_4_s1.c
index 5bbc844e196321cbf8c625df76d780c7b838cfc4..54a656e9649eedfa13cd3fae70f01d7b5174b7a4 100644
--- a/libgfortran/generated/minloc1_4_s1.c
+++ b/libgfortran/generated/minloc1_4_s1.c
@@ -121,12 +121,7 @@ minloc1_4_s1 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -324,11 +319,7 @@ mminloc1_4_s1 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -503,11 +494,7 @@ sminloc1_4_s1 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minloc1_4_s4.c b/libgfortran/generated/minloc1_4_s4.c
index 4f2ab20ab9f469ebe89740db555c99b1a075cf4b..fedddac374c9e6d508c08407bc3512e087e9f460 100644
--- a/libgfortran/generated/minloc1_4_s4.c
+++ b/libgfortran/generated/minloc1_4_s4.c
@@ -121,12 +121,7 @@ minloc1_4_s4 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -324,11 +319,7 @@ mminloc1_4_s4 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -503,11 +494,7 @@ sminloc1_4_s4 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minloc1_8_i1.c b/libgfortran/generated/minloc1_8_i1.c
index 1b8b24064d9522cbd5a58d511454155c75c193b9..17f2e0cbab258c78c3eb5ef6115704f7b90f4218 100644
--- a/libgfortran/generated/minloc1_8_i1.c
+++ b/libgfortran/generated/minloc1_8_i1.c
@@ -109,12 +109,7 @@ minloc1_8_i1 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -341,11 +336,7 @@ mminloc1_8_i1 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -547,11 +538,7 @@ sminloc1_8_i1 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minloc1_8_i16.c b/libgfortran/generated/minloc1_8_i16.c
index 9561270e15024020f3783f9fe90d12e85cabe0ed..be829bc255b896c87c536b4dc12ca4b63fd475ab 100644
--- a/libgfortran/generated/minloc1_8_i16.c
+++ b/libgfortran/generated/minloc1_8_i16.c
@@ -109,12 +109,7 @@ minloc1_8_i16 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -341,11 +336,7 @@ mminloc1_8_i16 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -547,11 +538,7 @@ sminloc1_8_i16 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minloc1_8_i2.c b/libgfortran/generated/minloc1_8_i2.c
index 979856579f98bc05fc6400fd9da478d9175f4f0a..9a3c8e8785821cb9e53648d5fb331d5e13440b33 100644
--- a/libgfortran/generated/minloc1_8_i2.c
+++ b/libgfortran/generated/minloc1_8_i2.c
@@ -109,12 +109,7 @@ minloc1_8_i2 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -341,11 +336,7 @@ mminloc1_8_i2 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -547,11 +538,7 @@ sminloc1_8_i2 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minloc1_8_i4.c b/libgfortran/generated/minloc1_8_i4.c
index 1c303ed6dea38a30af3103cc6077375434eb4c40..47c8547bdb930734d310b3fffed1cebd58fc85b5 100644
--- a/libgfortran/generated/minloc1_8_i4.c
+++ b/libgfortran/generated/minloc1_8_i4.c
@@ -109,12 +109,7 @@ minloc1_8_i4 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -341,11 +336,7 @@ mminloc1_8_i4 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -547,11 +538,7 @@ sminloc1_8_i4 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minloc1_8_i8.c b/libgfortran/generated/minloc1_8_i8.c
index 6249f20ae62d559cb6615a37fc0ca1cd26cd3395..ca2546699f6e0beb073f7fceeabcfbc2b30b2196 100644
--- a/libgfortran/generated/minloc1_8_i8.c
+++ b/libgfortran/generated/minloc1_8_i8.c
@@ -109,12 +109,7 @@ minloc1_8_i8 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -341,11 +336,7 @@ mminloc1_8_i8 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -547,11 +538,7 @@ sminloc1_8_i8 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minloc1_8_r10.c b/libgfortran/generated/minloc1_8_r10.c
index 2c6a0fd8a58b5ceefe66c7564c721001115f3cb0..e4103588f49dfb1fe40d2d41820cecae62f05623 100644
--- a/libgfortran/generated/minloc1_8_r10.c
+++ b/libgfortran/generated/minloc1_8_r10.c
@@ -109,12 +109,7 @@ minloc1_8_r10 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -341,11 +336,7 @@ mminloc1_8_r10 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -547,11 +538,7 @@ sminloc1_8_r10 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minloc1_8_r16.c b/libgfortran/generated/minloc1_8_r16.c
index f7d06648c37907170e9be01d30949a1dc99a7bb2..db9c163dd145a6eb77f4d11af4601888938d6846 100644
--- a/libgfortran/generated/minloc1_8_r16.c
+++ b/libgfortran/generated/minloc1_8_r16.c
@@ -109,12 +109,7 @@ minloc1_8_r16 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -341,11 +336,7 @@ mminloc1_8_r16 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -547,11 +538,7 @@ sminloc1_8_r16 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minloc1_8_r17.c b/libgfortran/generated/minloc1_8_r17.c
index 0cc70c439d0d9c3025ced684b47c3cc31d6f59c0..65241e7b19e08f68414363dda70764fa28fcb893 100644
--- a/libgfortran/generated/minloc1_8_r17.c
+++ b/libgfortran/generated/minloc1_8_r17.c
@@ -109,12 +109,7 @@ minloc1_8_r17 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -341,11 +336,7 @@ mminloc1_8_r17 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -547,11 +538,7 @@ sminloc1_8_r17 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minloc1_8_r4.c b/libgfortran/generated/minloc1_8_r4.c
index b2ae3dfcc06ab28e22ea05ec567874945e1f3c47..f76e79d857acff6fc55ad4768fd3b7a557505ae9 100644
--- a/libgfortran/generated/minloc1_8_r4.c
+++ b/libgfortran/generated/minloc1_8_r4.c
@@ -109,12 +109,7 @@ minloc1_8_r4 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -341,11 +336,7 @@ mminloc1_8_r4 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -547,11 +538,7 @@ sminloc1_8_r4 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minloc1_8_r8.c b/libgfortran/generated/minloc1_8_r8.c
index bafd72d0893a6c50d9d839ec75d1def25d53f600..730774e910cf122e28350ab0eef8ea0b7893aa1b 100644
--- a/libgfortran/generated/minloc1_8_r8.c
+++ b/libgfortran/generated/minloc1_8_r8.c
@@ -109,12 +109,7 @@ minloc1_8_r8 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -341,11 +336,7 @@ mminloc1_8_r8 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -547,11 +538,7 @@ sminloc1_8_r8 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minloc1_8_s1.c b/libgfortran/generated/minloc1_8_s1.c
index 8a40b52a188f1e2462999aebeb822c4cc5d512cb..188a8963a789b06490c6eed143bca3d68dbc4dec 100644
--- a/libgfortran/generated/minloc1_8_s1.c
+++ b/libgfortran/generated/minloc1_8_s1.c
@@ -121,12 +121,7 @@ minloc1_8_s1 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -324,11 +319,7 @@ mminloc1_8_s1 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -503,11 +494,7 @@ sminloc1_8_s1 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minloc1_8_s4.c b/libgfortran/generated/minloc1_8_s4.c
index 906d1df9a2e2f2de4b371ef74116113dd263d536..f7930de0643674b639a86f3f6ff806bc93870376 100644
--- a/libgfortran/generated/minloc1_8_s4.c
+++ b/libgfortran/generated/minloc1_8_s4.c
@@ -121,12 +121,7 @@ minloc1_8_s4 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -324,11 +319,7 @@ mminloc1_8_s4 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -503,11 +494,7 @@ sminloc1_8_s4 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minval1_s1.c b/libgfortran/generated/minval1_s1.c
index d83fef19d3c8c968cd75948e8ca53ec252409301..859530f16e53d153a4984f14c6123807b503cebb 100644
--- a/libgfortran/generated/minval1_s1.c
+++ b/libgfortran/generated/minval1_s1.c
@@ -121,12 +121,7 @@ minval1_s1 (gfc_array_s1 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_UINTEGER_1));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -320,11 +315,7 @@ mminval1_s1 (gfc_array_s1 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_UINTEGER_1));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -496,11 +487,7 @@ sminval1_s1 (gfc_array_s1 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_UINTEGER_1));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minval1_s4.c b/libgfortran/generated/minval1_s4.c
index 5ef09cdeebb60a6560a33eb72f69586248fa58fa..d6b5ab6d359a1d7fb60686f68dc03f82a9093e03 100644
--- a/libgfortran/generated/minval1_s4.c
+++ b/libgfortran/generated/minval1_s4.c
@@ -121,12 +121,7 @@ minval1_s4 (gfc_array_s4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_UINTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -320,11 +315,7 @@ mminval1_s4 (gfc_array_s4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_UINTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -496,11 +487,7 @@ sminval1_s4 (gfc_array_s4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_UINTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minval_i1.c b/libgfortran/generated/minval_i1.c
index 544a996a01c31291335990e8a9ddffc2cd716895..5972e6c2164460cb9a69763e8dbd765ce40691fe 100644
--- a/libgfortran/generated/minval_i1.c
+++ b/libgfortran/generated/minval_i1.c
@@ -106,12 +106,7 @@ minval_i1 (gfc_array_i1 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_1));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -317,11 +312,7 @@ mminval_i1 (gfc_array_i1 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_1));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -508,11 +499,7 @@ sminval_i1 (gfc_array_i1 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_1));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minval_i16.c b/libgfortran/generated/minval_i16.c
index 1bcdf58792ac5af69c192306a9972b65a2154474..28053b9606b031b352347ffda29f4f553c3920d4 100644
--- a/libgfortran/generated/minval_i16.c
+++ b/libgfortran/generated/minval_i16.c
@@ -106,12 +106,7 @@ minval_i16 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -317,11 +312,7 @@ mminval_i16 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -508,11 +499,7 @@ sminval_i16 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minval_i2.c b/libgfortran/generated/minval_i2.c
index 61801f163f28818adf86c5b9a9e307e8e20993f7..8284243db7f93e91548ed3f6e376174f7fb04827 100644
--- a/libgfortran/generated/minval_i2.c
+++ b/libgfortran/generated/minval_i2.c
@@ -106,12 +106,7 @@ minval_i2 (gfc_array_i2 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_2));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -317,11 +312,7 @@ mminval_i2 (gfc_array_i2 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_2));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -508,11 +499,7 @@ sminval_i2 (gfc_array_i2 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_2));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minval_i4.c b/libgfortran/generated/minval_i4.c
index 019a880e2abe0af75b485713253de74bb113edc2..fb8385363716defa8616ab60461f59b8dbfc3122 100644
--- a/libgfortran/generated/minval_i4.c
+++ b/libgfortran/generated/minval_i4.c
@@ -106,12 +106,7 @@ minval_i4 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -317,11 +312,7 @@ mminval_i4 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -508,11 +499,7 @@ sminval_i4 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minval_i8.c b/libgfortran/generated/minval_i8.c
index abbbd06da07897533930547de69c83ee500c0f60..c43d13eef4fcbee771a29e3d478ba1b5cdec173c 100644
--- a/libgfortran/generated/minval_i8.c
+++ b/libgfortran/generated/minval_i8.c
@@ -106,12 +106,7 @@ minval_i8 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -317,11 +312,7 @@ mminval_i8 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -508,11 +499,7 @@ sminval_i8 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minval_r10.c b/libgfortran/generated/minval_r10.c
index d5b9d76d9e6af169e404dcce750dde62557d90bc..b28522a60fab9998e01871b63391a5d99adf5359 100644
--- a/libgfortran/generated/minval_r10.c
+++ b/libgfortran/generated/minval_r10.c
@@ -106,12 +106,7 @@ minval_r10 (gfc_array_r10 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_10));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -317,11 +312,7 @@ mminval_r10 (gfc_array_r10 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_10));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -508,11 +499,7 @@ sminval_r10 (gfc_array_r10 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_10));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minval_r16.c b/libgfortran/generated/minval_r16.c
index 9fdde79f4fcd19ec6be502c8e29608898f676633..75eb72b3347a1d91753feca6436a7ca56f617ee4 100644
--- a/libgfortran/generated/minval_r16.c
+++ b/libgfortran/generated/minval_r16.c
@@ -106,12 +106,7 @@ minval_r16 (gfc_array_r16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -317,11 +312,7 @@ mminval_r16 (gfc_array_r16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -508,11 +499,7 @@ sminval_r16 (gfc_array_r16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minval_r17.c b/libgfortran/generated/minval_r17.c
index 3e75af04b2da951002a0108490e8fad37d19f6dc..c3731489d8dbd4537b8b4f1b7a0c19f8da3e4d5f 100644
--- a/libgfortran/generated/minval_r17.c
+++ b/libgfortran/generated/minval_r17.c
@@ -106,12 +106,7 @@ minval_r17 (gfc_array_r17 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_17));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -317,11 +312,7 @@ mminval_r17 (gfc_array_r17 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_17));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -508,11 +499,7 @@ sminval_r17 (gfc_array_r17 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_17));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minval_r4.c b/libgfortran/generated/minval_r4.c
index f096473e5ad79f18c6cc1442b37c803c45f8ceb6..24d132ac0d1029413d50d490b10e9239168624d7 100644
--- a/libgfortran/generated/minval_r4.c
+++ b/libgfortran/generated/minval_r4.c
@@ -106,12 +106,7 @@ minval_r4 (gfc_array_r4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -317,11 +312,7 @@ mminval_r4 (gfc_array_r4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -508,11 +499,7 @@ sminval_r4 (gfc_array_r4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/minval_r8.c b/libgfortran/generated/minval_r8.c
index 8fafc3c1869d3dc3619e0fa1663f787fa4793a6d..c44a273f79e449f708b8b29967748f192cb63de4 100644
--- a/libgfortran/generated/minval_r8.c
+++ b/libgfortran/generated/minval_r8.c
@@ -106,12 +106,7 @@ minval_r8 (gfc_array_r8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -317,11 +312,7 @@ mminval_r8 (gfc_array_r8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -508,11 +499,7 @@ sminval_r8 (gfc_array_r8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/norm2_r10.c b/libgfortran/generated/norm2_r10.c
index c844ade8b21922a382575fd97f7a9262ee51c033..8afad2fe16ee2013c82a505f2bcba8fa0eb15f4f 100644
--- a/libgfortran/generated/norm2_r10.c
+++ b/libgfortran/generated/norm2_r10.c
@@ -109,12 +109,7 @@ norm2_r10 (gfc_array_r10 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_10));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/norm2_r16.c b/libgfortran/generated/norm2_r16.c
index 0d4f8deb15d3839fd76861a5bc90abf174b84d10..88ed972d75f2a3cd7d8ab6c7d7eb5eebffc15639 100644
--- a/libgfortran/generated/norm2_r16.c
+++ b/libgfortran/generated/norm2_r16.c
@@ -117,12 +117,7 @@ norm2_r16 (gfc_array_r16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/norm2_r17.c b/libgfortran/generated/norm2_r17.c
index 5a69e52bcd06a404841ae7d60e7852cb9f8736fe..9cef5cb3cc0ec0101fcecfbfa0c1a5a318b264f6 100644
--- a/libgfortran/generated/norm2_r17.c
+++ b/libgfortran/generated/norm2_r17.c
@@ -115,12 +115,7 @@ norm2_r17 (gfc_array_r17 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_17));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/norm2_r4.c b/libgfortran/generated/norm2_r4.c
index 2e023f08668dec701be949fb2014488743aaff8a..16e0e962f743ef189f3d2d08c677b59cdf96a9cb 100644
--- a/libgfortran/generated/norm2_r4.c
+++ b/libgfortran/generated/norm2_r4.c
@@ -109,12 +109,7 @@ norm2_r4 (gfc_array_r4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/norm2_r8.c b/libgfortran/generated/norm2_r8.c
index 5494eaef284ff1bc3b426f83e8331767ffe4cfca..5462f6186d2be581e1a2e1739cab41d009ee5c40 100644
--- a/libgfortran/generated/norm2_r8.c
+++ b/libgfortran/generated/norm2_r8.c
@@ -109,12 +109,7 @@ norm2_r8 (gfc_array_r8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/parity_l1.c b/libgfortran/generated/parity_l1.c
index e8ee6bd3baca0211dd7e2cc947a929c2355a0f8c..731b862091a8e83dcd8a05b0ca8e6a76d36e505c 100644
--- a/libgfortran/generated/parity_l1.c
+++ b/libgfortran/generated/parity_l1.c
@@ -106,12 +106,7 @@ parity_l1 (gfc_array_l1 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_LOGICAL_1));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/parity_l16.c b/libgfortran/generated/parity_l16.c
index 03707a234ad60c1e19657e77e506ca1abb5a5c8a..3dd883e328b501125aedf510b552c1c47a88d03c 100644
--- a/libgfortran/generated/parity_l16.c
+++ b/libgfortran/generated/parity_l16.c
@@ -106,12 +106,7 @@ parity_l16 (gfc_array_l16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_LOGICAL_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/parity_l2.c b/libgfortran/generated/parity_l2.c
index 00aa0245ed08b9d97abe4efae492d2c9502237a5..90cc272ffe099ad30878328136da4e2e1cdaa301 100644
--- a/libgfortran/generated/parity_l2.c
+++ b/libgfortran/generated/parity_l2.c
@@ -106,12 +106,7 @@ parity_l2 (gfc_array_l2 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_LOGICAL_2));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/parity_l4.c b/libgfortran/generated/parity_l4.c
index 08a1e433ad930899686fba467ef008baf31da805..108755982bfeeaecdd8151175ce07fd1798cf805 100644
--- a/libgfortran/generated/parity_l4.c
+++ b/libgfortran/generated/parity_l4.c
@@ -106,12 +106,7 @@ parity_l4 (gfc_array_l4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_LOGICAL_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/parity_l8.c b/libgfortran/generated/parity_l8.c
index a55e221c72c0e03f6e75c5f6747266af81571cca..8e3ddaae6661f1a59fd6fe81a107fa5cc30b7182 100644
--- a/libgfortran/generated/parity_l8.c
+++ b/libgfortran/generated/parity_l8.c
@@ -106,12 +106,7 @@ parity_l8 (gfc_array_l8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_LOGICAL_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/product_c10.c b/libgfortran/generated/product_c10.c
index 7ecd80e3346d921b08301489fb2ea8ab773dd9ab..b97353e1de984efef1f53ceda8bc142eb1f13f66 100644
--- a/libgfortran/generated/product_c10.c
+++ b/libgfortran/generated/product_c10.c
@@ -106,12 +106,7 @@ product_c10 (gfc_array_c10 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_COMPLEX_10));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ mproduct_c10 (gfc_array_c10 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_COMPLEX_10));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ sproduct_c10 (gfc_array_c10 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_COMPLEX_10));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/product_c16.c b/libgfortran/generated/product_c16.c
index e1d0c932a089e6f77e1be8c21c593621753e5577..1538f605d583ed9e445f86d639a2ef5351e4f6bf 100644
--- a/libgfortran/generated/product_c16.c
+++ b/libgfortran/generated/product_c16.c
@@ -106,12 +106,7 @@ product_c16 (gfc_array_c16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_COMPLEX_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ mproduct_c16 (gfc_array_c16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_COMPLEX_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ sproduct_c16 (gfc_array_c16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_COMPLEX_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/product_c17.c b/libgfortran/generated/product_c17.c
index 2ed08b31f1eed0f9750ebbabc05aa57ceaac047d..fba33932d71a1feb16acbb97bbc3ca9b71fe9e46 100644
--- a/libgfortran/generated/product_c17.c
+++ b/libgfortran/generated/product_c17.c
@@ -106,12 +106,7 @@ product_c17 (gfc_array_c17 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_COMPLEX_17));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ mproduct_c17 (gfc_array_c17 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_COMPLEX_17));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ sproduct_c17 (gfc_array_c17 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_COMPLEX_17));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/product_c4.c b/libgfortran/generated/product_c4.c
index dbf00aacf7aa3577ba36e2a53fbe7e1e0a1df47f..d46eb69681415853c11603b9d6761a6b7f5f8a4d 100644
--- a/libgfortran/generated/product_c4.c
+++ b/libgfortran/generated/product_c4.c
@@ -106,12 +106,7 @@ product_c4 (gfc_array_c4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_COMPLEX_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ mproduct_c4 (gfc_array_c4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_COMPLEX_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ sproduct_c4 (gfc_array_c4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_COMPLEX_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/product_c8.c b/libgfortran/generated/product_c8.c
index 1a3f27d329e60f65967354650361425f84ec7558..ffdc538f12f72569c7d1a59e35efce00d1265040 100644
--- a/libgfortran/generated/product_c8.c
+++ b/libgfortran/generated/product_c8.c
@@ -106,12 +106,7 @@ product_c8 (gfc_array_c8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_COMPLEX_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ mproduct_c8 (gfc_array_c8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_COMPLEX_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ sproduct_c8 (gfc_array_c8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_COMPLEX_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/product_i1.c b/libgfortran/generated/product_i1.c
index 35f4f6ec804215ab72a224f5d365cfcef57ea026..d2abb955c97b13a3e3c4df0a7f61ee75ef837098 100644
--- a/libgfortran/generated/product_i1.c
+++ b/libgfortran/generated/product_i1.c
@@ -106,12 +106,7 @@ product_i1 (gfc_array_i1 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_1));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ mproduct_i1 (gfc_array_i1 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_1));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ sproduct_i1 (gfc_array_i1 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_1));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/product_i16.c b/libgfortran/generated/product_i16.c
index 3b815036f4faca0a6cd6de1032a66a4f1020acf3..9217c1265f113d4de01a7b29224f5232c9e5b5f0 100644
--- a/libgfortran/generated/product_i16.c
+++ b/libgfortran/generated/product_i16.c
@@ -106,12 +106,7 @@ product_i16 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ mproduct_i16 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ sproduct_i16 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/product_i2.c b/libgfortran/generated/product_i2.c
index e998c0d59c3adaac8e0a09dc87491fb8a098e6de..4287fa79868aec8253fcb1375a6a515479a82382 100644
--- a/libgfortran/generated/product_i2.c
+++ b/libgfortran/generated/product_i2.c
@@ -106,12 +106,7 @@ product_i2 (gfc_array_i2 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_2));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ mproduct_i2 (gfc_array_i2 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_2));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ sproduct_i2 (gfc_array_i2 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_2));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/product_i4.c b/libgfortran/generated/product_i4.c
index 7dbc77aff9f7d8bce9fb0acc361f6b5698aab42a..0c8d50901bda91c555733c9e72fb18744dbf4eb7 100644
--- a/libgfortran/generated/product_i4.c
+++ b/libgfortran/generated/product_i4.c
@@ -106,12 +106,7 @@ product_i4 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ mproduct_i4 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ sproduct_i4 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/product_i8.c b/libgfortran/generated/product_i8.c
index aaa688b69ffb010f1749d674d70c5e420474a719..555b9cd26f86dc6d1ce4dad8a9ab1bfd115c08cf 100644
--- a/libgfortran/generated/product_i8.c
+++ b/libgfortran/generated/product_i8.c
@@ -106,12 +106,7 @@ product_i8 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ mproduct_i8 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ sproduct_i8 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/product_r10.c b/libgfortran/generated/product_r10.c
index 8a7dba54fdddd020feafbe199d16094eba2aa16a..5271f55a98e16f16d8ac73661f59f71392ffc044 100644
--- a/libgfortran/generated/product_r10.c
+++ b/libgfortran/generated/product_r10.c
@@ -106,12 +106,7 @@ product_r10 (gfc_array_r10 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_10));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ mproduct_r10 (gfc_array_r10 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_10));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ sproduct_r10 (gfc_array_r10 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_10));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/product_r16.c b/libgfortran/generated/product_r16.c
index 38c9922ed9bf2f844cbd94dcc575612b85e66901..6a7c8506490d0330efc1d2a42b7123e4e60a84dd 100644
--- a/libgfortran/generated/product_r16.c
+++ b/libgfortran/generated/product_r16.c
@@ -106,12 +106,7 @@ product_r16 (gfc_array_r16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ mproduct_r16 (gfc_array_r16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ sproduct_r16 (gfc_array_r16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/product_r17.c b/libgfortran/generated/product_r17.c
index 37ed80c9d3a525f485cd0d4d69cf62e0ab47bb23..2103ec4da7f43b716c6ee80f97b6f1ae2b1b3ad4 100644
--- a/libgfortran/generated/product_r17.c
+++ b/libgfortran/generated/product_r17.c
@@ -106,12 +106,7 @@ product_r17 (gfc_array_r17 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_17));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ mproduct_r17 (gfc_array_r17 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_17));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ sproduct_r17 (gfc_array_r17 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_17));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/product_r4.c b/libgfortran/generated/product_r4.c
index 616fd5be89de5526a66b46ac2b24416884284cd1..f413cf0fc1e60eab2436c0d2d63f964e28481a11 100644
--- a/libgfortran/generated/product_r4.c
+++ b/libgfortran/generated/product_r4.c
@@ -106,12 +106,7 @@ product_r4 (gfc_array_r4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ mproduct_r4 (gfc_array_r4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ sproduct_r4 (gfc_array_r4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/product_r8.c b/libgfortran/generated/product_r8.c
index c4b710dfc6ff5dee1a75b3c332f09d43d49ec4f8..6d98fcae2eb2a15dbd16a2f7a0f853fd5929ba31 100644
--- a/libgfortran/generated/product_r8.c
+++ b/libgfortran/generated/product_r8.c
@@ -106,12 +106,7 @@ product_r8 (gfc_array_r8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ mproduct_r8 (gfc_array_r8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ sproduct_r8 (gfc_array_r8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/sum_c10.c b/libgfortran/generated/sum_c10.c
index 6de84a7e2ea5b55a9692bda9cc24b626c957061e..fa8d28d68b4df320607180da6832e5a3c7d7175a 100644
--- a/libgfortran/generated/sum_c10.c
+++ b/libgfortran/generated/sum_c10.c
@@ -106,12 +106,7 @@ sum_c10 (gfc_array_c10 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_COMPLEX_10));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ msum_c10 (gfc_array_c10 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_COMPLEX_10));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ ssum_c10 (gfc_array_c10 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_COMPLEX_10));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/sum_c16.c b/libgfortran/generated/sum_c16.c
index 96fc888290212e064e6109e7332f4047b5e88695..78dbb88ed79fb5c3643a6f551e847496882e8d51 100644
--- a/libgfortran/generated/sum_c16.c
+++ b/libgfortran/generated/sum_c16.c
@@ -106,12 +106,7 @@ sum_c16 (gfc_array_c16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_COMPLEX_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ msum_c16 (gfc_array_c16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_COMPLEX_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ ssum_c16 (gfc_array_c16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_COMPLEX_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/sum_c17.c b/libgfortran/generated/sum_c17.c
index 1472fe577334f85e0c5ffdf630be041b49210304..a392a09da3243e307d58f839406ae673a992a6b7 100644
--- a/libgfortran/generated/sum_c17.c
+++ b/libgfortran/generated/sum_c17.c
@@ -106,12 +106,7 @@ sum_c17 (gfc_array_c17 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_COMPLEX_17));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ msum_c17 (gfc_array_c17 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_COMPLEX_17));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ ssum_c17 (gfc_array_c17 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_COMPLEX_17));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/sum_c4.c b/libgfortran/generated/sum_c4.c
index 250aa416cb36dde54bf68907fb89692639468614..0da74be9a61efaa1c2d4336ceb1b1363801a7f60 100644
--- a/libgfortran/generated/sum_c4.c
+++ b/libgfortran/generated/sum_c4.c
@@ -106,12 +106,7 @@ sum_c4 (gfc_array_c4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_COMPLEX_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ msum_c4 (gfc_array_c4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_COMPLEX_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ ssum_c4 (gfc_array_c4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_COMPLEX_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/sum_c8.c b/libgfortran/generated/sum_c8.c
index 510a25847aca8c9d16d1e3f6d92d34ac0e40f478..8d7e18c897c760d3e5eb18358364cbc679bbe770 100644
--- a/libgfortran/generated/sum_c8.c
+++ b/libgfortran/generated/sum_c8.c
@@ -106,12 +106,7 @@ sum_c8 (gfc_array_c8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_COMPLEX_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ msum_c8 (gfc_array_c8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_COMPLEX_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ ssum_c8 (gfc_array_c8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_COMPLEX_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/sum_i1.c b/libgfortran/generated/sum_i1.c
index 974522b3bbffe8498c77c8bccf9214569fbeda0e..387fde4a47300100664c2c757aa74a466d90a6e5 100644
--- a/libgfortran/generated/sum_i1.c
+++ b/libgfortran/generated/sum_i1.c
@@ -106,12 +106,7 @@ sum_i1 (gfc_array_i1 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_1));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ msum_i1 (gfc_array_i1 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_1));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ ssum_i1 (gfc_array_i1 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_1));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/sum_i16.c b/libgfortran/generated/sum_i16.c
index 00f644bff71851786c193ed17b5b9cdb787a64b0..da33649514ef3535f307cbb0392daa2e1db0b58b 100644
--- a/libgfortran/generated/sum_i16.c
+++ b/libgfortran/generated/sum_i16.c
@@ -106,12 +106,7 @@ sum_i16 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ msum_i16 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ ssum_i16 (gfc_array_i16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/sum_i2.c b/libgfortran/generated/sum_i2.c
index 448273594f4e66dbac80b7299626a6120c1ab34a..9e49cf5586ccb0790a5b848daec9645f2022fc36 100644
--- a/libgfortran/generated/sum_i2.c
+++ b/libgfortran/generated/sum_i2.c
@@ -106,12 +106,7 @@ sum_i2 (gfc_array_i2 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_2));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ msum_i2 (gfc_array_i2 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_2));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ ssum_i2 (gfc_array_i2 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_2));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/sum_i4.c b/libgfortran/generated/sum_i4.c
index 529fb2e94a0b3cbdd5414e8788060f6294b386cb..69e31f1d67b26bdff51e05c6326eeb8e3429126a 100644
--- a/libgfortran/generated/sum_i4.c
+++ b/libgfortran/generated/sum_i4.c
@@ -106,12 +106,7 @@ sum_i4 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ msum_i4 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ ssum_i4 (gfc_array_i4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/sum_i8.c b/libgfortran/generated/sum_i8.c
index 7b7ca72aa7104e99ff3c82244450a30f46d25109..b8c86449df98ee486fecd0f54980086b17836d28 100644
--- a/libgfortran/generated/sum_i8.c
+++ b/libgfortran/generated/sum_i8.c
@@ -106,12 +106,7 @@ sum_i8 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ msum_i8 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ ssum_i8 (gfc_array_i8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_INTEGER_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/sum_r10.c b/libgfortran/generated/sum_r10.c
index 71e71dd91f00d037f0021d756449542b281d39d5..daba1023cb9c017386b4ac17e146bd78e3c3a75e 100644
--- a/libgfortran/generated/sum_r10.c
+++ b/libgfortran/generated/sum_r10.c
@@ -106,12 +106,7 @@ sum_r10 (gfc_array_r10 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_10));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ msum_r10 (gfc_array_r10 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_10));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ ssum_r10 (gfc_array_r10 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_10));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/sum_r16.c b/libgfortran/generated/sum_r16.c
index 813cc33dd907b74b077fe82928146f109be9c232..55a4c1f99ecfe30a55aa60f3a18220d75322a6a8 100644
--- a/libgfortran/generated/sum_r16.c
+++ b/libgfortran/generated/sum_r16.c
@@ -106,12 +106,7 @@ sum_r16 (gfc_array_r16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ msum_r16 (gfc_array_r16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ ssum_r16 (gfc_array_r16 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_16));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/sum_r17.c b/libgfortran/generated/sum_r17.c
index 8e82e871bb2618041fc7cd6cd45295a08d0d4ab0..519526f53ad4ec218c91303835b9143257669e70 100644
--- a/libgfortran/generated/sum_r17.c
+++ b/libgfortran/generated/sum_r17.c
@@ -106,12 +106,7 @@ sum_r17 (gfc_array_r17 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_17));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ msum_r17 (gfc_array_r17 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_17));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ ssum_r17 (gfc_array_r17 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_17));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/sum_r4.c b/libgfortran/generated/sum_r4.c
index 1b37711b99f7813b3cf2a5dca5df5f21fa1af413..b8cb0a88ca361c2ee78653bdc17474fb7f28d9ed 100644
--- a/libgfortran/generated/sum_r4.c
+++ b/libgfortran/generated/sum_r4.c
@@ -106,12 +106,7 @@ sum_r4 (gfc_array_r4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ msum_r4 (gfc_array_r4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ ssum_r4 (gfc_array_r4 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_4));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/generated/sum_r8.c b/libgfortran/generated/sum_r8.c
index 294211ba9bef89ae4484d297b2d17568105d3844..6299b5d32c9b6cac73f06bcff6141f98bcfd48c3 100644
--- a/libgfortran/generated/sum_r8.c
+++ b/libgfortran/generated/sum_r8.c
@@ -106,12 +106,7 @@ sum_r8 (gfc_array_r8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -303,11 +298,7 @@ msum_r8 (gfc_array_r8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -466,11 +457,7 @@ ssum_r8 (gfc_array_r8 * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (GFC_REAL_8));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/m4/ifindloc1.m4 b/libgfortran/m4/ifindloc1.m4
index a1c5be6848dc47179d2e8f153c5b75b364f084f0..68a39f326d467f87e5f14122f992aa6421bcdcdc 100644
--- a/libgfortran/m4/ifindloc1.m4
+++ b/libgfortran/m4/ifindloc1.m4
@@ -97,11 +97,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively.  If not, see
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -275,11 +271,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively.  If not, see
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -438,11 +430,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively.  If not, see
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (index_type));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/m4/ifunction-s.m4 b/libgfortran/m4/ifunction-s.m4
index 72793e435aafefaee1bd29ee1309e93df6f89eec..8275f6568c4ee78eb3b7b9a8dc4acf2c57511c6d 100644
--- a/libgfortran/m4/ifunction-s.m4
+++ b/libgfortran/m4/ifunction-s.m4
@@ -109,12 +109,7 @@ void
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (rtype_name));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -305,11 +300,7 @@ m'name`'rtype_qual`_'atype_code` ('rtype` * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (rtype_name));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -467,11 +458,7 @@ s'name`'rtype_qual`_'atype_code` ('rtype` * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (rtype_name));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/m4/ifunction-s2.m4 b/libgfortran/m4/ifunction-s2.m4
index b936d7c392c4cfc48bc5bd82038f8336488f1476..4189dd9e2d8f4000c3b529f97376f0674f3f8dc0 100644
--- a/libgfortran/m4/ifunction-s2.m4
+++ b/libgfortran/m4/ifunction-s2.m4
@@ -111,12 +111,7 @@ name`'rtype_qual`_'atype_code (rtype * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (rtype_name));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -306,11 +301,7 @@ void
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (rtype_name));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -468,11 +459,7 @@ void
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (rtype_name));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/m4/ifunction.m4 b/libgfortran/m4/ifunction.m4
index f3ab4ebd58dc41ee37afce351dd06b02785f9dfb..8e32d49218b7577d5e69d6d430c5267b846d9eba 100644
--- a/libgfortran/m4/ifunction.m4
+++ b/libgfortran/m4/ifunction.m4
@@ -96,12 +96,7 @@ name`'rtype_qual`_'atype_code` ('rtype` * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (rtype_name));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-
-	}
+	return;
     }
   else
     {
@@ -293,11 +288,7 @@ m'name`'rtype_qual`_'atype_code` ('rtype` * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (rtype_name));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
@@ -455,11 +446,7 @@ void
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (rtype_name));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {
diff --git a/libgfortran/m4/ifunction_logical.m4 b/libgfortran/m4/ifunction_logical.m4
index cb576f3472efd2114ad377759eda826e12f99b65..5fd776368b3be1376f5acc3aa3bdd3f969618f60 100644
--- a/libgfortran/m4/ifunction_logical.m4
+++ b/libgfortran/m4/ifunction_logical.m4
@@ -93,11 +93,7 @@ name`'rtype_qual`_'atype_code (rtype * const restrict retarray,
 
       retarray->base_addr = xmallocarray (alloc_size, sizeof (rtype_name));
       if (alloc_size == 0)
-	{
-	  /* Make sure we have a zero-sized array.  */
-	  GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
-	  return;
-	}
+	return;
     }
   else
     {