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

Last change on this file since 2000 was 2000, checked in by knoop, 8 years ago

Forced header and separation lines into 80 columns

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