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

Last change on this file since 4180 was 4180, checked in by scharf, 5 years ago

removed comments in 'Former revisions' section that are older than 01.01.2019

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