Ignore:
Timestamp:
Apr 22, 2014 3:03:56 PM (11 years ago)
Author:
boeske
Message:

large scale forcing enabled

File:
1 edited

Legend:

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

    r1354 r1365  
    2020! Current revisions:
    2121! ------------------
    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
    2325!
    2426! Former revisions:
     
    7880
    7981    PRIVATE
    80     PUBLIC buoyancy, buoyancy_acc, calc_mean_profile
     82    PUBLIC buoyancy, buoyancy_acc
    8183
    8284    INTERFACE buoyancy
     
    8890       MODULE PROCEDURE buoyancy_acc
    8991    END INTERFACE buoyancy_acc
    90 
    91     INTERFACE calc_mean_profile
    92        MODULE PROCEDURE calc_mean_profile
    93     END INTERFACE calc_mean_profile
    9492
    9593 CONTAINS
     
    376374    END SUBROUTINE buoyancy_ij
    377375
    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 case
    385 ! of potential temperature, 44 in case of virtual potential temperature, and 64
    386 ! in case of density (ocean runs)).
    387 !------------------------------------------------------------------------------!
    388 
    389        USE arrays_3d,                                                          &
    390            ONLY:  ref_state
    391 
    392        USE control_parameters,                                                 &
    393            ONLY:  intermediate_timestep_count, message_string
    394 
    395        USE indices,                                                            &
    396            ONLY:  ngp_2dh_s_inner, nxl, nxr, nyn, nys, nzb, nzb_s_inner, nzt
    397 
    398        USE kinds
    399 
    400        USE pegrid
    401 
    402        USE statistics,                                                         &
    403            ONLY:  flow_statistics_called, hom, sums, sums_l
    404 
    405 
    406        IMPLICIT NONE
    407 
    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 #else
    420        REAL(wp), DIMENSION(:,:,:), POINTER ::  var
    421 #endif
    422 
    423 !
    424 !--    Computation of the horizontally averaged profile of variable var, unless
    425 !--    already done by the relevant call from flow_statistics. The calculation
    426 !--    is done only for the first respective intermediate timestep in order to
    427 !--    spare communication time and to produce identical model results with jobs
    428 !--    which are calling flow_statistics at different time intervals.
    429        IF ( .NOT. flow_statistics_called  .AND.                                &
    430             intermediate_timestep_count == 1 )  THEN
    431 
    432 !
    433 !--       Horizontal average of variable var
    434           tn           =   0  ! Default thread number in case of one thread
    435           !$OMP PARALLEL PRIVATE( i, j, k, tn )
    436 !$        tn = omp_get_thread_num()
    437           sums_l(:,pr,tn) = 0.0_wp
    438           !$OMP DO
    439           DO  i = nxl, nxr
    440              DO  j =  nys, nyn
    441                 DO  k = nzb_s_inner(j,i), nzt+1
    442                    sums_l(k,pr,tn) = sums_l(k,pr,tn) + var(k,j,i)
    443                 ENDDO
    444              ENDDO
    445           ENDDO
    446           !$OMP END PARALLEL
    447 
    448           DO  i = 1, threads_per_task-1
    449              sums_l(:,pr,0) = sums_l(:,pr,0) + sums_l(:,pr,i)
    450           ENDDO
    451 
    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 #else
    459 
    460           sums(:,pr) = sums_l(:,pr,0)
    461 
    462 #endif
    463 
    464           hom(:,1,pr,0) = sums(:,pr) / ngp_2dh_s_inner(:,0)
    465 
    466        ENDIF
    467 
    468        SELECT CASE ( loc )
    469 
    470           CASE ( 'time_int' )
    471 
    472              ref_state(:)  = hom(:,1,pr,0)   ! this is used in the buoyancy term
    473 
    474 
    475           CASE ( 'nudging' )
    476              !nothing to be done
    477 
    478 
    479           CASE DEFAULT
    480              message_string = 'unknown location "' // loc // '"'
    481              CALL message( 'calc_mean_profile', 'PA0379', 1, 2, 0, 6, 0 )
    482 
    483        END SELECT
    484 
    485 
    486 
    487     END SUBROUTINE calc_mean_profile
    488 
    489376 END MODULE buoyancy_mod
Note: See TracChangeset for help on using the changeset viewer.