Why a simple code, Intel Fortran -O3 -O2 gives wrong results?

Thank you my man! @Euler-37
Yes I know. I have managed according to @certik suggestion, even simpler version here, 30 lines.
He suggested 10 lines, that is a little bit too tough. 10 lines there is almost nothing I can do :sweat_smile:

module tests 
implicit none
contains
subroutine test01
integer, parameter :: n = 10, np = 10
integer :: i, itot, istart, istep, j, k
real  :: x(0:n), xout(5,np)
itot = n
istart = itot/5
istep = istart
do j = 1, np
    i = 0
    x(i) = 20.0
    do i = 1, n
        call rk4_ti_step_mod3 ( x(i-1), x(i) ) ! check n=10 bug.
        !write ( *, '(2x,i8,2x,f14.6,2x,g14.6)' ) i, x(i-1), x(i)
    end do
    !write (6,'(''x = '',t20, 5(f15.7,1x))') x(istart:itot:istep)
    xout(1:5:1,j) = x(istart:itot:istep)
enddo    
write (6,'(5(f15.7,1x))') xout
return
end subroutine test01
subroutine rk4_ti_step_mod3 ( x, xstar ) 
real :: x, xstar
xstar = x 
!write(6,*) 'x', x 
xstar = xstar + x
return
end subroutine rk4_ti_step_mod3
end module tests    
program main
use tests
implicit none  
call test01
stop ('Program end normally.')
end program main

In this above version, there is just one module called tests.

However if I move the subroutines to the main program. That is, use no module, is bug is gone. I am a little bit confused. Please see below, this code does not have problem.

program main
implicit none  
call test01
stop ('Program end normally.')
contains
subroutine test01
integer, parameter :: n = 10, np = 10
integer :: i, itot, istart, istep, j, k
real  :: x(0:n), xout(5,np)
itot = n
istart = itot/5
istep = istart
do j = 1, np
    i = 0
    x(i) = 20.0
    do i = 1, n
        call rk4_ti_step_mod3 ( x(i-1), x(i) ) ! check n=10 bug.
        !write ( *, '(2x,i8,2x,f14.6,2x,g14.6)' ) i, x(i-1), x(i)
    end do
    !write (6,'(''x = '',t20, 5(f15.7,1x))') x(istart:itot:istep)
    xout(1:5:1,j) = x(istart:itot:istep)
enddo    
write (6,'(5(f15.7,1x))') xout
return
end subroutine test01
subroutine rk4_ti_step_mod3 ( x, xstar ) 
real :: x, xstar
xstar = x 
!write(6,*) 'x', x 
xstar = xstar + x
return
end subroutine rk4_ti_step_mod3
end program main