Allow complex pointers to real arrays and vice-versa

Consider this program:

program noncontig
   use, intrinsic :: iso_c_binding, only: c_loc, c_f_pointer
   implicit none
   real, target :: t(8)=[1,2,3,4,5,6,7,8]
   real, pointer :: a(:,:,:), rp(:,:,:)
   complex, pointer :: cp(:,:)
   character(*), parameter :: cfmt='(a,*(1x,f0.0))'
   !cp(1:1,1:4) => a    ! contiguous
   write(*,cfmt) ' t', t
   a(1:2,1:2,1:2) => t
   write(*,cfmt) ' a', a
   call c_f_pointer( c_loc(a), cp, [1,4] )
   write(*,cfmt) 'cp', cp

   !cp(1:1,1:2) => a(:,1:1,1:2) ! noncontiguous
   write(*,cfmt) ' a', a(1:2,1:1,1:2)
   rp => a(1:2,1:1,1:2)
   write(*,cfmt) 'rp', rp
   cp => cp(1:1,1:4:2)
   write(*,cfmt) 'cp', cp
end program noncontig

$ a.out
 t 1. 2. 3. 4. 5. 6. 7. 8.
 a 1. 2. 3. 4. 5. 6. 7. 8.
cp 1. 2. 3. 4. 5. 6. 7. 8.
 a 1. 2. 5. 6.
rp 1. 2. 5. 6.
cp 1. 2. 5. 6.

Note that all of the real pointer assignments are legal and are straightforward within the confines of the language. It is only the complex assignments that run afoul of the restrictions on the programmer.

However, through storage sequence association, the real and complex array elements are required by the standard to match up. Therefore it seems like an artificial restriction on the programmer that he is not allowed to take advantage of that storage sequence association.