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

Last change on this file since 1969 was 1958, checked in by suehring, 8 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 4.6 KB
Line 
1!> @file data_output_flight.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_flight.f90 1958 2016-07-07 10:51:40Z suehring $
26!
27! 1957 2016-07-07 10:43:48Z suehring
28! Initial revision
29!
30!
31! Description:
32! ------------
33!> Writing data from flight measurements on file.
34!------------------------------------------------------------------------------!
35 SUBROUTINE data_output_flight
36 
37#if defined( __netcdf )
38    USE control_parameters,                                                    &
39        ONLY:  message_string, num_leg, num_var_fl, run_description_header,    &
40               time_since_reference_point, virtual_flight
41
42    USE cpulog,                                                                &
43        ONLY:  cpu_log, log_point
44
45    USE flight_mod,                                                            &
46        ONLY:  sensor, x_pos, y_pos, z_pos
47
48    USE kinds
49
50    USE NETCDF
51
52    USE netcdf_interface,                                                      &
53        ONLY:  dofl_time_count, id_set_fl, id_var_dofl, id_var_time_fl,        &
54               id_var_x_fl, id_var_y_fl, id_var_z_fl, netcdf_handle_error,     &
55               nc_stat 
56             
57    USE pegrid
58
59    IMPLICIT NONE
60
61    INTEGER(iwp) ::  i !< loop variable for output quantities
62    INTEGER(iwp) ::  l !< loop variable for flight legs
63    INTEGER(iwp) ::  k !< internal count for variable labels and units
64
65    CALL cpu_log( log_point(64), 'data_output_flight', 'start' )
66
67!
68!-- Check if virtual flights are carried out
69    IF ( .NOT. virtual_flight )  RETURN
70
71!
72!-- Output is only performed on PE0
73    IF ( myid == 0 )  THEN
74
75!
76!--    Open file for flight output in NetCDF format
77       CALL check_open( 199 )
78
79!
80!--    Increment the counter for number of output times
81       dofl_time_count = dofl_time_count + 1
82
83!
84!--    Update the flight-output time and spatial coordinates
85       nc_stat = NF90_PUT_VAR( id_set_fl, id_var_time_fl,                      &
86                               (/ time_since_reference_point /),               &
87                               start = (/ dofl_time_count /),                  &
88                               count = (/ 1 /) )
89       CALL netcdf_handle_error( 'data_output_flight', 554 )
90
91       DO  l = 1, num_leg
92          nc_stat = NF90_PUT_VAR( id_set_fl, id_var_x_fl(l),                   &
93                                  (/ x_pos(l) /),                              &
94                                  start = (/ dofl_time_count /),               &
95                                  count = (/ 1 /) )
96          nc_stat = NF90_PUT_VAR( id_set_fl, id_var_y_fl(l),                   &
97                                  (/ y_pos(l) /),                              &
98                                  start = (/ dofl_time_count /),               &
99                                  count = (/ 1 /) )
100          nc_stat = NF90_PUT_VAR( id_set_fl, id_var_z_fl(l),                   &
101                                  (/ z_pos(l) /),                              &
102                                  start = (/ dofl_time_count /),               &
103                                  count = (/ 1 /) )
104          CALL netcdf_handle_error( 'data_output_flight', 555 )
105       ENDDO
106!
107!--    Output measured quantities
108       k = 1
109       DO  l = 1, num_leg
110          DO i = 1, num_var_fl
111             nc_stat = NF90_PUT_VAR( id_set_fl, id_var_dofl(k),                &
112                                     (/ sensor(i,l) /),                        &
113                                     start = (/ dofl_time_count /),            &
114                                     count = (/ 1 /) )
115
116             CALL netcdf_handle_error( 'data_output_flight', 556 )
117         
118             k = k + 1
119          ENDDO
120       ENDDO
121    ENDIF
122   
123    CALL cpu_log( log_point(64), 'data_output_flight', 'stop' )
124   
125#endif
126 END SUBROUTINE data_output_flight
Note: See TracBrowser for help on using the repository browser.