Ignore:
Timestamp:
Jun 11, 2020 8:51:48 AM (4 years ago)
Author:
raasch
Message:

files re-formatted to follow the PALM coding standard

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/data_output_flight.f90

    r4360 r4559  
    11!> @file data_output_flight.f90
    2 !------------------------------------------------------------------------------!
     2!--------------------------------------------------------------------------------------------------!
    33! This file is part of the PALM model system.
    44!
    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.
     5! PALM is free software: you can redistribute it and/or modify it under the terms of the GNU General
     6! Public License as published by the Free Software Foundation, either version 3 of the License, or
     7! (at your option) any later version.
    98!
    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.
     9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the
     10! implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General
     11! Public License for more details.
    1312!
    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/>.
     13! You should have received a copy of the GNU General Public License along with PALM. If not, see
     14! <http://www.gnu.org/licenses/>.
    1615!
    1716! Copyright 1997-2020 Leibniz Universitaet Hannover
    18 !------------------------------------------------------------------------------!
     17!--------------------------------------------------------------------------------------------------!
    1918!
    2019! Current revisions:
     
    2524! -----------------
    2625! $Id$
     26! file re-formatted to follow the PALM coding standard
     27!
     28! 4360 2020-01-07 11:25:50Z suehring
    2729! Corrected "Former revisions" section
    28 ! 
     30!
    2931! 3655 2019-01-07 16:51:22Z knoop
    3032! unused variables removed
    31 ! 
     33!
    3234! 1957 2016-07-07 10:43:48Z suehring
    3335! Initial revision
     
    3739! ------------
    3840!> Writing data from flight measurements on file.
    39 !------------------------------------------------------------------------------!
     41!--------------------------------------------------------------------------------------------------!
    4042 SUBROUTINE data_output_flight
    41  
     43
    4244#if defined( __netcdf )
    43     USE control_parameters,                                                    &
     45    USE control_parameters,                                                                        &
    4446        ONLY:  num_leg, num_var_fl, time_since_reference_point, virtual_flight
    4547
    46     USE cpulog,                                                                &
     48    USE cpulog,                                                                                    &
    4749        ONLY:  cpu_log, log_point
    4850
    49     USE flight_mod,                                                            &
     51    USE flight_mod,                                                                                &
    5052        ONLY:  sensor, x_pos, y_pos, z_pos
    5153
     
    5456    USE NETCDF
    5557
    56     USE netcdf_interface,                                                      &
    57         ONLY:  dofl_time_count, id_set_fl, id_var_dofl, id_var_time_fl,        &
    58                id_var_x_fl, id_var_y_fl, id_var_z_fl, netcdf_handle_error,     &
    59                nc_stat
    60              
     58    USE netcdf_interface,                                                                          &
     59        ONLY:  dofl_time_count, id_set_fl, id_var_dofl, id_var_time_fl, id_var_x_fl, id_var_y_fl,  &
     60               id_var_z_fl, nc_stat, netcdf_handle_error
     61
    6162    USE pegrid
    6263
     
    8788!
    8889!--    Update the flight-output time and spatial coordinates
    89        nc_stat = NF90_PUT_VAR( id_set_fl, id_var_time_fl,                      &
    90                                (/ time_since_reference_point /),               &
    91                                start = (/ dofl_time_count /),                  &
     90       nc_stat = NF90_PUT_VAR( id_set_fl, id_var_time_fl,                                          &
     91                               (/ time_since_reference_point /),                                   &
     92                               start = (/ dofl_time_count /),                                      &
    9293                               count = (/ 1 /) )
    9394       CALL netcdf_handle_error( 'data_output_flight', 554 )
    9495
    9596       DO  l = 1, num_leg
    96           nc_stat = NF90_PUT_VAR( id_set_fl, id_var_x_fl(l),                   &
    97                                   (/ x_pos(l) /),                              &
    98                                   start = (/ dofl_time_count /),               &
     97          nc_stat = NF90_PUT_VAR( id_set_fl, id_var_x_fl(l),                                       &
     98                                  (/ x_pos(l) /),                                                  &
     99                                  start = (/ dofl_time_count /),                                   &
    99100                                  count = (/ 1 /) )
    100           nc_stat = NF90_PUT_VAR( id_set_fl, id_var_y_fl(l),                   &
    101                                   (/ y_pos(l) /),                              &
    102                                   start = (/ dofl_time_count /),               &
     101          nc_stat = NF90_PUT_VAR( id_set_fl, id_var_y_fl(l),                                       &
     102                                  (/ y_pos(l) /),                                                  &
     103                                  start = (/ dofl_time_count /),                                   &
    103104                                  count = (/ 1 /) )
    104           nc_stat = NF90_PUT_VAR( id_set_fl, id_var_z_fl(l),                   &
    105                                   (/ z_pos(l) /),                              &
    106                                   start = (/ dofl_time_count /),               &
     105          nc_stat = NF90_PUT_VAR( id_set_fl, id_var_z_fl(l),                                       &
     106                                  (/ z_pos(l) /),                                                  &
     107                                  start = (/ dofl_time_count /),                                   &
    107108                                  count = (/ 1 /) )
    108109          CALL netcdf_handle_error( 'data_output_flight', 555 )
     
    113114       DO  l = 1, num_leg
    114115          DO i = 1, num_var_fl
    115              nc_stat = NF90_PUT_VAR( id_set_fl, id_var_dofl(k),                &
    116                                      (/ sensor(i,l) /),                        &
    117                                      start = (/ dofl_time_count /),            &
     116             nc_stat = NF90_PUT_VAR( id_set_fl, id_var_dofl(k),                                    &
     117                                     (/ sensor(i,l) /),                                            &
     118                                     start = (/ dofl_time_count /),                                &
    118119                                     count = (/ 1 /) )
    119120
    120121             CALL netcdf_handle_error( 'data_output_flight', 556 )
    121          
     122
    122123             k = k + 1
    123124          ENDDO
    124125       ENDDO
    125126    ENDIF
    126    
     127
    127128    CALL cpu_log( log_point(64), 'data_output_flight', 'stop' )
    128    
     129
    129130#endif
    130131 END SUBROUTINE data_output_flight
Note: See TracChangeset for help on using the changeset viewer.