source: palm/trunk/SOURCE/data_output_tseries.f90 @ 2

Last change on this file since 2 was 1, checked in by raasch, 17 years ago

Initial repository layout and content

File size: 6.8 KB
Line 
1 SUBROUTINE data_output_tseries
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Log: data_output_tseries.f90,v $
11! Revision 1.13  2006/03/14 12:42:51  raasch
12! Error removed: NetCDF output only if switched on
13!
14! Revision 1.12  2006/02/23 10:30:54  raasch
15! Former routine plot_ts renamed data_output_tseries
16! error number argument for handle_netcdf_error
17! plts_anz renamed dots_n
18!
19! Revision 1.11  2005/05/18 15:50:54  raasch
20! Extensions for NetCDF output
21!
22! Revision 1.10  2003/04/16 13:10:40  raasch
23! Output of Monin Obukhov length included
24!
25! Revision 1.9  2001/03/30 07:45:34  raasch
26! Translation of remaining German identifiers (variables, subroutines, etc.)
27!
28! Revision 1.8  2001/01/22 20:36:59  letzel
29! All comments translated into English.
30!
31! Revision 1.7  2001/01/22 07:42:50  raasch
32! Module test_variables removed
33!
34! Revision 1.6  1999/02/05 09:14:35  raasch
35! Erweiterung fuer Ausgabe von Upstream-Anteilen, Erweiterung von ts_value
36! auf 30 Elemente
37!
38! Revision 1.5  1998/07/06 12:26:59  raasch
39! + USE test_variables
40!
41! Revision 1.4  1998/04/15 11:22:22  raasch
42! Erweiterung der Zeitreihenausgabe auf oberflaechennahe Temperaturen und
43! Waermestroeme
44!
45! Revision 1.3  1998/03/30 11:48:03  raasch
46! Divergenzen stehen jetzt in hom
47!
48! Revision 1.2  1998/03/25 13:56:01  raasch
49! Erweiterungen fuer Gebietsstatistiken,
50! dt in dt_3d umbenannt
51!
52! Revision 1.1  1998/03/03 08:00:13  raasch
53! Initial revision
54!
55!
56! Description:
57! ------------
58! Time series output for PROFIL. Always all time series are stored. A selection
59! can be applied via the PROFIL-parameters in close_file.
60!------------------------------------------------------------------------------!
61
62    USE control_parameters
63    USE cpulog
64    USE indices
65    USE interfaces
66    USE netcdf_control
67    USE pegrid
68    USE profil_parameter
69    USE statistics
70
71    IMPLICIT NONE
72
73
74    INTEGER ::  file_id, i, j, sr
75    REAL    ::  ts_value(30)
76
77
78!
79!-- If required, compute statistics.
80    IF ( .NOT. flow_statistics_called )  CALL flow_statistics
81
82!
83!-- Flow_statistics has its own cpu-time measuring.
84    CALL cpu_log( log_point(21), 'data_output_tseries', 'start' )
85
86    IF ( myid == 0 )  THEN
87
88!
89!--    Open file for time series output in NetCDF format
90       IF ( netcdf_output )  THEN
91          dots_time_count = dots_time_count + 1
92          CALL check_open( 105 )
93#if defined( __netcdf )
94!
95!--       Update the time series time axis
96          nc_stat = NF90_PUT_VAR( id_set_ts, id_var_time_ts,     &
97                                  (/ simulated_time /),          &
98                                  start = (/ dots_time_count /), &
99                                  count = (/ 1 /) )
100          IF (nc_stat /= NF90_NOERR)  CALL handle_netcdf_error( 350 )
101#endif
102       ENDIF
103
104!
105!--    Time series output for the total domain (and each subregion, if
106!--    applicable)
107       DO  sr = 0, statistic_regions
108!
109!--       Open file for time series output.
110          IF ( profil_output )  THEN
111             file_id = 50 + sr
112             CALL check_open( file_id )
113          ENDIF
114
115!
116!--       Collect and printout all time series quantities in a single line.
117          ts_value(1) = hom(nzb+4,1,var_hom,sr)     ! E
118          ts_value(2) = hom(nzb+5,1,var_hom,sr)     ! E*
119          ts_value(3) = dt_3d
120          ts_value(4) = hom(nzb,1,var_hom,sr)       ! u*
121          ts_value(5) = hom(nzb+3,1,var_hom,sr)     ! th*
122          ts_value(6) = u_max
123          ts_value(7) = v_max
124          ts_value(8) = w_max
125          ts_value(9) = hom(nzb+10,1,var_sum,sr)    ! new divergence
126          ts_value(10) = hom(nzb+9,1,var_hom,sr)    ! old Divergence
127          ts_value(11) = hom(nzb+6,1,var_hom,sr)    ! z_i(1)
128          ts_value(12) = hom(nzb+7,1,var_hom,sr)    ! z_i(2)
129          ts_value(13) = hom(nzb+8,1,var_hom,sr)    ! w*
130          ts_value(14) = hom(nzb,1,16,sr)           ! w'pt'   at k=0
131          ts_value(15) = hom(nzb+1,1,16,sr)         ! w'pt'   at k=1
132          ts_value(16) = hom(nzb+1,1,18,sr)         ! wpt     at k=1
133          ts_value(17) = hom(nzb,1,4,sr)            ! pt(0)
134          ts_value(18) = hom(nzb+1,1,4,sr)          ! pt(zp)
135          ts_value(19) = hom(nzb+9,1,var_hom-1,sr)  ! splptx
136          ts_value(20) = hom(nzb+10,1,var_hom-1,sr) ! splpty
137          ts_value(21) = hom(nzb+11,1,var_hom-1,sr) ! splptz
138          IF ( ts_value(5) /= 0.0 )  THEN
139             ts_value(22) = ts_value(4)**2 / &
140                            ( kappa * g * ts_value(5) / ts_value(18) )  ! L
141          ELSE
142             ts_value(22) = 10000.0
143          ENDIF
144
145#if defined( __netcdf )
146          IF ( netcdf_output )  THEN
147             DO  i = 1, dots_num
148                nc_stat = NF90_PUT_VAR( id_set_ts, id_var_dots(i,sr),  &
149                                        (/ ts_value(i) /),             &
150                                        start = (/ dots_time_count /), &
151                                        count = (/ 1 /) )
152                IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 351 )
153             ENDDO
154          ENDIF
155#endif
156
157          IF ( profil_output )  THEN
158             WRITE ( file_id, 500 )  simulated_time, ts_value(1:22)
159!
160!--          y-value range of the crosses to be drawn by PROFIL
161!--          If required, enlarge them, provided they have not yet been
162!--          specified in
163!--          check_parameters
164             DO  i = 1, dots_n
165
166                j = dots_crossindex(i)
167
168                IF ( cross_ts_uymin(j) == 999.999 )  THEN
169!
170!--                When the value range of the first line in the corresponding
171!--                cross is determined, its value range is simply adopted.
172                   IF ( cross_ts_uymin_computed(j) == 999.999 ) &
173                   THEN
174                      cross_ts_uymin_computed(j) = ts_value(dots_index(i))
175                   ELSE
176                      cross_ts_uymin_computed(j) = &
177                         MIN(cross_ts_uymin_computed(j),ts_value(dots_index(i)))
178                   ENDIF
179                ENDIF
180
181                IF ( cross_ts_uymax(j) == 999.999 )  THEN
182!
183!--                When the value range of the first line in the corresponding
184!--                cross is determined, its value range is simply adopted.
185                   IF ( cross_ts_uymax_computed(j) == 999.999 ) &
186                   THEN
187                      cross_ts_uymax_computed(j) = ts_value(dots_index(i))
188                   ELSE
189                      cross_ts_uymax_computed(j) = &
190                         MAX(cross_ts_uymax_computed(j),ts_value(dots_index(i)))
191                   ENDIF
192                ENDIF
193
194             ENDDO
195
196          ENDIF
197
198       ENDDO   ! Loop of subregions.
199
200    ENDIF
201
202
203    CALL cpu_log( log_point(21), 'data_output_tseries','stop', 'nobarrier' )
204
205!
206!-- formats
207500 FORMAT (23(E15.7,1X))
208
209 END SUBROUTINE data_output_tseries
Note: See TracBrowser for help on using the repository browser.