Ignore:
Timestamp:
Sep 27, 2012 9:23:24 AM (12 years ago)
Author:
raasch
Message:

Starting with changes required for GPU optimization. OpenACC statements for using NVIDIA GPUs added.
Adjustment of mixing length to the Prandtl mixing length at first grid point above ground removed.
mask array is set zero for ghost boundaries

File:
1 edited

Legend:

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

    r979 r1015  
    44! Current revisions:
    55! -----------------
    6 !
     6! OpenACC statements added
    77!
    88! Former revisions:
     
    6565
    6666    INTEGER ::  i, j, k
     67    LOGICAL ::  coupled_run
    6768    REAL    ::  a, b, e_q, rifm, uv_total, z_p
    6869
     70!
     71!-- Data information for accelerators
     72    !$acc data present( e, nzb_u_inner, nzb_v_inner, nzb_s_inner, pt, q, qs ) &
     73    !$acc      present( qsws, rif, shf, ts, u, us, usws, v, vpt, vsws, zu, zw, z0, z0h )
    6974!
    7075!-- Compute theta*
     
    7479!--    for u* use the value from the previous time step
    7580       !$OMP PARALLEL DO
     81       !$acc kernels do
    7682       DO  i = nxlg, nxrg
    7783          DO  j = nysg, nyng
     
    9096!--    (the Richardson number is still the one from the previous time step)
    9197       !$OMP PARALLEL DO PRIVATE( a, b, k, z_p )
     98       !$acc kernels do
    9299       DO  i = nxlg, nxrg
    93100          DO  j = nysg, nyng
     
    122129    IF ( .NOT. humidity )  THEN
    123130       !$OMP PARALLEL DO PRIVATE( k, z_p )
     131       !$acc kernels do
    124132       DO  i = nxlg, nxrg
    125133          DO  j = nysg, nyng
     
    140148    ELSE
    141149       !$OMP PARALLEL DO PRIVATE( k, z_p )
     150       !$acc kernels do
    142151       DO  i = nxlg, nxrg
    143152          DO  j = nysg, nyng
     
    162171!-- Compute u* at the scalars' grid points
    163172    !$OMP PARALLEL DO PRIVATE( a, b, k, uv_total, z_p )
     173    !$acc kernels do
    164174    DO  i = nxl, nxr
    165175       DO  j = nys, nyn
     
    203213!-- Values of us at ghost point locations are needed for the evaluation of usws
    204214!-- and vsws.
     215    !$acc update host( us )
    205216    CALL exchange_horiz_2d( us )
     217    !$acc update device( us )
     218
    206219!
    207220!-- Compute u'w' for the total model domain.
    208221!-- First compute the corresponding component of u* and square it.
    209222    !$OMP PARALLEL DO PRIVATE( a, b, k, rifm, z_p )
     223    !$acc kernels do
    210224    DO  i = nxl, nxr
    211225       DO  j = nys, nyn
     
    245259!-- First compute the corresponding component of u* and square it.
    246260    !$OMP PARALLEL DO PRIVATE( a, b, k, rifm, z_p )
     261    !$acc kernels do
    247262    DO  i = nxl, nxr
    248263       DO  j = nys, nyn
     
    285300!--       For a given water flux in the Prandtl layer:
    286301          !$OMP PARALLEL DO
     302          !$acc kernels do
    287303          DO  i = nxlg, nxrg
    288304             DO  j = nysg, nyng
     
    291307          ENDDO
    292308         
    293        ELSE         
     309       ELSE
     310          coupled_run = ( coupling_mode == 'atmosphere_to_ocean' .AND. run_coupled )
    294311          !$OMP PARALLEL DO PRIVATE( a, b, k, z_p )
     312          !$acc kernels do
    295313          DO  i = nxlg, nxrg
    296314             DO  j = nysg, nyng
     
    302320!--             Assume saturation for atmosphere coupled to ocean (but not
    303321!--             in case of precursor runs)
    304                 IF ( coupling_mode == 'atmosphere_to_ocean' .AND. run_coupled )&
    305                 THEN
     322                IF ( coupled_run )  THEN
    306323                   e_q = 6.1 * &
    307324                        EXP( 0.07 * ( MIN(pt(0,j,i),pt(1,j,i)) - 273.15 ) )
     
    334351!-- Exchange the boundaries for the momentum fluxes (only for sake of
    335352!-- completeness)
     353    !$acc update host( usws, vsws )
    336354    CALL exchange_horiz_2d( usws )
    337355    CALL exchange_horiz_2d( vsws )
    338     IF ( humidity  .OR.  passive_scalar )  CALL exchange_horiz_2d( qsws )
     356    !$acc update device( usws, vsws )
     357    IF ( humidity  .OR.  passive_scalar )  THEN
     358       !$acc update host( qsws )
     359       CALL exchange_horiz_2d( qsws )
     360       !$acc update device( qsws )
     361    ENDIF
    339362
    340363!
     
    342365    IF ( .NOT. constant_heatflux )  THEN
    343366       !$OMP PARALLEL DO
     367       !$acc kernels do
    344368       DO  i = nxlg, nxrg
    345369          DO  j = nysg, nyng
     
    353377    IF ( .NOT. constant_waterflux .AND. ( humidity .OR. passive_scalar ) ) THEN
    354378       !$OMP PARALLEL DO
     379       !$acc kernels do
    355380       DO  i = nxlg, nxrg
    356381          DO  j = nysg, nyng
     
    364389    IF ( ibc_e_b == 2 )  THEN
    365390       !$OMP PARALLEL DO
     391       !$acc kernels do
    366392       DO  i = nxlg, nxrg
    367393          DO  j = nysg, nyng
     
    375401    ENDIF
    376402
     403    !$acc end data
    377404
    378405 END SUBROUTINE prandtl_fluxes
Note: See TracChangeset for help on using the changeset viewer.