SUBROUTINE user_statistics( mode, sr, tn ) !------------------------------------------------------------------------------! ! Actual revisions: ! ----------------- ! ! ! Former revisions: ! ----------------- ! $Id: user_statistics.f90 226 2009-02-02 07:39:34Z fricke $ ! ! 211 2008-11-11 04:46:24Z raasch ! Former file user_interface.f90 split into one file per subroutine ! ! Description: ! ------------ ! Calculation of user-defined statistics, i.e. horizontally averaged profiles ! and time series. ! This routine is called for every statistic region sr defined by the user, ! but at least for the region "total domain" (sr=0). ! See section 3.5.4 on how to define, calculate, and output user defined ! quantities. !------------------------------------------------------------------------------! USE arrays_3d USE indices USE statistics USE user IMPLICIT NONE CHARACTER (LEN=*) :: mode INTEGER :: i, j, k, sr, tn IF ( mode == 'profiles' ) THEN ! !-- Sample on how to calculate horizontally averaged profiles of user- !-- defined quantities. Each quantity is identified by the index !-- "pr_palm+#" where "#" is an integer starting from 1. These !-- user-profile-numbers must also be assigned to the respective strings !-- given by data_output_pr_user in routine user_check_data_output_pr. ! !$OMP DO ! DO i = nxl, nxr ! DO j = nys, nyn ! DO k = nzb_s_inner(j,i)+1, nzt !! !!-- Sample on how to calculate the profile of the resolved-scale !!-- horizontal momentum flux u*v* ! sums_l(k,pr_palm+1,tn) = sums_l(k,pr_palm+1,tn) + & ! ( 0.5 * ( u(k,j,i) + u(k,j,i+1) ) - hom(k,1,1,sr) ) * & ! ( 0.5 * ( v(k,j,i) + v(k,j+1,i) ) - hom(k,1,2,sr) ) & ! * rmask(j,i,sr) !! !!-- Further profiles can be defined and calculated by increasing !!-- the second index of array sums_l (replace ... appropriately) ! sums_l(k,pr_palm+2,tn) = sums_l(k,pr_palm+2,tn) + ... & ! * rmask(j,i,sr) ! ENDDO ! ENDDO ! ENDDO ELSEIF ( mode == 'time_series' ) THEN ! !-- Sample on how to add values for the user-defined time series quantities. !-- These have to be defined before in routine user_init. This sample !-- creates two time series for the absolut values of the horizontal !-- velocities u and v. ! ts_value(dots_num_palm+1,sr) = ABS( u_max ) ! ts_value(dots_num_palm+2,sr) = ABS( v_max ) ENDIF END SUBROUTINE user_statistics