Ignore:
Timestamp:
Jan 17, 2017 4:38:49 PM (7 years ago)
Author:
raasch
Message:

all OpenACC directives and related parts removed from the code

File:
1 edited

Legend:

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

    r2101 r2118  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! OpenACC directives and related code removed
    2323!
    2424! Former revisions:
     
    163163!>
    164164!> @todo (re)move large_scale_forcing actions
    165 !> @todo check/optimize OpenMP and OpenACC directives
     165!> @todo check/optimize OpenMP directives
    166166!------------------------------------------------------------------------------!
    167167 MODULE surface_layer_fluxes_mod
     
    472472
    473473       !$OMP PARALLEL DO PRIVATE( k )
    474        !$acc kernels loop present( nzb_s_inner, u, uv_total, v ) private( j, k )
    475474       DO  i = nxl, nxr
    476475          DO  j = nys, nyn
     
    492491!
    493492!--    Values of uv_total need to be exchanged at the ghost boundaries
    494        !$acc update host( uv_total )
    495493       CALL exchange_horiz_2d( uv_total )
    496        !$acc update device( uv_total )
    497494
    498495    END SUBROUTINE calc_uv_total
     
    522519       IF ( TRIM( most_method ) /= 'circular' )  THEN
    523520     
    524           !$acc data present( nzb_s_inner, pt, q, qsws, rib, shf, uv_total, vpt, zu, zw )
    525 
    526521          !$OMP PARALLEL DO PRIVATE( k, z_mo )
    527           !$acc kernels loop private( j, k, z_mo )
    528522          DO  i = nxl, nxr
    529523             DO  j = nys, nyn
     
    564558             ENDDO
    565559          ENDDO
    566           !$acc end data
    567560
    568561       ENDIF
     
    574567
    575568          !$OMP PARALLEL DO PRIVATE( k, z_mo )
    576           !# WARNING: does not work on GPU so far because of DO-loop with
    577           !#          undetermined iterations
    578           !!!!!!$acc kernels loop
    579569          DO  i = nxl, nxr
    580570             DO  j = nys, nyn
     
    695685
    696686          !$OMP PARALLEL DO PRIVATE( k, l, z_mo ) FIRSTPRIVATE( l_bnd ) LASTPRIVATE( l_bnd )
    697           !# WARNING: does not work on GPU so far because of DO  WHILE construct
    698           !!!!!!$acc kernels loop
    699687          DO  i = nxl, nxr
    700688             DO  j = nys, nyn
     
    736724
    737725          !$OMP PARALLEL DO PRIVATE( k, z_mo )
    738           !$acc kernels loop present( nzb_s_inner, ol, pt, pt1, q, ql, qs, qv1, ts, us, vpt, zu, zw ) private( j, k, z_mo )
    739726          DO  i = nxl, nxr
    740727             DO  j = nys, nyn
     
    775762!--    Values of ol at ghost point locations are needed for the evaluation
    776763!--    of usws and vsws.
    777        !$acc update host( ol )
    778764       CALL exchange_horiz_2d( ol )
    779        !$acc update device( ol )
    780765
    781766    END SUBROUTINE calc_ol
     
    788773
    789774       !$OMP PARALLEL DO PRIVATE( k, z_mo )
    790        !$acc kernels loop present( nzb_s_inner, ol, us, uv_total, zu, zw, z0 ) private( j, k, z_mo )
    791775       DO  i = nxlg, nxrg
    792776          DO  j = nysg, nyng
     
    811795       IMPLICIT NONE
    812796
    813        !$acc kernels loop present( nzb_s_inner, pt, pt1, pt_d_t, q, ql, qv1 ) private( j, k )
    814797       DO  i = nxlg, nxrg
    815798          DO  j = nysg, nyng
     
    828811       IMPLICIT NONE
    829812
    830 !
    831 !--    Data information for accelerators
    832        !$acc data present( e, nrsws, nzb_u_inner, nzb_v_inner, nzb_s_inner, pt )  &
    833        !$acc      present( q, qs, qsws, qrsws, shf, ts, u, us, usws, v )     &
    834        !$acc      present( vpt, vsws, zu, zw, z0, z0h )
    835813!
    836814!--    Compute theta*
     
    840818!--       For a given heat flux in the surface layer:
    841819          !$OMP PARALLEL DO
    842           !$acc kernels loop private( j, k )
    843820          DO  i = nxlg, nxrg
    844821             DO  j = nysg, nyng
     
    858835          IF ( large_scale_forcing  .AND.  lsf_surf )  THEN
    859836             !$OMP PARALLEL DO
    860              !$acc kernels loop private( j, k )
    861837             DO  i = nxlg, nxrg
    862838                DO  j = nysg, nyng
     
    868844
    869845          !$OMP PARALLEL DO PRIVATE( k, z_mo )
    870           !$acc kernels loop present( nzb_s_inner, ol, pt, pt1, ts, zu, zw, z0h ) private( j, k, z_mo )
    871846          DO  i = nxlg, nxrg
    872847             DO  j = nysg, nyng
     
    898873!--          For a given water flux in the surface layer
    899874             !$OMP PARALLEL DO
    900              !$acc kernels loop private( j )
    901875             DO  i = nxlg, nxrg
    902876                DO  j = nysg, nyng
     
    912886             IF ( large_scale_forcing  .AND.  lsf_surf )  THEN
    913887                !$OMP PARALLEL DO
    914                 !$acc kernels loop private( j, k )
    915888                DO  i = nxlg, nxrg
    916889                   DO  j = nysg, nyng
     
    922895
    923896             !$OMP PARALLEL DO PRIVATE( e_s, k, z_mo )
    924              !$acc kernels loop independent present( nzb_s_inner, ol, pt, q, qs, qv1, zu, zw, z0q ) private( e_s, j, k, z_mo )
    925897             DO  i = nxlg, nxrg
    926                 !$acc loop independent
    927898                DO  j = nysg, nyng
    928899
     
    965936!--          For a given water flux in the surface layer
    966937             !$OMP PARALLEL DO
    967              !$acc kernels loop private( j )
    968938             DO  i = nxlg, nxrg
    969939                DO  j = nysg, nyng
     
    981951
    982952          !$OMP PARALLEL DO PRIVATE( k, z_mo )
    983           !$acc kernels loop independent present( nr, nrs, nzb_s_inner, ol, qr, qrs, zu, zw, z0q ) private( j, k, z_mo )
    984953          DO  i = nxlg, nxrg
    985              !$acc loop independent
    986954             DO  j = nysg, nyng
    987955
     
    1002970
    1003971       ENDIF
    1004        !$acc end data
    1005972
    1006973    END SUBROUTINE calc_scaling_parameters
     
    1020987!--    First compute the corresponding component of u* and square it.
    1021988       !$OMP PARALLEL DO PRIVATE( k, ol_mid, z_mo )
    1022        !$acc kernels loop present( nzb_u_inner, ol, u, us, usws, zu, zw, z0 ) private( j, k, z_mo )
    1023989       DO  i = nxl, nxr
    1024990          DO  j = nys, nyn
     
    10481014!--    First compute the corresponding component of u* and square it.
    10491015       !$OMP PARALLEL DO PRIVATE( k, ol_mid, z_mo )
    1050        !$acc kernels loop present( nzb_v_inner, ol, v, us, vsws, zu, zw, z0 ) private( j, k, ol_mid, z_mo )
    10511016       DO  i = nxl, nxr
    10521017          DO  j = nys, nyn
     
    10751040!
    10761041!--    Exchange the boundaries for the momentum fluxes (is this still required?)
    1077        !$acc update host( usws, vsws )
    10781042       CALL exchange_horiz_2d( usws )
    10791043       CALL exchange_horiz_2d( vsws )
    1080        !$acc update device( usws, vsws )
    10811044
    10821045!
     
    10861049            .NOT.  urban_surface )  THEN
    10871050          !$OMP PARALLEL DO
    1088           !$acc kernels loop independent present( shf, ts, us )
    10891051          DO  i = nxlg, nxrg
    1090              !$acc loop independent
    10911052             DO  j = nysg, nyng
    10921053                k   = nzb_s_inner(j,i)
     
    11031064            .OR.  .NOT.  land_surface ) )  THEN
    11041065          !$OMP PARALLEL DO
    1105           !$acc kernels loop independent present( qs, qsws, us )
    11061066          DO  i = nxlg, nxrg
    1107              !$acc loop independent
    11081067             DO  j = nysg, nyng
    11091068                k   = nzb_s_inner(j,i)
     
    11201079            .OR.  .NOT.  land_surface ) )  THEN
    11211080          !$OMP PARALLEL DO
    1122           !$acc kernels loop independent present( qs, qsws, us )
    11231081          DO  i = nxlg, nxrg
    1124              !$acc loop independent
    11251082             DO  j = nysg, nyng
    11261083                ssws(j,i) = -ss(j,i) * us(j,i)
     
    11341091       IF ( cloud_physics  .AND.  microphysics_seifert )  THEN
    11351092          !$OMP PARALLEL DO
    1136           !$acc kernels loop independent present( nrs, nrsws, qrs, qrsws, us )
    11371093          DO  i = nxlg, nxrg
    1138              !$acc loop independent
    11391094             DO  j = nysg, nyng
    11401095                qrsws(j,i) = -qrs(j,i) * us(j,i)
     
    11481103       IF ( ibc_e_b == 2 )  THEN
    11491104          !$OMP PARALLEL DO
    1150           !$acc kernels loop independent present( e, nzb_s_inner, us )
    11511105          DO  i = nxlg, nxrg
    1152              !$acc loop independent
    11531106             DO  j = nysg, nyng
    11541107                k = nzb_s_inner(j,i)
Note: See TracChangeset for help on using the changeset viewer.