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

Last change on this file since 964 was 964, checked in by raasch, 12 years ago

old profil-parameters (cross_xtext, cross_normalized_x, etc. ) and respective code removed
(check_open, check_parameters, close_file, data_output_profiles, data_output_spectra, header, modules, parin)

reformatting (netcdf)

append feature removed from unit 14 (check_open)

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