Ignore:
Timestamp:
Jul 1, 2019 2:05:51 PM (5 years ago)
Author:
Giersch
Message:

Bugfix for masked output, compiler warning removed, test case for wind turbine model revised

File:
1 edited

Legend:

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

    r4029 r4069  
    2727! -----------------
    2828! $Id$
     29! Masked output running index mid has been introduced as a local variable to
     30! avoid runtime error (Loop variable has been modified) in time_integration
     31!
     32! 4029 2019-06-14 14:04:35Z raasch
    2933! nest_chemistry option removed
    3034!
     
    15101514!> Subroutine defining mask output variables for chemical species
    15111515!------------------------------------------------------------------------------!
    1512  SUBROUTINE chem_data_output_mask( av, variable, found, local_pf )
     1516 SUBROUTINE chem_data_output_mask( av, variable, found, local_pf, mid )
    15131517
    15141518
     
    15201524
    15211525    CHARACTER(LEN=5)  ::  grid        !< flag to distinquish between staggered grids
     1526    CHARACTER(LEN=16) ::  spec_name
    15221527    CHARACTER(LEN=*)  ::  variable    !<
    1523     INTEGER(iwp)  ::  av              !< flag to control data output of instantaneous or time-averaged data
    1524     LOGICAL ::  found
    1525     REAL(wp), DIMENSION(mask_size_l(mid,1),mask_size_l(mid,2),mask_size_l(mid,3)) ::  &
    1526               local_pf   !<
    1527 !
    1528 !-- local variables.
    1529     CHARACTER(LEN=16)  ::  spec_name
     1528   
     1529    INTEGER(iwp) ::  av              !< flag to control data output of instantaneous or time-averaged data
    15301530    INTEGER(iwp) ::  lsp
    15311531    INTEGER(iwp) ::  i               !< grid index along x-direction
    15321532    INTEGER(iwp) ::  j               !< grid index along y-direction
    15331533    INTEGER(iwp) ::  k               !< grid index along z-direction
     1534    INTEGER(iwp) ::  mid             !< masked output running index
    15341535    INTEGER(iwp) ::  topo_top_ind    !< k index of highest horizontal surface
     1536   
     1537    LOGICAL ::  found
     1538   
     1539    REAL(wp), DIMENSION(mask_size_l(mid,1),mask_size_l(mid,2),mask_size_l(mid,3)) ::  &
     1540              local_pf   !<
     1541!
     1542!-- local variables.
    15351543
    15361544    found = .TRUE.
Note: See TracChangeset for help on using the changeset viewer.