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

    r4360 r4498  
    11!> @file user_data_output_mask.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! 4168 2019-08-16 13:50:17Z suehring
    30 ! Remove dependency on surface_mod + example for terrain-following output 
     34! Remove dependency on surface_mod + example for terrain-following output
    3135! adjusted
    32 ! 
     36!
    3337! 4069 2019-07-01 14:05:51Z Giersch
    34 ! Masked output running index mid has been introduced as a local variable to 
     38! Masked output running index mid has been introduced as a local variable to
    3539! avoid runtime error (Loop variable has been modified) in time_integration
    36 ! 
     40!
    3741! 3768 2019-02-27 14:35:58Z raasch
    3842! variables commented + statement added to avoid compiler warnings about unused variables
    39 ! 
     43!
    4044! 3655 2019-01-07 16:51:22Z knoop
    4145! Add terrain-following output
     
    4549! Description:
    4650! ------------
    47 !> Resorts the user-defined output quantity with indices (k,j,i) to a
    48 !> temporary array with indices (i,j,k) for masked data output.
    49 !------------------------------------------------------------------------------!
     51!> Resorts the user-defined output quantity with indices (k,j,i) to a temporary array with
     52!> indices (i,j,k) for masked data output.
     53!--------------------------------------------------------------------------------------------------!
    5054 SUBROUTINE user_data_output_mask( av, variable, found, local_pf, mid )
    51  
     55
    5256
    5357    USE control_parameters
    54        
     58
    5559    USE indices
    56    
     60
    5761    USE kinds
    58    
     62
    5963    USE user
    6064
    6165    IMPLICIT NONE
    6266
    63     CHARACTER (LEN=*) ::  variable  !<
     67    CHARACTER(LEN=*) ::  variable  !<
    6468
    65     INTEGER(iwp) ::  av             !<
    66     INTEGER(iwp) ::  mid            !< masked output running index
    67 !    INTEGER(iwp) ::  i              !<
    68 !    INTEGER(iwp) ::  j              !<
    69 !    INTEGER(iwp) ::  k              !<
    70 !    INTEGER(iwp) ::  topo_top_index !< k index of highest horizontal surface
     69    INTEGER(iwp) ::  av              !<
     70    INTEGER(iwp) ::  mid             !< masked output running index
     71!    INTEGER(iwp) ::  i               !<
     72!    INTEGER(iwp) ::  j               !<
     73!    INTEGER(iwp) ::  k               !<
     74!    INTEGER(iwp) ::  topo_top_index  !< k index of highest horizontal surface
    7175
    72     LOGICAL ::  found               !<
     76    LOGICAL ::  found  !<
    7377
    74     REAL(wp),                                                                  &
    75        DIMENSION(mask_size_l(mid,1),mask_size_l(mid,2),mask_size_l(mid,3)) ::  &
    76           local_pf   !<
     78    REAL(wp), DIMENSION(mask_size_l(mid,1),mask_size_l(mid,2),mask_size_l(mid,3)) ::  local_pf  !<
    7779
    7880!
     
    8789
    8890!--    Uncomment and extend the following lines, if necessary.
    89 !--    The arrays for storing the user defined quantities (here u2 and u2_av)
    90 !--    have to be declared and defined by the user!
     91!--    The arrays for storing the user defined quantities (here u2 and u2_av) have to be declared
     92!--    and defined by the user!
    9193!--    Sample for user-defined output:
    9294!       CASE ( 'u2' )
     
    98100!                   DO  j = 1, mask_size_l(mid,2)
    99101!                      DO  k = 1, mask_size_l(mid,3)
    100 !                         local_pf(i,j,k) = u2(mask_k(mid,k),                  &
    101 !                                              mask_j(mid,j),                  &
     102!                         local_pf(i,j,k) = u2(mask_k(mid,k),                                       &
     103!                                              mask_j(mid,j),                                       &
    102104!                                              mask_i(mid,i))
    103105!                      ENDDO
     
    111113!!
    112114!!--                   Get k index of highest horizontal surface
    113 !                      topo_top_index = topo_top_ind( &
    114 !                                        mask_j(mid,j), &
    115 !                                        mask_i(mid,i), &
    116 !                                        1          )
     115!                      topo_top_index = topo_top_ind( mask_j(mid,j), mask_i(mid,i), 1 )
    117116!!
    118117!!--                   Save output array
    119118!                      DO  k = 1, mask_size_l(mid,3)
    120 !                         local_pf(i,j,k) = u2(MIN( topo_top_index+mask_k(mid,k),&
    121 !                                                   nzt+1 ),                     &
    122 !                                              mask_j(mid,j),                    &
    123 !                                              mask_i(mid,i)                   )
     119!                         local_pf(i,j,k) = u2(MIN( topo_top_index + mask_k(mid,k), nzt+1 ),        &
     120!                                              mask_j(mid,j), mask_i(mid,i) )
    124121!                      ENDDO
    125122!                   ENDDO
     
    133130!                   DO  j = 1, mask_size_l(mid,2)
    134131!                      DO  k = 1, mask_size_l(mid,3)
    135 !                          local_pf(i,j,k) = u2_av(mask_k(mid,k),              &
    136 !                                                  mask_j(mid,j),              &
    137 !                                                  mask_i(mid,i) )
     132!                          local_pf(i,j,k) = u2_av(mask_k(mid,k), mask_j(mid,j), mask_i(mid,i) )
    138133!                       ENDDO
    139134!                    ENDDO
     
    146141!!
    147142!!--                   Get k index of highest horizontal surface
    148 !                      topo_top_index = topo_top_ind(   &
    149 !                                        mask_j(mid,j), &
    150 !                                        mask_i(mid,i), &
    151 !                                        1 )
     143!                      topo_top_index = topo_top_ind( mask_j(mid,j), mask_i(mid,i), 1 )
    152144!!
    153145!!--                   Save output array
    154146!                      DO  k = 1, mask_size_l(mid,3)
    155 !                         local_pf(i,j,k) = u2_av(                               &
    156 !                                              MIN( topo_top_index+mask_k(mid,k),&
    157 !                                                   nzt+1 ),                     &
    158 !                                              mask_j(mid,j),                    &
    159 !                                              mask_i(mid,i)                   )
     147!                         local_pf(i,j,k) = u2_av( MIN( topo_top_index+mask_k(mid,k), nzt+1 ),      &
     148!                                                  mask_j(mid,j), mask_i(mid,i) )
    160149!                      ENDDO
    161150!                   ENDDO
Note: See TracChangeset for help on using the changeset viewer.