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

Last change on this file since 1575 was 1354, checked in by heinze, 10 years ago

last commit documented

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