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

Last change on this file since 1952 was 1818, checked in by maronga, 8 years ago

last commit documented / copyright update

  • Property svn:keywords set to Id
File size: 4.7 KB
Line 
1!> @file data_output_tseries.f90
2!--------------------------------------------------------------------------------!
3! This file is part of PALM.
4!
5! PALM is free software: you can redistribute it and/or modify it under the terms
6! of the GNU General Public License as published by the Free Software Foundation,
7! either version 3 of the License, or (at your option) any later version.
8!
9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
10! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
11! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
12!
13! You should have received a copy of the GNU General Public License along with
14! PALM. If not, see <http://www.gnu.org/licenses/>.
15!
16! Copyright 1997-2016 Leibniz Universitaet Hannover
17!--------------------------------------------------------------------------------!
18!
19! Current revisions:
20! -----------------
21!
22!
23! Former revisions:
24! -----------------
25! $Id: data_output_tseries.f90 1818 2016-04-06 15:53:27Z suehring $
26!
27! 1783 2016-03-06 18:36:17Z raasch
28! name change of netcdf routines and module + related changes
29!
30! 1682 2015-10-07 23:56:08Z knoop
31! Code annotations made doxygen readable
32!
33! 1524 2015-01-14 13:18:19Z keck
34! Bugfix: increment dots_time_count after the call of subroutine check_open
35!
36! 1327 2014-03-21 11:00:16Z raasch
37! -netcdf output queries
38!
39! 1320 2014-03-20 08:40:49Z raasch
40! ONLY-attribute added to USE-statements,
41! kind-parameters added to all INTEGER and REAL declaration statements,
42! kinds are defined in new module kinds,
43! revision history before 2012 removed,
44! comment fields (!:) to be used for variable explanations added to
45! all variable declaration statements
46!
47! 1318 2014-03-17 13:35:16Z raasch
48! barrier argument removed from cpu_log.
49! module interfaces removed
50!
51! 1092 2013-02-02 11:24:22Z raasch
52! unused variables removed
53!
54! 1036 2012-10-22 13:43:42Z raasch
55! code put under GPL (PALM 3.9)
56!
57! Revision 1.1  1998/03/03 08:00:13  raasch
58! Initial revision
59!
60!
61! Description:
62! ------------
63!> Time series output for PROFIL. Always all time series are stored. A selection
64!> can be applied via the PROFIL-parameters in close_file.
65!------------------------------------------------------------------------------!
66 SUBROUTINE data_output_tseries
67 
68
69    USE control_parameters,                                                    &
70        ONLY:  dots_time_count, time_since_reference_point
71
72    USE cpulog,                                                                &
73        ONLY:  cpu_log, log_point 
74
75    USE kinds
76
77#if defined( __netcdf )
78    USE NETCDF
79#endif
80    USE netcdf_interface,                                                      &
81        ONLY:  dots_num, id_set_ts, id_var_dots, id_var_time_ts, nc_stat,      &
82               netcdf_handle_error
83
84    USE pegrid
85
86    USE profil_parameter
87   
88    USE statistics,                                                            &
89        ONLY:  flow_statistics_called, statistic_regions, ts_value
90
91    IMPLICIT NONE
92
93
94    INTEGER(iwp) ::  i  !<
95    INTEGER(iwp) ::  sr !<
96
97
98!
99!-- If required, compute statistics.
100    IF ( .NOT. flow_statistics_called )  CALL flow_statistics
101
102!
103!-- Flow_statistics has its own cpu-time measuring.
104    CALL cpu_log( log_point(21), 'data_output_tseries', 'start' )
105
106    IF ( myid == 0 )  THEN
107
108!
109!--    Open file for time series output in NetCDF format
110       CALL check_open( 105 )
111       
112!--    Increment the counter for number of output times
113!      CAUTION: The following line has to be after the call of the subroutine
114!               check_open, since check_open resets the counter dots_time_count
115!               to 0, if a new file is opened
116       dots_time_count = dots_time_count + 1
117       
118#if defined( __netcdf )
119!
120!--    Update the time series time axis
121       nc_stat = NF90_PUT_VAR( id_set_ts, id_var_time_ts,        &
122                               (/ time_since_reference_point /), &
123                               start = (/ dots_time_count /),    &
124                               count = (/ 1 /) )
125       CALL netcdf_handle_error( 'data_output_tseries', 350 )
126#endif
127
128!
129!--    Time series output for the total domain (and each subregion, if
130!--    applicable)
131       DO  sr = 0, statistic_regions
132
133#if defined( __netcdf )
134          DO  i = 1, dots_num
135             nc_stat = NF90_PUT_VAR( id_set_ts, id_var_dots(i,sr),  &
136                                     (/ ts_value(i,sr) /),          &
137                                     start = (/ dots_time_count /), &
138                                     count = (/ 1 /) )
139             CALL netcdf_handle_error( 'data_output_tseries', 351 )
140          ENDDO
141#endif
142
143       ENDDO
144
145    ENDIF
146
147
148    CALL cpu_log( log_point(21), 'data_output_tseries', 'stop' )
149
150!
151!-- formats
152500 FORMAT (23(E15.7,1X))
153
154 END SUBROUTINE data_output_tseries
Note: See TracBrowser for help on using the repository browser.