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

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

New:
---

Porting of FFT-solver for serial runs to GPU using CUDA FFT,
preprocessor lines in transpose routines rearranged, so that routines can also
be used in serial (non-parallel) mode,
transpositions also carried out in serial mode, routines fftx, fftxp replaced
by calls of fft_x, fft_x replaced by fft_x_1d in the 1D-decomposition routines
(Makefile, Makefile_check, fft_xy, poisfft, poisfft_hybrid, transpose, new: cuda_fft_interfaces)

--stdin argument for mpiexec on lckyuh, -y and -Y settings output to header (mrun)

Changed:


Module array_kind renamed precision_kind
(check_open, data_output_3d, fft_xy, modules, user_data_output_3d)

some format changes for coupled atmosphere-ocean runs (header)
small changes in code formatting (microphysics, prognostic_equations)

Errors:


bugfix: default value (0) assigned to coupling_start_time (modules)
bugfix: initial time for preruns of coupled runs is output as -coupling_start_time (data_output_profiles)

  • 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! bugfix: initial time for preruns of coupled runs is output as -coupling_start_time
23!
24! Former revisions:
25! -----------------
26! $Id: data_output_profiles.f90 1106 2013-03-04 05:31:38Z 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 to time axis, but only if an output
129!--             is required for at least one of the profiles. The initial time
130!--             is either 0, or, in case of a prerun for coupled atmosphere-ocean
131!--             runs, has a negative value
132                DO  i = 1, dopr_n
133                IF ( dopr_initial_index(i) /= 0 )  THEN
134                   nc_stat = NF90_PUT_VAR( id_set_pr, id_var_time_pr,  &
135                                           (/ -coupling_start_time /), &
136                                           start = (/ 1 /), count = (/ 1 /) )
137                      CALL handle_netcdf_error( 'data_output_profiles', 329 )
138                      output_for_t0 = .TRUE.
139                      EXIT
140                   ENDIF
141                ENDDO
142
143!
144!--             Store normalization factors
145                nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(1), & ! wpt0
146                                     (/ hom_sum(nzb,18,normalizing_region) /), &
147                                        start = (/ 1 /), count = (/ 1 /) )
148                CALL handle_netcdf_error( 'data_output_profiles', 330 )
149
150                nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(2), & ! ws2
151                           (/ hom_sum(nzb+8,pr_palm,normalizing_region)**2 /), &
152                                        start = (/ 1 /), count = (/ 1 /) )
153                CALL handle_netcdf_error( 'data_output_profiles', 331 )
154                nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(3), & ! tsw2
155                           (/ hom_sum(nzb+3,pr_palm,normalizing_region)**2 /), &
156                                     start = (/ 1 /), count = (/ 1 /) )
157                CALL handle_netcdf_error( 'data_output_profiles', 332 )
158                nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(4), & ! ws3
159                           (/ hom_sum(nzb+8,pr_palm,normalizing_region)**3 /), &
160                                        start = (/ 1 /), count = (/ 1 /) )
161                CALL handle_netcdf_error( 'data_output_profiles', 333 )
162
163                nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(5), &!ws2tsw
164                           (/ hom_sum(nzb+8,pr_palm,normalizing_region)**3 *   &
165                              hom_sum(nzb+3,pr_palm,normalizing_region)    /), &
166                                        start = (/ 1 /), count = (/ 1 /) )
167                CALL handle_netcdf_error( 'data_output_profiles', 334 )
168
169                nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(6), &!wstsw2
170                           (/ hom_sum(nzb+8,pr_palm,normalizing_region) *      &
171                              hom_sum(nzb+3,pr_palm,normalizing_region)**2 /), &
172                                        start = (/ 1 /), count = (/ 1 /) )
173                CALL handle_netcdf_error( 'data_output_profiles', 335 )
174
175                nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(7), & ! z_i
176                              (/ hom_sum(nzb+6,pr_palm,normalizing_region) /), &
177                                        start = (/ 1 /), count = (/ 1 /) )
178                CALL handle_netcdf_error( 'data_output_profiles', 336 )
179             
180#endif
181             ENDIF
182!
183!--          Loop over all 1D variables
184             DO  i = 1, dopr_n
185
186                IF ( dopr_initial_index(i) /= 0 )  THEN
187
188!
189!--                Output for the individual (sub-)regions
190                   DO  sr = 0, statistic_regions
191
192                      IF ( netcdf_output )  THEN
193#if defined( __netcdf )
194!
195!--                      Write data to netcdf file
196                         nc_stat = NF90_PUT_VAR( id_set_pr, id_var_dopr(i,sr),    &
197                                       hom(nzb:nzt+1,1,dopr_initial_index(i),sr), &
198                                                 start = (/ 1, 1 /),              &
199                                                 count = (/ nzt-nzb+2, 1 /) )
200                         CALL handle_netcdf_error( 'data_output_profiles', 337 )
201#endif
202                      ENDIF
203
204                   ENDDO
205
206                ENDIF   ! Initial profile available
207
208             ENDDO   ! Loop over dopr_n for initial profiles
209
210             IF ( netcdf_output  .AND.  output_for_t0 )  THEN
211                dopr_time_count = dopr_time_count + 1
212             ENDIF
213
214          END IF
215       ENDIF   ! Initial profiles
216
217       IF ( netcdf_output )  THEN
218#if defined( __netcdf )
219
220!
221!--       Store time to time axis         
222          nc_stat = NF90_PUT_VAR( id_set_pr, id_var_time_pr,        &
223                                  (/ time_since_reference_point /), &
224                                  start = (/ dopr_time_count /),    &
225                                  count = (/ 1 /) )
226          CALL handle_netcdf_error( 'data_output_profiles', 338 )
227
228!
229!--       Store normalization factors
230          nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(1), &  ! wpt0
231                                  (/ hom_sum(nzb,18,normalizing_region) /), &
232                                  start = (/ dopr_time_count /),               &
233                                  count = (/ 1 /) )
234          CALL handle_netcdf_error( 'data_output_profiles', 339 )
235
236          nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(2), &  ! ws2
237                        (/ hom_sum(nzb+8,pr_palm,normalizing_region)**2 /), &
238                                  start = (/ dopr_time_count /),               &
239                                  count = (/ 1 /) )
240          CALL handle_netcdf_error( 'data_output_profiles', 340 )
241
242          nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(3), &  ! tsw2
243                        (/ hom_sum(nzb+3,pr_palm,normalizing_region)**2 /), &
244                                  start = (/ dopr_time_count /),               &
245                                  count = (/ 1 /) )
246          CALL handle_netcdf_error( 'data_output_profiles', 341 )
247
248          nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(4), &  ! ws3
249                        (/ hom_sum(nzb+8,pr_palm,normalizing_region)**3 /), &
250                                  start = (/ dopr_time_count /),               &
251                                  count = (/ 1 /) )
252          CALL handle_netcdf_error( 'data_output_profiles', 342 )
253
254          nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(5), &  ! ws2tsw
255                        (/ hom_sum(nzb+8,pr_palm,normalizing_region)**3 *   &
256                           hom_sum(nzb+3,pr_palm,normalizing_region)    /), &
257                                  start = (/ dopr_time_count /),               &
258                                  count = (/ 1 /) )
259          CALL handle_netcdf_error( 'data_output_profiles', 343 )
260         
261          nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(6), &  ! wstsw2
262                        (/ hom_sum(nzb+8,pr_palm,normalizing_region) *      &
263                           hom_sum(nzb+3,pr_palm,normalizing_region)**2 /), &
264                                  start = (/ dopr_time_count /),               &
265                                  count = (/ 1 /) )
266          CALL handle_netcdf_error( 'data_output_profiles', 344 )
267
268          nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(7), &  ! z_i
269                           (/ hom_sum(nzb+6,pr_palm,normalizing_region) /), &
270                                  start = (/ dopr_time_count /),               &
271                                  count = (/ 1 /) )
272          CALL handle_netcdf_error( 'data_output_profiles', 345 )
273#endif
274       ENDIF
275
276!
277!--    Output of the individual (non-initial) profiles
278       DO  i = 1, dopr_n
279
280!
281!--       Output for the individual (sub-)domains
282          DO  sr = 0, statistic_regions
283
284             IF ( netcdf_output )  THEN
285#if defined( __netcdf )
286!
287!--             Write data to netcdf file
288                nc_stat = NF90_PUT_VAR( id_set_pr, id_var_dopr(i,sr),          &
289                                        hom_sum(nzb:nzt+1,dopr_index(i),sr),&
290                                        start = (/ 1, dopr_time_count /),      &
291                                        count = (/ nzt-nzb+2, 1 /) )
292                CALL handle_netcdf_error( 'data_output_profiles', 346 )
293#endif
294             ENDIF
295
296          ENDDO
297
298       ENDDO
299
300    ENDIF  ! Output on PE0
301
302!
303!-- If averaging has been done above, the summation counter must be re-set.
304    IF ( averaging_interval_pr /= 0.0 )  THEN
305       average_count_pr = 0
306    ENDIF
307
308    CALL cpu_log( log_point(15), 'data_output_profiles','stop', 'nobarrier' )
309
310!
311!-- Formats
312100 FORMAT ('#1 ',A,1X,A)
313101 FORMAT (E15.7,1X,E15.7)
314102 FORMAT ('NEXT')
315
316 END SUBROUTINE data_output_profiles
Note: See TracBrowser for help on using the repository browser.