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

Last change on this file since 1037 was 1037, checked in by raasch, 11 years ago

last commit documented

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