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

Last change on this file since 1319 was 1319, checked in by raasch, 10 years ago

last commit documented

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