Changeset 1365 for palm/trunk/SOURCE/buoyancy.f90
- Timestamp:
- Apr 22, 2014 3:03:56 PM (11 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/SOURCE/buoyancy.f90
r1354 r1365 20 20 ! Current revisions: 21 21 ! ------------------ 22 ! 22 ! Calculation of reference state in subroutine calc_mean_profile moved to 23 ! subroutine time_integration, 24 ! subroutine calc_mean_profile moved to new file calc_mean_profile.f90 23 25 ! 24 26 ! Former revisions: … … 78 80 79 81 PRIVATE 80 PUBLIC buoyancy, buoyancy_acc , calc_mean_profile82 PUBLIC buoyancy, buoyancy_acc 81 83 82 84 INTERFACE buoyancy … … 88 90 MODULE PROCEDURE buoyancy_acc 89 91 END INTERFACE buoyancy_acc 90 91 INTERFACE calc_mean_profile92 MODULE PROCEDURE calc_mean_profile93 END INTERFACE calc_mean_profile94 92 95 93 CONTAINS … … 376 374 END SUBROUTINE buoyancy_ij 377 375 378 379 SUBROUTINE calc_mean_profile( var, pr, loc )380 381 !------------------------------------------------------------------------------!382 ! Description:383 ! ------------384 ! Calculate the horizontally averaged vertical temperature profile (pr=4 in case385 ! of potential temperature, 44 in case of virtual potential temperature, and 64386 ! in case of density (ocean runs)).387 !------------------------------------------------------------------------------!388 389 USE arrays_3d, &390 ONLY: ref_state391 392 USE control_parameters, &393 ONLY: intermediate_timestep_count, message_string394 395 USE indices, &396 ONLY: ngp_2dh_s_inner, nxl, nxr, nyn, nys, nzb, nzb_s_inner, nzt397 398 USE kinds399 400 USE pegrid401 402 USE statistics, &403 ONLY: flow_statistics_called, hom, sums, sums_l404 405 406 IMPLICIT NONE407 408 CHARACTER (LEN=*) :: loc !:409 410 INTEGER(iwp) :: i !:411 INTEGER(iwp) :: j !:412 INTEGER(iwp) :: k !:413 INTEGER(iwp) :: pr !:414 INTEGER(iwp) :: omp_get_thread_num !:415 INTEGER(iwp) :: tn !:416 417 #if defined( __nopointer )418 REAL(wp), DIMENSION(:,:,:) :: var !:419 #else420 REAL(wp), DIMENSION(:,:,:), POINTER :: var421 #endif422 423 !424 !-- Computation of the horizontally averaged profile of variable var, unless425 !-- already done by the relevant call from flow_statistics. The calculation426 !-- is done only for the first respective intermediate timestep in order to427 !-- spare communication time and to produce identical model results with jobs428 !-- which are calling flow_statistics at different time intervals.429 IF ( .NOT. flow_statistics_called .AND. &430 intermediate_timestep_count == 1 ) THEN431 432 !433 !-- Horizontal average of variable var434 tn = 0 ! Default thread number in case of one thread435 !$OMP PARALLEL PRIVATE( i, j, k, tn )436 !$ tn = omp_get_thread_num()437 sums_l(:,pr,tn) = 0.0_wp438 !$OMP DO439 DO i = nxl, nxr440 DO j = nys, nyn441 DO k = nzb_s_inner(j,i), nzt+1442 sums_l(k,pr,tn) = sums_l(k,pr,tn) + var(k,j,i)443 ENDDO444 ENDDO445 ENDDO446 !$OMP END PARALLEL447 448 DO i = 1, threads_per_task-1449 sums_l(:,pr,0) = sums_l(:,pr,0) + sums_l(:,pr,i)450 ENDDO451 452 #if defined( __parallel )453 454 IF ( collective_wait ) CALL MPI_BARRIER( comm2d, ierr )455 CALL MPI_ALLREDUCE( sums_l(nzb,pr,0), sums(nzb,pr), nzt+2-nzb, &456 MPI_REAL, MPI_SUM, comm2d, ierr )457 458 #else459 460 sums(:,pr) = sums_l(:,pr,0)461 462 #endif463 464 hom(:,1,pr,0) = sums(:,pr) / ngp_2dh_s_inner(:,0)465 466 ENDIF467 468 SELECT CASE ( loc )469 470 CASE ( 'time_int' )471 472 ref_state(:) = hom(:,1,pr,0) ! this is used in the buoyancy term473 474 475 CASE ( 'nudging' )476 !nothing to be done477 478 479 CASE DEFAULT480 message_string = 'unknown location "' // loc // '"'481 CALL message( 'calc_mean_profile', 'PA0379', 1, 2, 0, 6, 0 )482 483 END SELECT484 485 486 487 END SUBROUTINE calc_mean_profile488 489 376 END MODULE buoyancy_mod
Note: See TracChangeset
for help on using the changeset viewer.