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/diffusion_v.f90

    r1132 r1257  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! openacc loop and loop vector clauses removed, declare create moved after
     23! the FORTRAN declaration statement
    2324!
    2425! Former revisions:
     
    262263       REAL    ::  kmxm, kmxp, kmzm, kmzp
    263264
     265       REAL, DIMENSION(nzb:nzt+1,nys:nyn,nxl:nxr) ::  vsus
    264266       !$acc declare create ( vsus )
    265        REAL, DIMENSION(nzb:nzt+1,nys:nyn,nxl:nxr) ::  vsus
    266267
    267268!
     
    276277       !$acc         present ( ddzu, ddzw, fxm, fxp, wall_v )           &
    277278       !$acc         present ( nzb_v_inner, nzb_v_outer, nzb_diff_v )
    278        !$acc loop
    279279       DO  i = i_left, i_right
    280280          DO  j = j_south, j_north
    281281!
    282282!--          Compute horizontal diffusion
    283              !$acc loop vector(32)
    284283             DO  k = 1, nzt
    285284                IF ( k > nzb_v_outer(j,i) )  THEN
     
    306305!
    307306!--          Wall functions at the left and right walls, respectively
    308              !$acc loop vector(32)
    309307             DO  k = 1, nzt
    310308                IF( k > nzb_v_inner(j,i)  .AND.  k <= nzb_v_outer(j,i)  .AND. &
     
    337335!--          Compute vertical diffusion. In case of simulating a Prandtl
    338336!--          layer, index k starts at nzb_v_inner+2.
    339              !$acc loop vector(32)
    340337             DO  k = 1, nzt_diff
    341338                IF ( k >= nzb_diff_v(j,i) )  THEN
     
    373370       IF ( use_surface_fluxes )  THEN
    374371
    375           !$acc loop
    376372          DO  i = i_left, i_right
    377              !$acc loop vector(32)
    378373             DO  j = j_south, j_north
    379374         
     
    404399          k = nzt
    405400
    406           !$acc loop
    407401          DO  i = i_left, i_right
    408              !$acc loop vector(32)
    409402             DO  j = j_south, j_north
    410403
Note: See TracChangeset for help on using the changeset viewer.