Ignore:
Timestamp:
Dec 11, 2020 2:18:43 PM (4 years ago)
Author:
raasch
Message:

reading of namelist file and actions in case of namelist errors revised so that statement labels and goto statements are not required any more

File:
1 edited

Legend:

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

    r4651 r4822  
    375375          value     = fmax(1)
    376376          value_ijk = fmax_ijk
    377           IF ( fmax_ijk(1) < 0 )  THEN
     377          IF ( fmax_ijk(1) <= -10 )  THEN
     378!
     379!--          Index needs to be corrected because it has been modified above to indicate negative
     380!--          values
     381             value_ijk(1) = -value_ijk(1) - 10
     382!
     383!--          For this reason also change the sign of the quantity
    378384             value        = -value
    379              value_ijk(1) = -value_ijk(1) - 10         !???
    380385          ENDIF
    381386
     
    389394    IF ( value_ijk(2) > ny ) value_ijk(2) = value_ijk(2) - (ny+1)
    390395
     396    WRITE (9,*) 'global_min_max: value = ', value, ' kji = ', value_ijk, ' ar=', &
     397                ar(value_ijk(1),value_ijk(2),value_ijk(3))
    391398
    392399 END SUBROUTINE global_min_max
Note: See TracChangeset for help on using the changeset viewer.