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

Last change on this file since 3979 was 3655, checked in by knoop, 5 years ago

Bugfix: made "unit" and "found" intend INOUT in module interface subroutines + automatic copyright update

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