Ignore:
Timestamp:
Nov 8, 2013 3:18:40 PM (10 years ago)
Author:
raasch
Message:

New:
---

openACC porting of timestep calculation
(modules, timestep, time_integration)

Changed:


openACC loop directives and vector clauses removed (because they do not give any performance improvement with PGI
compiler versions > 13.6)
(advec_ws, buoyancy, coriolis, diffusion_e, diffusion_s, diffusion_u, diffusion_v, diffusion_w, diffusivities, exchange_horiz, fft_xy, pres, production_e, transpose, tridia_solver, wall_fluxes)

openACC loop independent clauses added
(boundary_conds, prandtl_fluxes, pres)

openACC declare create statements moved after FORTRAN declaration statement
(diffusion_u, diffusion_v, diffusion_w, fft_xy, poisfft, production_e, tridia_solver)

openACC end parallel replaced by end parallel loop
(flow_statistics, pres)

openACC "kernels do" replaced by "kernels loop"
(prandtl_fluxes)

output format for theta* changed to avoid output of *
(run_control)

Errors:


bugfix for calculation of advective timestep (old version may cause wrong timesteps in case of
vertixcally stretched grids)
Attention: standard run-control output has changed!
(timestep)

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/prandtl_fluxes.f90

    r1037 r1257  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! openACC "kernels do" replaced by "kernels loop", "loop independent" added
    2323!
    2424! Former revisions:
     
    101101!--    for u* use the value from the previous time step
    102102       !$OMP PARALLEL DO
    103        !$acc kernels do
     103       !$acc kernels loop
    104104       DO  i = nxlg, nxrg
    105105          DO  j = nysg, nyng
     
    118118!--    (the Richardson number is still the one from the previous time step)
    119119       !$OMP PARALLEL DO PRIVATE( a, b, k, z_p )
    120        !$acc kernels do
     120       !$acc kernels loop
    121121       DO  i = nxlg, nxrg
    122122          DO  j = nysg, nyng
     
    151151    IF ( .NOT. humidity )  THEN
    152152       !$OMP PARALLEL DO PRIVATE( k, z_p )
    153        !$acc kernels do
     153       !$acc kernels loop
    154154       DO  i = nxlg, nxrg
    155155          DO  j = nysg, nyng
     
    170170    ELSE
    171171       !$OMP PARALLEL DO PRIVATE( k, z_p )
    172        !$acc kernels do
     172       !$acc kernels loop
    173173       DO  i = nxlg, nxrg
    174174          DO  j = nysg, nyng
     
    193193!-- Compute u* at the scalars' grid points
    194194    !$OMP PARALLEL DO PRIVATE( a, b, k, uv_total, z_p )
    195     !$acc kernels do
     195    !$acc kernels loop
    196196    DO  i = nxl, nxr
    197197       DO  j = nys, nyn
     
    243243!-- First compute the corresponding component of u* and square it.
    244244    !$OMP PARALLEL DO PRIVATE( a, b, k, rifm, z_p )
    245     !$acc kernels do
     245    !$acc kernels loop
    246246    DO  i = nxl, nxr
    247247       DO  j = nys, nyn
     
    281281!-- First compute the corresponding component of u* and square it.
    282282    !$OMP PARALLEL DO PRIVATE( a, b, k, rifm, z_p )
    283     !$acc kernels do
     283    !$acc kernels loop
    284284    DO  i = nxl, nxr
    285285       DO  j = nys, nyn
     
    322322!--       For a given water flux in the Prandtl layer:
    323323          !$OMP PARALLEL DO
    324           !$acc kernels do
     324          !$acc kernels loop
    325325          DO  i = nxlg, nxrg
    326326             DO  j = nysg, nyng
     
    332332          coupled_run = ( coupling_mode == 'atmosphere_to_ocean' .AND. run_coupled )
    333333          !$OMP PARALLEL DO PRIVATE( a, b, k, z_p )
    334           !$acc kernels do
     334          !$acc kernels loop independent
    335335          DO  i = nxlg, nxrg
     336             !$acc loop independent
    336337             DO  j = nysg, nyng
    337338
     
    387388    IF ( .NOT. constant_heatflux )  THEN
    388389       !$OMP PARALLEL DO
    389        !$acc kernels do
    390        DO  i = nxlg, nxrg
     390       !$acc kernels loop independent
     391       DO  i = nxlg, nxrg
     392          !$acc loop independent
    391393          DO  j = nysg, nyng
    392394             shf(j,i) = -ts(j,i) * us(j,i)
     
    399401    IF ( .NOT. constant_waterflux .AND. ( humidity .OR. passive_scalar ) ) THEN
    400402       !$OMP PARALLEL DO
    401        !$acc kernels do
    402        DO  i = nxlg, nxrg
     403       !$acc kernels loop independent
     404       DO  i = nxlg, nxrg
     405          !$acc loop independent
    403406          DO  j = nysg, nyng
    404407             qsws(j,i) = -qs(j,i) * us(j,i)
     
    411414    IF ( ibc_e_b == 2 )  THEN
    412415       !$OMP PARALLEL DO
    413        !$acc kernels do
    414        DO  i = nxlg, nxrg
     416       !$acc kernels loop independent
     417       DO  i = nxlg, nxrg
     418          !$acc loop independent
    415419          DO  j = nysg, nyng
    416420             e(nzb_s_inner(j,i)+1,j,i) = ( us(j,i) / 0.1 )**2
Note: See TracChangeset for help on using the changeset viewer.