program test use mpi use omp_lib implicit none include "VT.inc" integer :: rank integer :: size integer :: state integer :: ierr integer :: prof_init integer :: prof_iter integer :: prof_intf integer :: prof_dyn integer :: prof_ada integer :: prof_tl integer :: prof_wp integer*8 :: n double precision, allocatable :: x(:), y(:) integer :: iter integer*8 :: i n = 1000000000 call mpi_init(ierr) call mpi_comm_rank(MPI_COMM_WORLD, rank, ierr) call mpi_comm_size(MPI_COMM_WORLD, size, ierr) !$omp parallel write (*, '(a,i0,a,i0)') "Hello from rank #", rank, ", thread #", omp_get_thread_num() !$omp end parallel call vtfuncdef("Init", VT_NOCLASS, prof_init, ierr) call vtfuncdef("Time loop", VT_NOCLASS, prof_iter, ierr) call vtfuncdef("Internal force computation", VT_NOCLASS, prof_intf, ierr) call vtfuncdef("Dynamics", VT_NOCLASS, prof_dyn, ierr) call vtfuncdef("Adaption", VT_NOCLASS, prof_ada, ierr) call vtfuncdef("Tool", VT_NOCLASS, prof_tl, ierr) call vtfuncdef("Workpiece", VT_NOCLASS, prof_wp, ierr) call vtbegin(prof_init, ierr) allocate(x(n), y(n)) call vtend(prof_init, ierr) call vtbegin(prof_iter, ierr) do iter = 1, 5 call vtbegin(prof_intf, ierr) call vtbegin(prof_tl, ierr) !$omp parallel do do i = 1, n/2 y(i) = .1d0 * iter * i end do call vtend(prof_tl, ierr) call vtbegin(prof_wp, ierr) !$omp parallel do do i = n/2+1, n y(i) = .2d0 * iter * i end do call vtend(prof_wp, ierr) call vtend(prof_intf, ierr) call mpi_barrier(MPI_COMM_WORLD, ierr) call vtbegin(prof_dyn, ierr) call vtbegin(prof_tl, ierr) !$omp parallel do do i = 1, n/2 x(i) = y(i) * y(i) end do call vtend(prof_tl, ierr) call vtbegin(prof_wp, ierr) !$omp parallel do do i = n/2+1, n x(i) = sqrt(y(i)) end do call vtend(prof_wp, ierr) call vtend(prof_dyn, ierr) if (iter == 3) then call vtbegin(prof_ada, ierr) n = 1.1 * n; deallocate(x, y) allocate(x(n), y(n)) call vtend(prof_ada, ierr) end if end do call vtend(prof_iter, ierr) call mpi_finalize(ierr) end program test