Changeset 2118 for palm/trunk/SOURCE/buoyancy.f90
- Timestamp:
- Jan 17, 2017 4:38:49 PM (6 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/SOURCE/buoyancy.f90
r2101 r2118 20 20 ! Current revisions: 21 21 ! ------------------ 22 ! 22 ! OpenACC version of subroutine removed 23 23 ! 24 24 ! Former revisions: … … 102 102 103 103 PRIVATE 104 PUBLIC buoyancy , buoyancy_acc104 PUBLIC buoyancy 105 105 106 106 INTERFACE buoyancy … … 108 108 MODULE PROCEDURE buoyancy_ij 109 109 END INTERFACE buoyancy 110 111 INTERFACE buoyancy_acc112 MODULE PROCEDURE buoyancy_acc113 END INTERFACE buoyancy_acc114 110 115 111 CONTAINS … … 212 208 213 209 END SUBROUTINE buoyancy 214 215 216 !------------------------------------------------------------------------------!217 ! Description:218 ! ------------219 !> Call for all grid points - accelerator version220 !------------------------------------------------------------------------------!221 SUBROUTINE buoyancy_acc( var, wind_component )222 223 USE arrays_3d, &224 ONLY: pt, pt_slope_ref, ref_state, tend225 226 USE control_parameters, &227 ONLY: atmos_ocean_sign, cos_alpha_surface, g, message_string, &228 pt_surface, sin_alpha_surface, sloping_surface229 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, nzt233 234 USE kinds235 236 USE pegrid237 238 239 IMPLICIT NONE240 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 #else249 REAL(wp), DIMENSION(:,:,:), POINTER :: var250 #endif251 252 253 IF ( .NOT. sloping_surface ) THEN254 !255 !-- Normal case: horizontal surface256 !$acc kernels present( nzb_s_inner, ref_state, tend, var )257 !$acc loop258 DO i = i_left, i_right259 DO j = j_south, j_north260 !$acc loop independent vector261 DO k = nzb_s_inner(j,i)+1, nzt-1262 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 ENDDO268 ENDDO269 ENDDO270 !$acc end kernels271 272 ELSE273 !274 !-- Buoyancy term for a surface with a slope in x-direction. The equations275 !-- 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 corner278 !-- of the total domain.279 IF ( wind_component == 1 ) THEN280 281 DO i = nxlu, nxr282 DO j = nys, nyn283 DO k = nzb_s_inner(j,i)+1, nzt-1284 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_surface288 ENDDO289 ENDDO290 ENDDO291 292 ELSEIF ( wind_component == 3 ) THEN293 294 DO i = nxl, nxr295 DO j = nys, nyn296 DO k = nzb_s_inner(j,i)+1, nzt-1297 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_surface301 ENDDO302 ENDDO303 ENDDO304 305 ELSE306 307 WRITE( message_string, * ) 'no term for component "', &308 wind_component,'"'309 CALL message( 'buoyancy', 'PA0159', 1, 2, 0, 6, 0 )310 311 ENDIF312 313 ENDIF314 315 END SUBROUTINE buoyancy_acc316 210 317 211
Note: See TracChangeset
for help on using the changeset viewer.