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

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