Ignore:
Timestamp:
Aug 6, 2019 9:11:47 AM (5 years ago)
Author:
raasch
Message:

relational operators .EQ., .NE., etc. replaced by ==, /=, etc.

File:
1 edited

Legend:

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

    r4127 r4144  
    2727! -----------------
    2828! $Id$
     29! relational operators .EQ., .NE., etc. replaced by ==, /=, etc.
     30!
     31! 4127 2019-07-30 14:47:10Z suehring
    2932! Output for bio_mrt added (merge from branch resler)
    3033!
     
    43194322!
    43204323!-- calculation of solar azimuth angle
    4321     IF (woz .LE. 12.0_wp) alpha = pi - acos( ( sin(thetasr) * sin( lat * dtor ) -                                     &
     4324    IF (woz <= 12.0_wp) alpha = pi - acos( ( sin(thetasr) * sin( lat * dtor ) -                                     &
    43224325    sin( declination * dtor ) ) / ( cos(thetasr) * cos( lat * dtor ) ) )   
    4323     IF (woz .GT. 12.0_wp) alpha = pi + acos( ( sin(thetasr) * sin( lat * dtor ) -                                     &
     4326    IF (woz > 12.0_wp) alpha = pi + acos( ( sin(thetasr) * sin( lat * dtor ) -                                     &
    43244327    sin( declination * dtor ) ) / ( cos(thetasr) * cos( lat * dtor ) ) )   
    43254328    saa = alpha / dtor
     
    43474350    CALL uvem_solar_position
    43484351     
    4349     IF (sza  .GE.  90)  THEN
     4352    IF (sza  >=  90)  THEN
    43504353       vitd3_exposure(:,:) = 0.0_wp
    43514354    ELSE
     
    44464449             IF (consider_obstructions )  THEN
    44474450                obstruction_temp1 = building_obstruction_f%var_3d(:,j,i)
    4448                 IF (obstruction_temp1(0)  .NE.  9)  THEN
     4451                IF ( obstruction_temp1(0)  /=  9 )  THEN
    44494452                   DO  pobi = 0, 44
    44504453                      DO  bi = 0, 7
     
    44684471         
    44694472             obstruction_direct_beam = obstruction( nint(startpos_saa_float), nint( sza / 10.0_wp ) )
    4470              IF (sza  .GE.  89.99_wp)  THEN
     4473             IF (sza  >=  89.99_wp)  THEN
    44714474                sza = 89.99999_wp
    44724475             ENDIF
Note: See TracChangeset for help on using the changeset viewer.