source: palm/trunk/SOURCE/data_output_flight.f90 @ 2716

Last change on this file since 2716 was 2716, checked in by kanani, 6 years ago

Correction of "Former revisions" section

  • Property svn:keywords set to Id
File size: 4.9 KB
Line 
1!> @file data_output_flight.f90
2!------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! 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-2017 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! ------------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: data_output_flight.f90 2716 2017-12-29 16:35:59Z kanani $
27! Corrected "Former revisions" section
28!
29! 2696 2017-12-14 17:12:51Z kanani
30! Change in file header (GPL part)
31!
32! 2101 2017-01-05 16:42:31Z suehring
33!
34! 2000 2016-08-20 18:09:15Z knoop
35! Forced header and separation lines into 80 columns
36!
37! 1957 2016-07-07 10:43:48Z suehring
38! Initial revision
39!
40!
41! Description:
42! ------------
43!> Writing data from flight measurements on file.
44!------------------------------------------------------------------------------!
45 SUBROUTINE data_output_flight
46 
47#if defined( __netcdf )
48    USE control_parameters,                                                    &
49        ONLY:  message_string, num_leg, num_var_fl, run_description_header,    &
50               time_since_reference_point, virtual_flight
51
52    USE cpulog,                                                                &
53        ONLY:  cpu_log, log_point
54
55    USE flight_mod,                                                            &
56        ONLY:  sensor, x_pos, y_pos, z_pos
57
58    USE kinds
59
60    USE NETCDF
61
62    USE netcdf_interface,                                                      &
63        ONLY:  dofl_time_count, id_set_fl, id_var_dofl, id_var_time_fl,        &
64               id_var_x_fl, id_var_y_fl, id_var_z_fl, netcdf_handle_error,     &
65               nc_stat 
66             
67    USE pegrid
68
69    IMPLICIT NONE
70
71    INTEGER(iwp) ::  i !< loop variable for output quantities
72    INTEGER(iwp) ::  l !< loop variable for flight legs
73    INTEGER(iwp) ::  k !< internal count for variable labels and units
74
75    CALL cpu_log( log_point(64), 'data_output_flight', 'start' )
76
77!
78!-- Check if virtual flights are carried out
79    IF ( .NOT. virtual_flight )  RETURN
80
81!
82!-- Output is only performed on PE0
83    IF ( myid == 0 )  THEN
84
85!
86!--    Open file for flight output in NetCDF format
87       CALL check_open( 199 )
88
89!
90!--    Increment the counter for number of output times
91       dofl_time_count = dofl_time_count + 1
92
93!
94!--    Update the flight-output time and spatial coordinates
95       nc_stat = NF90_PUT_VAR( id_set_fl, id_var_time_fl,                      &
96                               (/ time_since_reference_point /),               &
97                               start = (/ dofl_time_count /),                  &
98                               count = (/ 1 /) )
99       CALL netcdf_handle_error( 'data_output_flight', 554 )
100
101       DO  l = 1, num_leg
102          nc_stat = NF90_PUT_VAR( id_set_fl, id_var_x_fl(l),                   &
103                                  (/ x_pos(l) /),                              &
104                                  start = (/ dofl_time_count /),               &
105                                  count = (/ 1 /) )
106          nc_stat = NF90_PUT_VAR( id_set_fl, id_var_y_fl(l),                   &
107                                  (/ y_pos(l) /),                              &
108                                  start = (/ dofl_time_count /),               &
109                                  count = (/ 1 /) )
110          nc_stat = NF90_PUT_VAR( id_set_fl, id_var_z_fl(l),                   &
111                                  (/ z_pos(l) /),                              &
112                                  start = (/ dofl_time_count /),               &
113                                  count = (/ 1 /) )
114          CALL netcdf_handle_error( 'data_output_flight', 555 )
115       ENDDO
116!
117!--    Output measured quantities
118       k = 1
119       DO  l = 1, num_leg
120          DO i = 1, num_var_fl
121             nc_stat = NF90_PUT_VAR( id_set_fl, id_var_dofl(k),                &
122                                     (/ sensor(i,l) /),                        &
123                                     start = (/ dofl_time_count /),            &
124                                     count = (/ 1 /) )
125
126             CALL netcdf_handle_error( 'data_output_flight', 556 )
127         
128             k = k + 1
129          ENDDO
130       ENDDO
131    ENDIF
132   
133    CALL cpu_log( log_point(64), 'data_output_flight', 'stop' )
134   
135#endif
136 END SUBROUTINE data_output_flight
Note: See TracBrowser for help on using the repository browser.