source: palm/trunk/SOURCE/data_output_profiles.f90 @ 965

Last change on this file since 965 was 965, checked in by raasch, 12 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 10.8 KB
RevLine 
[1]1 SUBROUTINE data_output_profiles
2
3!------------------------------------------------------------------------------!
[254]4! Current revisions:
[1]5! -----------------
[392]6!
[965]7!
[392]8! Former revisions:
9! -----------------
10! $Id: data_output_profiles.f90 965 2012-07-26 09:29:52Z raasch $
11!
[965]12! 964 2012-07-26 09:14:24Z raasch
13! code for profil-output removed
14!
[392]15! 345 2009-07-01 14:37:56Z heinze
[345]16! In case of restart runs without extension, initial profiles are not written
17! to NetCDF-file anymore.
[291]18! simulated_time in NetCDF output replaced by time_since_reference_point.
[263]19! Output of NetCDF messages with aid of message handling routine.
[254]20! Output of messages replaced by message handling routine.
[1]21!
[198]22! 197 2008-09-16 15:29:03Z raasch
23! Time coordinate t=0 stored on netcdf-file only if an output is required for
24! this time for at least one of the profiles
25!
26! February 2007
[3]27! RCS Log replace by Id keyword, revision history cleaned up
28!
[90]29! 87 2007-05-22 15:46:47Z raasch
30! var_hom renamed pr_palm
31!
[1]32! Revision 1.18  2006/08/16 14:27:04  raasch
33! PRINT* statements for testing removed
34!
35! Revision 1.1  1997/09/12 06:28:48  raasch
36! Initial revision
37!
38!
39! Description:
40! ------------
41! Plot output of 1D-profiles for PROFIL
42!------------------------------------------------------------------------------!
43
44    USE control_parameters
45    USE cpulog
46    USE indices
47    USE interfaces
48    USE netcdf_control
49    USE pegrid
50    USE profil_parameter
51    USE statistics
52
53    IMPLICIT NONE
54
55
56    INTEGER ::  i, id, ilc, ils, j, k, sr
57
58!
59!-- If required, compute statistics
60    IF ( .NOT. flow_statistics_called )  CALL flow_statistics
61
62!
63!-- Flow_statistics has its own CPU time measurement
64    CALL cpu_log( log_point(15), 'data_output_profiles', 'start' )
65
66!
67!-- If required, compute temporal average
68    IF ( averaging_interval_pr == 0.0 )  THEN
69       hom_sum(:,:,:) = hom(:,1,:,:)
70    ELSE
71       IF ( average_count_pr > 0 )  THEN
72          hom_sum = hom_sum / REAL( average_count_pr )
73       ELSE
74!
75!--       This case may happen if dt_dopr is changed in the d3par-list of
76!--       a restart run
77          RETURN
78       ENDIF
79    ENDIF
80
81   
82    IF ( myid == 0 )  THEN
83
84!
85!--    Plot-output for each (sub-)region
86
87!
88!--    Open file for profile output in NetCDF format
89       IF ( netcdf_output )  THEN
90          CALL check_open( 104 )
91       ENDIF
92
93!
94!--    Increment the counter for number of output times
95       dopr_time_count = dopr_time_count + 1
96
97!
98!--    Output of initial profiles
99       IF ( dopr_time_count == 1 )  THEN
[345]100       
101          IF ( .NOT. output_for_t0 ) THEN
[1]102
[345]103             IF ( netcdf_output )  THEN
104#if defined( __netcdf )         
[1]105!
[345]106!--             Store initial time (t=0) to time axis, but only if an output
107!--             is required for at least one of the profiles
108                DO  i = 1, dopr_n
[197]109                IF ( dopr_initial_index(i) /= 0 )  THEN
110                   nc_stat = NF90_PUT_VAR( id_set_pr, id_var_time_pr,  &
[345]111                                              (/ 0.0 /), start = (/ 1 /), &
112                                              count = (/ 1 /) )
113                      CALL handle_netcdf_error( 'data_output_profiles', 329 )
114                      output_for_t0 = .TRUE.
115                      EXIT
116                   ENDIF
117                ENDDO
[1]118
119!
[345]120!--             Store normalization factors
121                nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(1), & ! wpt0
122                                     (/ hom_sum(nzb,18,normalizing_region) /), &
123                                        start = (/ 1 /), count = (/ 1 /) )
124                CALL handle_netcdf_error( 'data_output_profiles', 330 )
[1]125
[345]126                nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(2), & ! ws2
127                           (/ hom_sum(nzb+8,pr_palm,normalizing_region)**2 /), &
128                                        start = (/ 1 /), count = (/ 1 /) )
129                CALL handle_netcdf_error( 'data_output_profiles', 331 )
130                nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(3), & ! tsw2
131                           (/ hom_sum(nzb+3,pr_palm,normalizing_region)**2 /), &
[1]132                                     start = (/ 1 /), count = (/ 1 /) )
[345]133                CALL handle_netcdf_error( 'data_output_profiles', 332 )
134                nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(4), & ! ws3
135                           (/ hom_sum(nzb+8,pr_palm,normalizing_region)**3 /), &
136                                        start = (/ 1 /), count = (/ 1 /) )
137                CALL handle_netcdf_error( 'data_output_profiles', 333 )
[1]138
[345]139                nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(5), &!ws2tsw
140                           (/ hom_sum(nzb+8,pr_palm,normalizing_region)**3 *   &
141                              hom_sum(nzb+3,pr_palm,normalizing_region)    /), &
142                                        start = (/ 1 /), count = (/ 1 /) )
143                CALL handle_netcdf_error( 'data_output_profiles', 334 )
[1]144
[345]145                nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(6), &!wstsw2
146                           (/ hom_sum(nzb+8,pr_palm,normalizing_region) *      &
147                              hom_sum(nzb+3,pr_palm,normalizing_region)**2 /), &
148                                        start = (/ 1 /), count = (/ 1 /) )
149                CALL handle_netcdf_error( 'data_output_profiles', 335 )
[1]150
[345]151                nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(7), & ! z_i
152                              (/ hom_sum(nzb+6,pr_palm,normalizing_region) /), &
153                                        start = (/ 1 /), count = (/ 1 /) )
154                CALL handle_netcdf_error( 'data_output_profiles', 336 )
155             
[1]156#endif
[345]157             ENDIF
[1]158!
[345]159!--          Loop over all 1D variables
160             DO  i = 1, dopr_n
[1]161
[345]162                IF ( dopr_initial_index(i) /= 0 )  THEN
[1]163
164!
[345]165!--                Output for the individual (sub-)regions
166                   DO  sr = 0, statistic_regions
[1]167
[345]168                      IF ( netcdf_output )  THEN
[1]169#if defined( __netcdf )
170!
[345]171!--                      Write data to netcdf file
172                         nc_stat = NF90_PUT_VAR( id_set_pr, id_var_dopr(i,sr),    &
173                                       hom(nzb:nzt+1,1,dopr_initial_index(i),sr), &
174                                                 start = (/ 1, 1 /),              &
175                                                 count = (/ nzt-nzb+2, 1 /) )
176                         CALL handle_netcdf_error( 'data_output_profiles', 337 )
[1]177#endif
[345]178                      ENDIF
[1]179
[345]180                   ENDDO
[1]181
[345]182                ENDIF   ! Initial profile available
[1]183
[345]184             ENDDO   ! Loop over dopr_n for initial profiles
[1]185
[345]186             IF ( netcdf_output  .AND.  output_for_t0 )  THEN
187                dopr_time_count = dopr_time_count + 1
188             ENDIF
[1]189
[345]190          END IF
[1]191       ENDIF   ! Initial profiles
192
193       IF ( netcdf_output )  THEN
194#if defined( __netcdf )
[345]195
[1]196!
197!--       Store time to time axis         
[291]198          nc_stat = NF90_PUT_VAR( id_set_pr, id_var_time_pr,        &
199                                  (/ time_since_reference_point /), &
200                                  start = (/ dopr_time_count /),    &
[1]201                                  count = (/ 1 /) )
[263]202          CALL handle_netcdf_error( 'data_output_profiles', 338 )
[1]203
204!
205!--       Store normalization factors
206          nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(1), &  ! wpt0
207                                  (/ hom_sum(nzb,18,normalizing_region) /), &
208                                  start = (/ dopr_time_count /),               &
209                                  count = (/ 1 /) )
[263]210          CALL handle_netcdf_error( 'data_output_profiles', 339 )
[1]211
212          nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(2), &  ! ws2
[87]213                        (/ hom_sum(nzb+8,pr_palm,normalizing_region)**2 /), &
[1]214                                  start = (/ dopr_time_count /),               &
215                                  count = (/ 1 /) )
[263]216          CALL handle_netcdf_error( 'data_output_profiles', 340 )
[1]217
218          nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(3), &  ! tsw2
[87]219                        (/ hom_sum(nzb+3,pr_palm,normalizing_region)**2 /), &
[1]220                                  start = (/ dopr_time_count /),               &
221                                  count = (/ 1 /) )
[263]222          CALL handle_netcdf_error( 'data_output_profiles', 341 )
[1]223
224          nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(4), &  ! ws3
[87]225                        (/ hom_sum(nzb+8,pr_palm,normalizing_region)**3 /), &
[1]226                                  start = (/ dopr_time_count /),               &
227                                  count = (/ 1 /) )
[263]228          CALL handle_netcdf_error( 'data_output_profiles', 342 )
[1]229
230          nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(5), &  ! ws2tsw
[87]231                        (/ hom_sum(nzb+8,pr_palm,normalizing_region)**3 *   &
232                           hom_sum(nzb+3,pr_palm,normalizing_region)    /), &
[1]233                                  start = (/ dopr_time_count /),               &
234                                  count = (/ 1 /) )
[263]235          CALL handle_netcdf_error( 'data_output_profiles', 343 )
236         
[1]237          nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(6), &  ! wstsw2
[87]238                        (/ hom_sum(nzb+8,pr_palm,normalizing_region) *      &
239                           hom_sum(nzb+3,pr_palm,normalizing_region)**2 /), &
[1]240                                  start = (/ dopr_time_count /),               &
241                                  count = (/ 1 /) )
[263]242          CALL handle_netcdf_error( 'data_output_profiles', 344 )
[1]243
244          nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(7), &  ! z_i
[87]245                           (/ hom_sum(nzb+6,pr_palm,normalizing_region) /), &
[1]246                                  start = (/ dopr_time_count /),               &
247                                  count = (/ 1 /) )
[263]248          CALL handle_netcdf_error( 'data_output_profiles', 345 )
[1]249#endif
250       ENDIF
251
252!
253!--    Output of the individual (non-initial) profiles
254       DO  i = 1, dopr_n
255
256!
257!--       Output for the individual (sub-)domains
258          DO  sr = 0, statistic_regions
259
260             IF ( netcdf_output )  THEN
261#if defined( __netcdf )
262!
263!--             Write data to netcdf file
264                nc_stat = NF90_PUT_VAR( id_set_pr, id_var_dopr(i,sr),          &
265                                        hom_sum(nzb:nzt+1,dopr_index(i),sr),&
266                                        start = (/ 1, dopr_time_count /),      &
267                                        count = (/ nzt-nzb+2, 1 /) )
[263]268                CALL handle_netcdf_error( 'data_output_profiles', 346 )
[1]269#endif
270             ENDIF
271
272          ENDDO
273
[964]274       ENDDO
[1]275
276    ENDIF  ! Output on PE0
277
278!
279!-- If averaging has been done above, the summation counter must be re-set.
280    IF ( averaging_interval_pr /= 0.0 )  THEN
281       average_count_pr = 0
282    ENDIF
283
284    CALL cpu_log( log_point(15), 'data_output_profiles','stop', 'nobarrier' )
285
286!
287!-- Formats
288100 FORMAT ('#1 ',A,1X,A)
289101 FORMAT (E15.7,1X,E15.7)
290102 FORMAT ('NEXT')
291
292 END SUBROUTINE data_output_profiles
Note: See TracBrowser for help on using the repository browser.