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

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

code has been put under the GNU General Public License (v3)

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