Ignore:
Timestamp:
May 22, 2019 6:59:54 PM (5 years ago)
Author:
suehring
Message:

remove unused variable and fix non-standard string operation PGI compiler

File:
1 edited

Legend:

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

    r3994 r3995  
    2525! -----------------
    2626! $Id$
     27! Avoid compiler warnings about unused variable and fix string operation which
     28! is not allowed with PGI compiler
     29!
     30! 3994 2019-05-22 18:08:09Z suehring
    2731! Initial revision
    2832!
     
    149153
    150154    IMPLICIT NONE
    151 
     155!
     156!-- Next line is to avoid compiler warnings about unused variables
     157    IF ( timestep_number_at_prev_calc == 0 )  CONTINUE
    152158
    153159    initialized_diagnostic_output_quantities = .FALSE.
     
    269275!--    Remove _xy, _xz, or _yz from string
    270276       l = MAX( 3, LEN_TRIM( do2d(av,ivar) ) )
    271        do2d_var(av,ivar) = do2d(av,ivar)(0:l-2)
     277       do2d_var(av,ivar)(0:l-2) = do2d(av,ivar)(0:l-2)
    272278!
    273279!--    Gather 2d output quantity names, check for double occurrence of output quantity
     
    279285          ivar_all = ivar_all + 1
    280286          l = MAX( 3, LEN_TRIM( do2d(av,ivar) ) )
    281           do2d_var(av,ivar) = do2d(av,ivar)(0:l-2)
     287          do2d_var(av,ivar)(0:l-2) = do2d(av,ivar)(0:l-2)
    282288       ENDDO
    283289
Note: See TracChangeset for help on using the changeset viewer.