SUBROUTINE data_output_profiles !------------------------------------------------------------------------------! ! Current revisions: ! ----------------- ! ! ! Former revisions: ! ----------------- ! $Id: data_output_profiles.f90 392 2009-09-24 10:39:14Z banzhafs $ ! ! 345 2009-07-01 14:37:56Z heinze ! In case of restart runs without extension, initial profiles are not written ! to NetCDF-file anymore. ! simulated_time in NetCDF output replaced by time_since_reference_point. ! Output of NetCDF messages with aid of message handling routine. ! Output of messages replaced by message handling routine. ! ! 197 2008-09-16 15:29:03Z raasch ! Time coordinate t=0 stored on netcdf-file only if an output is required for ! this time for at least one of the profiles ! ! February 2007 ! RCS Log replace by Id keyword, revision history cleaned up ! ! 87 2007-05-22 15:46:47Z raasch ! var_hom renamed pr_palm ! ! Revision 1.18 2006/08/16 14:27:04 raasch ! PRINT* statements for testing removed ! ! Revision 1.1 1997/09/12 06:28:48 raasch ! Initial revision ! ! ! Description: ! ------------ ! Plot output of 1D-profiles for PROFIL !------------------------------------------------------------------------------! USE control_parameters USE cpulog USE indices USE interfaces USE netcdf_control USE pegrid USE profil_parameter USE statistics IMPLICIT NONE INTEGER :: i, id, ilc, ils, j, k, sr REAL :: uxma, uxmi ! !-- If required, compute statistics IF ( .NOT. flow_statistics_called ) CALL flow_statistics ! !-- Flow_statistics has its own CPU time measurement CALL cpu_log( log_point(15), 'data_output_profiles', 'start' ) ! !-- If required, compute temporal average IF ( averaging_interval_pr == 0.0 ) THEN hom_sum(:,:,:) = hom(:,1,:,:) ELSE IF ( average_count_pr > 0 ) THEN hom_sum = hom_sum / REAL( average_count_pr ) ELSE ! !-- This case may happen if dt_dopr is changed in the d3par-list of !-- a restart run RETURN ENDIF ENDIF IF ( myid == 0 ) THEN ! !-- Plot-output for each (sub-)region ! !-- Open file for profile output in NetCDF format IF ( netcdf_output ) THEN CALL check_open( 104 ) ENDIF ! !-- Open PROFIL-output files for each (sub-)region IF ( profil_output ) THEN DO sr = 0, statistic_regions CALL check_open( 40 + sr ) ENDDO ENDIF ! !-- Increment the counter for number of output times dopr_time_count = dopr_time_count + 1 ! !-- Re-set to zero the counter for the number of profiles already written !-- at the current output time into the respective crosses cross_pnc_local = 0 ! !-- Output of initial profiles IF ( dopr_time_count == 1 ) THEN IF ( .NOT. output_for_t0 ) THEN IF ( netcdf_output ) THEN #if defined( __netcdf ) ! !-- Store initial time (t=0) to time axis, but only if an output !-- is required for at least one of the profiles DO i = 1, dopr_n IF ( dopr_initial_index(i) /= 0 ) THEN nc_stat = NF90_PUT_VAR( id_set_pr, id_var_time_pr, & (/ 0.0 /), start = (/ 1 /), & count = (/ 1 /) ) CALL handle_netcdf_error( 'data_output_profiles', 329 ) output_for_t0 = .TRUE. EXIT ENDIF ENDDO ! !-- Store normalization factors nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(1), & ! wpt0 (/ hom_sum(nzb,18,normalizing_region) /), & start = (/ 1 /), count = (/ 1 /) ) CALL handle_netcdf_error( 'data_output_profiles', 330 ) nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(2), & ! ws2 (/ hom_sum(nzb+8,pr_palm,normalizing_region)**2 /), & start = (/ 1 /), count = (/ 1 /) ) CALL handle_netcdf_error( 'data_output_profiles', 331 ) nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(3), & ! tsw2 (/ hom_sum(nzb+3,pr_palm,normalizing_region)**2 /), & start = (/ 1 /), count = (/ 1 /) ) CALL handle_netcdf_error( 'data_output_profiles', 332 ) nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(4), & ! ws3 (/ hom_sum(nzb+8,pr_palm,normalizing_region)**3 /), & start = (/ 1 /), count = (/ 1 /) ) CALL handle_netcdf_error( 'data_output_profiles', 333 ) nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(5), &!ws2tsw (/ hom_sum(nzb+8,pr_palm,normalizing_region)**3 * & hom_sum(nzb+3,pr_palm,normalizing_region) /), & start = (/ 1 /), count = (/ 1 /) ) CALL handle_netcdf_error( 'data_output_profiles', 334 ) nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(6), &!wstsw2 (/ hom_sum(nzb+8,pr_palm,normalizing_region) * & hom_sum(nzb+3,pr_palm,normalizing_region)**2 /), & start = (/ 1 /), count = (/ 1 /) ) CALL handle_netcdf_error( 'data_output_profiles', 335 ) nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(7), & ! z_i (/ hom_sum(nzb+6,pr_palm,normalizing_region) /), & start = (/ 1 /), count = (/ 1 /) ) CALL handle_netcdf_error( 'data_output_profiles', 336 ) #endif ENDIF ! !-- Loop over all 1D variables DO i = 1, dopr_n IF ( dopr_initial_index(i) /= 0 ) THEN ! !-- Output for the individual (sub-)regions DO sr = 0, statistic_regions IF ( profil_output ) THEN id = 40 + sr ! !-- Write Label-Header WRITE ( id, 100 ) TRIM( data_output_pr(i) ), '(t=0)' ! !-- Write total profile DO k = nzb, nzt+1 WRITE ( id, 101 ) hom(k,2,dopr_initial_index(i),sr), & hom(k,1,dopr_initial_index(i),sr) ENDDO ! !-- Write separation label WRITE ( id, 102 ) ENDIF IF ( netcdf_output ) THEN #if defined( __netcdf ) ! !-- Write data to netcdf file nc_stat = NF90_PUT_VAR( id_set_pr, id_var_dopr(i,sr), & hom(nzb:nzt+1,1,dopr_initial_index(i),sr), & start = (/ 1, 1 /), & count = (/ nzt-nzb+2, 1 /) ) CALL handle_netcdf_error( 'data_output_profiles', 337 ) #endif ENDIF ENDDO IF ( profil_output ) THEN ! !-- Determine indices for later NAMELIST-output (s. below) profile_number = profile_number + 1 j = dopr_crossindex(i) IF ( j /= 0 ) THEN cross_profile_number_count(j) = & cross_profile_number_count(j) + 1 k = cross_profile_number_count(j) cross_profile_numbers(k,j) = profile_number ! !-- Initial profiles are always drawn as solid lines in !-- anti-background colour. cross_linecolors(k,j) = 1 cross_linestyles(k,j) = 0 ! !-- If required, extend x-value range of the respective !-- cross, provided it has not been specified in & !-- check_parameters. Determination over all (sub-)regions. IF ( cross_uxmin(j) == 0.0 .AND. & cross_uxmax(j) == 0.0 ) THEN DO sr = 0, statistic_regions uxmi = & MINVAL( hom(:nz_do1d,1,dopr_initial_index(i),sr) ) uxma = & MAXVAL( hom(:nz_do1d,1,dopr_initial_index(i),sr) ) ! !-- When the value range of the first line in the !-- corresponding cross is determined, its value range !-- is simply adopted. IF ( cross_uxmin_computed(j) > & cross_uxmax_computed(j) ) THEN cross_uxmin_computed(j) = uxmi cross_uxmax_computed(j) = uxma ELSE cross_uxmin_computed(j) = & MIN( cross_uxmin_computed(j), uxmi ) cross_uxmax_computed(j) = & MAX( cross_uxmax_computed(j), uxma ) ENDIF ENDDO ENDIF ! !-- If required, determine and note normalizing factors SELECT CASE ( cross_normalized_x(j) ) CASE ( 'ts2' ) cross_normx_factor(k,j) = & ( hom_sum(nzb+3,pr_palm,normalizing_region) )**2 CASE ( 'wpt0' ) cross_normx_factor(k,j) = & hom_sum(nzb,18,normalizing_region) CASE ( 'wsts2' ) cross_normx_factor(k,j) = & hom_sum(nzb+8,pr_palm,normalizing_region) & * ( hom_sum(nzb+3,pr_palm,normalizing_region) )**2 CASE ( 'ws2' ) cross_normx_factor(k,j) = & ( hom_sum(nzb+8,pr_palm,normalizing_region) )**2 CASE ( 'ws2ts' ) cross_normx_factor(k,j) = & ( hom_sum(nzb+8,pr_palm,normalizing_region) )**2 & * hom_sum(nzb+3,pr_palm,normalizing_region) CASE ( 'ws3' ) cross_normx_factor(k,j) = & ( hom_sum(nzb+8,pr_palm,normalizing_region) )**3 END SELECT SELECT CASE ( cross_normalized_y(j) ) CASE ( 'z_i' ) cross_normy_factor(k,j) = & hom_sum(nzb+6,pr_palm,normalizing_region) END SELECT ! !-- Check the normalizing factors for zeros and deactivate !-- the normalization, if required. IF ( cross_normx_factor(k,j) == 0.0 .OR. & cross_normy_factor(k,j) == 0.0 ) THEN WRITE( message_string, * ) 'data_output_profiles: ', & 'normalizing cross ',j, ' is not possible ', & 'since one of the & normalizing factors ', & 'is zero! & cross_normx_factor(',k,',',j,') = ', & cross_normx_factor(k,j), & ' & cross_normy_factor(',k,',',j,') = ', & cross_normy_factor(k,j) CALL message( 'data_output_profiles', 'PA0185',& 0, 1, 0, 6, 0 ) cross_normx_factor(k,j) = 1.0 cross_normy_factor(k,j) = 1.0 cross_normalized_x(j) = ' ' cross_normalized_y(j) = ' ' ENDIF ! !-- If required, extend normalized x-value range of the !-- respective cross, provided it has not been specified in !-- check_parameters. Determination over all (sub-)regions. IF ( cross_uxmin_normalized(j) == 0.0 .AND. & cross_uxmax_normalized(j) == 0.0 ) THEN DO sr = 0, statistic_regions uxmi = MINVAL( hom(:nz_do1d,1, & dopr_initial_index(i),sr) ) / & cross_normx_factor(k,j) uxma = MAXVAL( hom(:nz_do1d,1, & dopr_initial_index(i),sr) ) / & cross_normx_factor(k,j) ! !-- When the value range of the first line in the !-- corresponding cross is determined, its value range !-- is simply adopted. IF ( cross_uxmin_normalized_computed(j) > & cross_uxmax_normalized_computed(j) ) THEN cross_uxmin_normalized_computed(j) = uxmi cross_uxmax_normalized_computed(j) = uxma ELSE cross_uxmin_normalized_computed(j) = & MIN( cross_uxmin_normalized_computed(j), uxmi ) cross_uxmax_normalized_computed(j) = & MAX( cross_uxmax_normalized_computed(j), uxma ) ENDIF ENDDO ENDIF ENDIF ! Index determination ENDIF ! profil output ENDIF ! Initial profile available ENDDO ! Loop over dopr_n for initial profiles IF ( netcdf_output .AND. output_for_t0 ) THEN dopr_time_count = dopr_time_count + 1 ENDIF END IF ENDIF ! Initial profiles IF ( netcdf_output ) THEN #if defined( __netcdf ) ! !-- Store time to time axis nc_stat = NF90_PUT_VAR( id_set_pr, id_var_time_pr, & (/ time_since_reference_point /), & start = (/ dopr_time_count /), & count = (/ 1 /) ) CALL handle_netcdf_error( 'data_output_profiles', 338 ) ! !-- Store normalization factors nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(1), & ! wpt0 (/ hom_sum(nzb,18,normalizing_region) /), & start = (/ dopr_time_count /), & count = (/ 1 /) ) CALL handle_netcdf_error( 'data_output_profiles', 339 ) nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(2), & ! ws2 (/ hom_sum(nzb+8,pr_palm,normalizing_region)**2 /), & start = (/ dopr_time_count /), & count = (/ 1 /) ) CALL handle_netcdf_error( 'data_output_profiles', 340 ) nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(3), & ! tsw2 (/ hom_sum(nzb+3,pr_palm,normalizing_region)**2 /), & start = (/ dopr_time_count /), & count = (/ 1 /) ) CALL handle_netcdf_error( 'data_output_profiles', 341 ) nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(4), & ! ws3 (/ hom_sum(nzb+8,pr_palm,normalizing_region)**3 /), & start = (/ dopr_time_count /), & count = (/ 1 /) ) CALL handle_netcdf_error( 'data_output_profiles', 342 ) nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(5), & ! ws2tsw (/ hom_sum(nzb+8,pr_palm,normalizing_region)**3 * & hom_sum(nzb+3,pr_palm,normalizing_region) /), & start = (/ dopr_time_count /), & count = (/ 1 /) ) CALL handle_netcdf_error( 'data_output_profiles', 343 ) nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(6), & ! wstsw2 (/ hom_sum(nzb+8,pr_palm,normalizing_region) * & hom_sum(nzb+3,pr_palm,normalizing_region)**2 /), & start = (/ dopr_time_count /), & count = (/ 1 /) ) CALL handle_netcdf_error( 'data_output_profiles', 344 ) nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(7), & ! z_i (/ hom_sum(nzb+6,pr_palm,normalizing_region) /), & start = (/ dopr_time_count /), & count = (/ 1 /) ) CALL handle_netcdf_error( 'data_output_profiles', 345 ) #endif ENDIF ! !-- Output of the individual (non-initial) profiles DO i = 1, dopr_n ! !-- Output for the individual (sub-)domains DO sr = 0, statistic_regions IF ( profil_output ) THEN id = 40 + sr ! !-- Write Label-Header WRITE ( id, 100 ) TRIM( dopr_label(i) ), simulated_time_chr ! !-- Output of total profile DO k = nzb, nzt+1 WRITE ( id, 101 ) hom(k,2,dopr_index(i),sr), & hom_sum(k,dopr_index(i),sr) ENDDO ! !-- Write separation label WRITE ( id, 102 ) ENDIF IF ( netcdf_output ) THEN #if defined( __netcdf ) ! !-- Write data to netcdf file nc_stat = NF90_PUT_VAR( id_set_pr, id_var_dopr(i,sr), & hom_sum(nzb:nzt+1,dopr_index(i),sr),& start = (/ 1, dopr_time_count /), & count = (/ nzt-nzb+2, 1 /) ) CALL handle_netcdf_error( 'data_output_profiles', 346 ) #endif ENDIF ENDDO IF ( profil_output ) THEN ! !-- Determine profile number on file and note the data for later !-- NAMELIST output, if the respective profile is to be drawn by !-- PROFIL (if it shall not be drawn, the variable dopr_crossindex has !-- the value 0, otherwise the number of the coordinate cross) profile_number = profile_number + 1 j = dopr_crossindex(i) IF ( j /= 0 ) THEN cross_profile_number_count(j) = cross_profile_number_count(j) +1 k = cross_profile_number_count(j) cross_pnc_local(j) = cross_pnc_local(j) +1 cross_profile_numbers(k,j) = profile_number ilc = MOD( dopr_time_count, 10 ) IF ( ilc == 0 ) ilc = 10 cross_linecolors(k,j) = linecolors(ilc) ils = MOD( cross_pnc_local(j), 11 ) IF ( ils == 0 ) ils = 11 cross_linestyles(k,j) = linestyles(ils) ! !-- If required, extend x-value range of the respective coordinate !-- cross, provided it has not been specified in check_parameters. !-- Determination over all (sub-)regions. IF ( cross_uxmin(j) == 0.0 .AND. cross_uxmax(j) == 0.0 ) THEN DO sr = 0, statistic_regions uxmi = MINVAL( hom_sum(:nz_do1d,dopr_index(i),sr) ) uxma = MAXVAL( hom_sum(:nz_do1d,dopr_index(i),sr) ) ! !-- When the value range of the first line in the !-- corresponding cross is determined, its value range is !-- simply adopted. IF ( cross_uxmin_computed(j) > cross_uxmax_computed(j) ) & THEN cross_uxmin_computed(j) = uxmi cross_uxmax_computed(j) = uxma ELSE cross_uxmin_computed(j) = & MIN( cross_uxmin_computed(j), uxmi ) cross_uxmax_computed(j) = & MAX( cross_uxmax_computed(j), uxma ) ENDIF ENDDO ENDIF ! !-- If required, store the normalizing factors SELECT CASE ( cross_normalized_x(j) ) CASE ( 'tsw2' ) cross_normx_factor(k,j) = & ( hom_sum(nzb+11,pr_palm,normalizing_region) )**2 CASE ( 'wpt0' ) cross_normx_factor(k,j) = & hom_sum(nzb,18,normalizing_region) CASE ( 'wstsw2' ) cross_normx_factor(k,j) = & hom_sum(nzb+8,pr_palm,normalizing_region) & * ( hom_sum(nzb+11,pr_palm,normalizing_region) )**2 CASE ( 'ws2' ) cross_normx_factor(k,j) = & ( hom_sum(nzb+8,pr_palm,normalizing_region) )**2 CASE ( 'ws2tsw' ) cross_normx_factor(k,j) = & ( hom_sum(nzb+8,pr_palm,normalizing_region) )**2& * hom_sum(nzb+11,pr_palm,normalizing_region) CASE ( 'ws3' ) cross_normx_factor(k,j) = & ( hom_sum(nzb+8,pr_palm,normalizing_region) )**3 END SELECT SELECT CASE ( cross_normalized_y(j) ) CASE ( 'z_i' ) cross_normy_factor(k,j) = & hom_sum(nzb+6,pr_palm,normalizing_region) END SELECT ! !-- Check the normalizing factors for zeros and deactivate !-- the normalization, if required. IF ( cross_normx_factor(k,j) == 0.0 .OR. & cross_normy_factor(k,j) == 0.0 ) THEN WRITE( message_string, * ) 'data_output_profiles: ', & 'normalizing cross ',j, ' is not possible ', & 'since one of the & normalizing factors ', & 'is zero! & cross_normx_factor(',k,',',j,') = ', & cross_normx_factor(k,j), & ' & cross_normy_factor(',k,',',j,') = ', & cross_normy_factor(k,j) CALL message( 'data_output_profiles', 'PA0185',& 0, 1, 0, 6, 0 ) cross_normx_factor(k,j) = 1.0 cross_normy_factor(k,j) = 1.0 cross_normalized_x(j) = ' ' cross_normalized_y(j) = ' ' ENDIF ! !-- If required, extend normalized x-value range of the respective !-- cross, provided it has not been specified in check_parameters. !-- Determination over all (sub-)regions. IF ( cross_uxmin_normalized(j) == 0.0 .AND. & cross_uxmax_normalized(j) == 0.0 ) THEN DO sr = 0, statistic_regions uxmi = MINVAL( hom(:nz_do1d,1,dopr_index(i),sr) ) / & cross_normx_factor(k,j) uxma = MAXVAL( hom(:nz_do1d,1,dopr_index(i),sr) ) / & cross_normx_factor(k,j) ! !-- When the value range of the first line in the !-- corresponding cross is determined, its value range is !-- simply adopted. IF ( cross_uxmin_normalized_computed(j) > & cross_uxmax_normalized_computed(j) ) THEN cross_uxmin_normalized_computed(j) = uxmi cross_uxmax_normalized_computed(j) = uxma ELSE cross_uxmin_normalized_computed(j) = & MIN( cross_uxmin_normalized_computed(j), uxmi ) cross_uxmax_normalized_computed(j) = & MAX( cross_uxmax_normalized_computed(j), uxma ) ENDIF ENDDO ENDIF ENDIF ! Index determination ENDIF ! profil output ENDDO ! Loop over dopr_n ENDIF ! Output on PE0 ! !-- If averaging has been done above, the summation counter must be re-set. IF ( averaging_interval_pr /= 0.0 ) THEN average_count_pr = 0 ENDIF CALL cpu_log( log_point(15), 'data_output_profiles','stop', 'nobarrier' ) ! !-- Formats 100 FORMAT ('#1 ',A,1X,A) 101 FORMAT (E15.7,1X,E15.7) 102 FORMAT ('NEXT') END SUBROUTINE data_output_profiles