source: palm/tags/release-3.10/SOURCE/data_output_profiles.f90 @ 1614

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

last commit documented

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