Ignore:
Timestamp:
Jan 17, 2017 4:38:49 PM (6 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/buoyancy.f90

    r2101 r2118  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! OpenACC version of subroutine removed
    2323!
    2424! Former revisions:
     
    102102
    103103    PRIVATE
    104     PUBLIC buoyancy, buoyancy_acc
     104    PUBLIC buoyancy
    105105
    106106    INTERFACE buoyancy
     
    108108       MODULE PROCEDURE buoyancy_ij
    109109    END INTERFACE buoyancy
    110 
    111     INTERFACE buoyancy_acc
    112        MODULE PROCEDURE buoyancy_acc
    113     END INTERFACE buoyancy_acc
    114110
    115111 CONTAINS
     
    212208
    213209    END SUBROUTINE buoyancy
    214 
    215 
    216 !------------------------------------------------------------------------------!
    217 ! Description:
    218 ! ------------
    219 !> Call for all grid points - accelerator version
    220 !------------------------------------------------------------------------------!
    221     SUBROUTINE buoyancy_acc( var, wind_component )
    222 
    223        USE arrays_3d,                                                          &
    224            ONLY:  pt, pt_slope_ref, ref_state, tend
    225 
    226        USE control_parameters,                                                 &
    227            ONLY:  atmos_ocean_sign, cos_alpha_surface, g, message_string,      &
    228                   pt_surface, sin_alpha_surface, sloping_surface
    229 
    230        USE indices,                                                            &
    231            ONLY:  i_left, i_right, j_north, j_south, nxl, nxlg, nxlu, nxr,     &
    232                   nxrg, nyn, nyng, nys, nysg, nzb, nzb_s_inner, nzt
    233 
    234        USE kinds
    235 
    236        USE pegrid
    237 
    238 
    239        IMPLICIT NONE
    240 
    241        INTEGER(iwp) ::  i              !<
    242        INTEGER(iwp) ::  j              !<
    243        INTEGER(iwp) ::  k              !<
    244        INTEGER(iwp) ::  wind_component !<
    245        
    246 #if defined( __nopointer )
    247        REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  var !<
    248 #else
    249        REAL(wp), DIMENSION(:,:,:), POINTER ::  var
    250 #endif
    251 
    252 
    253        IF ( .NOT. sloping_surface )  THEN
    254 !
    255 !--       Normal case: horizontal surface
    256           !$acc kernels present( nzb_s_inner, ref_state, tend, var )
    257           !$acc loop
    258           DO  i = i_left, i_right
    259              DO  j = j_south, j_north
    260                 !$acc loop independent vector
    261                 DO  k = nzb_s_inner(j,i)+1, nzt-1
    262                    tend(k,j,i) = tend(k,j,i) + atmos_ocean_sign * g * 0.5_wp * &
    263                           (                                                    &
    264                              ( var(k,j,i)   - ref_state(k) )   / ref_state(k) + &
    265                              ( var(k+1,j,i) - ref_state(k+1) ) / ref_state(k+1) &
    266                           )
    267                 ENDDO
    268              ENDDO
    269           ENDDO
    270           !$acc end kernels
    271 
    272        ELSE
    273 !
    274 !--       Buoyancy term for a surface with a slope in x-direction. The equations
    275 !--       for both the u and w velocity-component contain proportionate terms.
    276 !--       Temperature field at time t=0 serves as environmental temperature.
    277 !--       Reference temperature (pt_surface) is the one at the lower left corner
    278 !--       of the total domain.
    279           IF ( wind_component == 1 )  THEN
    280 
    281              DO  i = nxlu, nxr
    282                 DO  j = nys, nyn
    283                    DO  k = nzb_s_inner(j,i)+1, nzt-1
    284                       tend(k,j,i) = tend(k,j,i) + g * sin_alpha_surface *      &
    285                            0.5_wp * ( ( pt(k,j,i-1)         + pt(k,j,i)         ) &
    286                                     - ( pt_slope_ref(k,i-1) + pt_slope_ref(k,i) ) &
    287                                     ) / pt_surface
    288                    ENDDO
    289                 ENDDO
    290              ENDDO
    291 
    292           ELSEIF ( wind_component == 3 )  THEN
    293 
    294              DO  i = nxl, nxr
    295                 DO  j = nys, nyn
    296                    DO  k = nzb_s_inner(j,i)+1, nzt-1
    297                       tend(k,j,i) = tend(k,j,i) + g * cos_alpha_surface *      &
    298                            0.5_wp * ( ( pt(k,j,i)         + pt(k+1,j,i)         ) &
    299                                     - ( pt_slope_ref(k,i) + pt_slope_ref(k+1,i) ) &
    300                                     ) / pt_surface
    301                    ENDDO
    302                 ENDDO
    303             ENDDO
    304 
    305           ELSE
    306 
    307              WRITE( message_string, * ) 'no term for component "',             &
    308                                        wind_component,'"'
    309              CALL message( 'buoyancy', 'PA0159', 1, 2, 0, 6, 0 )
    310 
    311           ENDIF
    312 
    313        ENDIF
    314 
    315     END SUBROUTINE buoyancy_acc
    316210
    317211
Note: See TracChangeset for help on using the changeset viewer.