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

    r1220 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:
     
    328329       REAL, DIMENSION(6*(nx+1)) ::  work2
    329330#elif defined( __cuda_fft )
     331       COMPLEX(dpk), DIMENSION(0:(nx+1)/2,nys_x:nyn_x,nzb_x:nzt_x) ::  ar_tmp
    330332       !$acc declare create( ar_tmp )
    331        COMPLEX(dpk), DIMENSION(0:(nx+1)/2,nys_x:nyn_x,nzb_x:nzt_x) ::  ar_tmp
    332333#endif
    333334       REAL, DIMENSION(0:nx,nys_x:nyn_x), OPTIONAL   ::  ar_2d
     
    634635
    635636             !$acc kernels
    636              !$acc loop
    637637             DO  k = nzb_x, nzt_x
    638638                DO  j = nys_x, nyn_x
    639639
    640                    !$acc loop vector( 32 )
    641640                   DO  i = 0, (nx+1)/2
    642641                      ar(i,j,k)      = REAL( ar_tmp(i,j,k) )  * dnx
    643642                   ENDDO
    644643
    645                    !$acc loop vector( 32 )
    646644                   DO  i = 1, (nx+1)/2 - 1
    647645                      ar(nx+1-i,j,k) = AIMAG( ar_tmp(i,j,k) ) * dnx
     
    657655             !$acc data present( ar )
    658656             !$acc kernels
    659              !$acc loop
    660657             DO  k = nzb_x, nzt_x
    661658                DO  j = nys_x, nyn_x
     
    663660                   ar_tmp(0,j,k) = CMPLX( ar(0,j,k), 0.0 )
    664661
    665                    !$acc loop vector( 32 )
    666662                   DO  i = 1, (nx+1)/2 - 1
    667663                      ar_tmp(i,j,k) = CMPLX( ar(i,j,k), ar(nx+1-i,j,k) )
     
    957953       REAL, DIMENSION(6*(ny+1)) ::  work2
    958954#elif defined( __cuda_fft )
     955       COMPLEX(dpk), DIMENSION(0:(ny+1)/2,nxl_y:nxr_y,nzb_y:nzt_y) ::  ar_tmp
    959956       !$acc declare create( ar_tmp )
    960        COMPLEX(dpk), DIMENSION(0:(ny+1)/2,nxl_y:nxr_y,nzb_y:nzt_y) ::  ar_tmp
    961957#endif
    962958       REAL, DIMENSION(0:ny,nxl_y_l:nxr_y_l,nzb_y:nzt_y) ::  ar
     
    12361232
    12371233             !$acc kernels
    1238              !$acc loop
    12391234             DO  k = nzb_y, nzt_y
    12401235                DO  i = nxl_y, nxr_y
    12411236
    1242                    !$acc loop vector( 32 )
    12431237                   DO  j = 0, (ny+1)/2
    12441238                      ar(j,i,k)      = REAL( ar_tmp(j,i,k) )  * dny
    12451239                   ENDDO
    12461240
    1247                    !$acc loop vector( 32 )
    12481241                   DO  j = 1, (ny+1)/2 - 1
    12491242                      ar(ny+1-j,i,k) = AIMAG( ar_tmp(j,i,k) ) * dny
     
    12591252             !$acc data present( ar )
    12601253             !$acc kernels
    1261              !$acc loop
    12621254             DO  k = nzb_y, nzt_y
    12631255                DO  i = nxl_y, nxr_y
     
    12651257                   ar_tmp(0,i,k) = CMPLX( ar(0,i,k), 0.0 )
    12661258
    1267                    !$acc loop vector( 32 )
    12681259                   DO  j = 1, (ny+1)/2 - 1
    12691260                      ar_tmp(j,i,k) = CMPLX( ar(j,i,k), ar(ny+1-j,i,k) )
Note: See TracChangeset for help on using the changeset viewer.