Ignore:
Timestamp:
Apr 15, 2020 2:26:31 PM (4 years ago)
Author:
raasch
Message:

bugfix for creation of filetypes, argument removed from rd_mpi_io_open, files re-formatted to follow the PALM coding standard

File:
1 edited

Legend:

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

    r4360 r4498  
    11!> @file user_init_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!--------------------------------------------------------------------------------------------------!
     18!
    1919!
    2020! Current revisions:
     
    2525! -----------------
    2626! $Id$
     27! file re-formatted to follow the PALM coding standard
     28!
     29!
     30! 4360 2020-01-07 11:25:50Z suehring
    2731! Corrected "Former revisions" section
    28 ! 
     32!
    2933! 3768 2019-02-27 14:35:58Z raasch
    3034! statements commented or added to avoid compiler warnings about unused variables
    31 ! 
     35!
    3236! 3655 2019-01-07 16:51:22Z knoop
    3337! Corrected "Former revisions" section
    34 ! 
     38!
    3539! 1957 2016-07-07 10:43:48Z suehring
    3640! Initial revision
     
    3943! ------------
    4044!> Execution of user-defined initialization for flight measurements.
    41 !------------------------------------------------------------------------------!
     45!--------------------------------------------------------------------------------------------------!
    4246 SUBROUTINE user_init_flight( init, k, id, label_leg )
    43  
     47
    4448
    4549    USE control_parameters
    46    
     50
    4751    USE indices
    48    
     52
    4953    USE kinds
    50    
    51 !    USE netcdf_interface,                                                      &
    52 !        ONLY: dofl_label, dofl_unit
    53    
     54
     55!    USE netcdf_interface,                                                                          &
     56!        ONLY: dofl_label,                                                                          &
     57!              dofl_unit
     58
    5459    USE user
    5560
    5661    IMPLICIT NONE
    57    
     62
    5863    CHARACTER(LEN=10), OPTIONAL ::  label_leg     !< label of the respective leg
    59    
     64
    6065    INTEGER(iwp), OPTIONAL                ::  id  !< variable index
    6166    INTEGER(iwp), OPTIONAL, INTENT(INOUT) ::  k   !< index for respective variable and leg
    62    
    63     LOGICAL ::  init  !< variable to recognize initial call 
     67
     68    LOGICAL ::  init  !< variable to recognize initial call
    6469
    6570!
     
    7176!
    7277!-- Sample for user-defined flight-time series.
    73 !-- For each quantity you have to give a label and a unit, which will be used
    74 !-- for the output into NetCDF file. They must not contain more than
    75 !-- twenty characters.
     78!-- For each quantity you have to give a label and a unit, which will be used for the output into
     79!-- NetCDF file. They must not contain more than twenty characters.
    7680
    7781
     
    8084!--    The number of user-defined quantity has to be increased appropriately.
    8185!--    In the following example, 2 user-defined quantities are added.
    82 !        num_var_fl_user = num_var_fl_user + 2 
     86!        num_var_fl_user = num_var_fl_user + 2
    8387
    8488       init = .FALSE.
    85    
     89
    8690    ELSE
    87    
     91
    8892!
    8993!--    Please add the respective number of new variables as following:
    90      
     94
    9195!        SELECT CASE ( id )
    92 !       
     96!
    9397!           CASE ( 1 )
    9498!              dofl_label(k)   = TRIM(label_leg) // '_' // 'abs_u'
    9599!              dofl_unit(k)    = 'm/s'
    96100!              k               = k + 1
    97 !             
     101!
    98102!           CASE ( 2 )
    99 !     
     103!
    100104!              dofl_label(k)   = TRIM(label_leg) // '_' // 'abs_v'
    101105!              dofl_unit(k)    = 'm/s'
    102106!              k               = k + 1
    103 !             
     107!
    104108!        END SELECT
    105109
    106110    ENDIF
    107        
     111
    108112 END SUBROUTINE user_init_flight
    109113
Note: See TracChangeset for help on using the changeset viewer.