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

Last change on this file since 55 was 48, checked in by raasch, 17 years ago

preliminary version, several changes to be explained later

  • Property svn:keywords set to Id
File size: 2.6 KB
Line 
1 SUBROUTINE data_output_tseries
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6! Collection of time series quantities moved to routine flow_statistics,
7! output for "profil" removed
8!
9! Former revisions:
10! -----------------
11! $Id: data_output_tseries.f90 48 2007-03-06 12:28:36Z raasch $
12! RCS Log replace by Id keyword, revision history cleaned up
13!
14! Revision 1.13  2006/03/14 12:42:51  raasch
15! Error removed: NetCDF output only if switched on
16!
17! Revision 1.1  1998/03/03 08:00:13  raasch
18! Initial revision
19!
20!
21! Description:
22! ------------
23! Time series output for PROFIL. Always all time series are stored. A selection
24! can be applied via the PROFIL-parameters in close_file.
25!------------------------------------------------------------------------------!
26
27    USE control_parameters
28    USE cpulog
29    USE indices
30    USE interfaces
31    USE netcdf_control
32    USE pegrid
33    USE profil_parameter
34    USE statistics
35
36    IMPLICIT NONE
37
38
39    INTEGER ::  file_id, i, j, sr
40
41
42!
43!-- If required, compute statistics.
44    IF ( .NOT. flow_statistics_called )  CALL flow_statistics
45
46!
47!-- Flow_statistics has its own cpu-time measuring.
48    CALL cpu_log( log_point(21), 'data_output_tseries', 'start' )
49
50    IF ( myid == 0 )  THEN
51
52!
53!--    Open file for time series output in NetCDF format
54       IF ( netcdf_output )  THEN
55          dots_time_count = dots_time_count + 1
56          CALL check_open( 105 )
57#if defined( __netcdf )
58!
59!--       Update the time series time axis
60          nc_stat = NF90_PUT_VAR( id_set_ts, id_var_time_ts,     &
61                                  (/ simulated_time /),          &
62                                  start = (/ dots_time_count /), &
63                                  count = (/ 1 /) )
64          IF (nc_stat /= NF90_NOERR)  CALL handle_netcdf_error( 350 )
65#endif
66       ENDIF
67
68!
69!--    Time series output for the total domain (and each subregion, if
70!--    applicable)
71       DO  sr = 0, statistic_regions
72
73#if defined( __netcdf )
74          IF ( netcdf_output )  THEN
75             DO  i = 1, dots_num
76                nc_stat = NF90_PUT_VAR( id_set_ts, id_var_dots(i,sr),  &
77                                        (/ ts_value(i,sr) /),          &
78                                        start = (/ dots_time_count /), &
79                                        count = (/ 1 /) )
80                IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 351 )
81             ENDDO
82          ENDIF
83#endif
84
85       ENDDO
86
87    ENDIF
88
89
90    CALL cpu_log( log_point(21), 'data_output_tseries','stop', 'nobarrier' )
91
92!
93!-- formats
94500 FORMAT (23(E15.7,1X))
95
96 END SUBROUTINE data_output_tseries
Note: See TracBrowser for help on using the repository browser.