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_flight.f90

    r4360 r4498  
    11!> @file user_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:
    21 ! ------------------
     21! -----------------
    2222!
    2323!
     
    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! unused variables commented out + statement added to avoid compiler warnings
    31 ! 
     35!
    3236! 3684 2019-01-20 20:20:58Z knoop
    3337! Corrected "Former revisions" section
    34 ! 
     38!
    3539! 1957 2016-07-07 10:43:48Z suehring
    3640! Initial revision
     
    3842! Description:
    3943! ------------
    40 !> Calculation of user-defined output quantity for flight measurements after
    41 !> each timestep.
    42 !------------------------------------------------------------------------------!
     44!> Calculation of user-defined output quantity for flight measurements after each timestep.
     45!--------------------------------------------------------------------------------------------------!
    4346 SUBROUTINE user_flight( var, id )
    4447
    4548    USE control_parameters
    46    
     49
    4750    USE grid_variables
    4851
     
    6063!    INTEGER(iwp) ::  j  !< index along y
    6164!    INTEGER(iwp) ::  k  !< index along z
    62     INTEGER(iwp) ::  id !< variable identifyer, according to the settings in user_init_flight
    63        
    64     REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  var !< treated variable
     65    INTEGER(iwp) ::  id  !< variable identifyer, according to the settings in user_init_flight
     66
     67    REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  var  !< treated variable
    6568
    6669!
     
    6972
    7073!
    71 !-- Here, the respective variable is calculated. There is no call of
    72 !-- exchange_horiz necessary.
    73 !-- The variable identifyer (id) must be set according to the settings in
    74 !-- user_init_flight.
     74!-- Here, the respective variable is calculated. There is no call of exchange_horiz necessary.
     75!-- The variable identifyer (id) must be set according to the settings in user_init_flight.
    7576!-- Please note, so far, variable must be located at the center of a grid box.
    7677!     var = 0.0_wp
    7778
    7879!     SELECT CASE ( id )
    79 ! 
     80!
    8081!        CASE ( 1 )
    81 !           DO i = nxl-1, nxr+1
    82 !              DO j = nys-1, nyn+1
    83 !                 DO k = nzb, nzt
     82!           DO  i = nxl-1, nxr+1
     83!              DO  j = nys-1, nyn+1
     84!                 DO  k = nzb, nzt
    8485!                    var(k,j,i) = ABS( u(k,j,i )
    8586!                 ENDDO
    8687!              ENDDO
    8788!           ENDDO
    88 !           
     89!
    8990!        CASE ( 2 )
    90 !           DO i = nxl-1, nxr+1
    91 !              DO j = nys-1, nyn+1
    92 !                 DO k = nzb, nzt
     91!           DO  i = nxl-1, nxr+1
     92!              DO  j = nys-1, nyn+1
     93!                 DO  k = nzb, nzt
    9394!                    var(k,j,i) = ABS( v(k,j,i) )
    9495!                 ENDDO
    9596!              ENDDO
    9697!           ENDDO
    97 ! 
     98!
    9899!     END SELECT
    99100
Note: See TracChangeset for help on using the changeset viewer.