Ignore:
Timestamp:
Sep 11, 2024, 4:27:07 PM (9 days ago)
Author:
abarral
Message:

Replace REPROBUS CPP KEY by logical using handmade wonky wrapper

Location:
LMDZ6/branches/Amaury_dev/libf/phylmd/ecrad
Files:
30 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev/libf/phylmd/ecrad/driver/ecrad_driver.F90

    r5159 r5185  
    200200  end if
    201201
    202   if (driver_config%do_save_cloud_optics .and. config%use_general_cloud_optics) then
     202  if (driver_config%do_save_cloud_optics .AND. config%use_general_cloud_optics) then
    203203    call save_general_cloud_optics(config, 'hydrometeor_optics', iverbose=driver_config%iverbose)
    204204  end if
  • LMDZ6/branches/Amaury_dev/libf/phylmd/ecrad/driver/ecrad_driver_config.F90

    r5159 r5185  
    355355
    356356    if (do_override_eff_size &
    357          &  .and. (this%high_inv_effective_size_override < 0.0_jprb &
     357         &  .AND. (this%high_inv_effective_size_override < 0.0_jprb &
    358358              .or. this%middle_inv_effective_size_override < 0.0_jprb &
    359359              .or. this%low_inv_effective_size_override < 0.0_jprb)) then
  • LMDZ6/branches/Amaury_dev/libf/phylmd/ecrad/driver/ecrad_driver_read_input.F90

    r5159 r5185  
    103103    else
    104104      single_level%solar_irradiance = 1366.0_jprb
    105       if (driver_config%iverbose >= 1 .and. config%do_sw) then
     105      if (driver_config%iverbose >= 1 .AND. config%do_sw) then
    106106        write(nulout,'(a,g10.3,a)') 'Warning: solar irradiance set to ', &
    107107             &  single_level%solar_irradiance, ' W m-2'
     
    204204      ! Optional scaling of liquid water mixing ratio
    205205      if (driver_config%q_liq_scaling >= 0.0_jprb &
    206            &  .and. driver_config%q_liq_scaling /= 1.0_jprb) then
     206           &  .AND. driver_config%q_liq_scaling /= 1.0_jprb) then
    207207        cloud%q_liq = cloud%q_liq * driver_config%q_liq_scaling
    208208        if (driver_config%iverbose >= 2) then
     
    213213
    214214      ! Optional scaling of ice water mixing ratio
    215       if (driver_config%q_ice_scaling >= 0.0_jprb .and. driver_config%q_ice_scaling /= 1.0_jprb) then
     215      if (driver_config%q_ice_scaling >= 0.0_jprb .AND. driver_config%q_ice_scaling /= 1.0_jprb) then
    216216        cloud%q_ice = cloud%q_ice * driver_config%q_ice_scaling
    217217        if (driver_config%iverbose >= 2) then
     
    223223      ! Optional scaling of cloud fraction
    224224      if (driver_config%cloud_fraction_scaling >= 0.0_jprb &
    225            &  .and. driver_config%cloud_fraction_scaling /= 1.0_jprb) then
     225           &  .AND. driver_config%cloud_fraction_scaling /= 1.0_jprb) then
    226226        cloud%fraction = cloud%fraction * driver_config%cloud_fraction_scaling
    227227        if (driver_config%iverbose >= 2) then
     
    332332
    333333        else if (driver_config%cloud_separation_scale_surface > 0.0_jprb &
    334              &  .and. driver_config%cloud_separation_scale_toa > 0.0_jprb) then
     334             &  .AND. driver_config%cloud_separation_scale_toa > 0.0_jprb) then
    335335          ! (2) Cloud separation scale provided in namelist
    336336
     
    386386          allocate(cloud%inv_inhom_effective_size(ncol,nlev))
    387387          where (cloud%fraction > config%cloud_fraction_threshold &
    388                &  .and. cloud%fraction < 1.0_jprb - config%cloud_fraction_threshold)
     388               &  .AND. cloud%fraction < 1.0_jprb - config%cloud_fraction_threshold)
    389389            ! Convert effective cloud separation to effective cloud
    390390            ! size, noting divisions rather than multiplications
     
    442442        ! In cases (3) and (4) above the effective size obtained from
    443443        ! the NetCDF may be scaled by a namelist variable
    444         if (is_cloud_size_scalable .and. driver_config%effective_size_scaling > 0.0_jprb) then
     444        if (is_cloud_size_scalable .AND. driver_config%effective_size_scaling > 0.0_jprb) then
    445445          ! Scale cloud effective size
    446446          cloud%inv_cloud_effective_size = cloud%inv_cloud_effective_size &
     
    477477      allocate(single_level%skin_temperature(ncol))
    478478      single_level%skin_temperature(1:ncol) = thermodynamics%temperature_hl(1:ncol,nlev+1)
    479       if (driver_config%iverbose >= 1 .and. config%do_lw &
    480            &  .and. driver_config%skin_temperature_override < 0.0_jprb) then
     479      if (driver_config%iverbose >= 1 .AND. config%do_lw &
     480           &  .AND. driver_config%skin_temperature_override < 0.0_jprb) then
    481481        write(nulout,'(a)') 'Warning: skin temperature set equal to lowest air temperature'
    482482      end if
  • LMDZ6/branches/Amaury_dev/libf/phylmd/ecrad/driver/ifs_blocking.F90

    r5159 r5185  
    7373  lldebug=(driver_config%iverbose>4)     ! debug
    7474  llactaero = .false.
    75   if(yradiation%rad_config%n_aerosol_types > 0 .and.&
    76     & yradiation%rad_config%n_aerosol_types <= 21 .and. yradiation%yrerad%naermacc == 0) then
     75  if(yradiation%rad_config%n_aerosol_types > 0 .AND.&
     76    & yradiation%rad_config%n_aerosol_types <= 21 .AND. yradiation%yrerad%naermacc == 0) then
    7777    llactaero = .true.
    7878  endif
     
    121121  ifs_config%ihti   =indrad(inext,nlev+1,.true.)
    122122  ifs_config%iaero  =indrad(inext,yradiation%rad_config%n_aerosol_types*nlev,&
    123                           & llactaero .and. yradiation%yrerad%naermacc==0)
     123                          & llactaero .AND. yradiation%yrerad%naermacc==0)
    124124
    125125  iinend =inext-1                  ! end of input variables
  • LMDZ6/branches/Amaury_dev/libf/phylmd/ecrad/ifsaux/abor1.F90

    r5159 r5185  
    2323  ! FLUSH not understood by NAG compiler
    2424  !CALL FLUSH(NULOUT)
    25   IF (NULOUT /= 0 .and. NULOUT /= 6) CLOSE(NULOUT)
     25  IF (NULOUT /= 0 .AND. NULOUT /= 6) CLOSE(NULOUT)
    2626ENDIF
    2727
  • LMDZ6/branches/Amaury_dev/libf/phylmd/ecrad/radiation/radiation_aerosol_optics.F90

    r5159 r5185  
    292292          else
    293293            iwn = 1
    294             DO while (wavenumber(iwn+1) < wavenumber_target .and. iwn < nwn-1)
     294            DO while (wavenumber(iwn+1) < wavenumber_target .AND. iwn < nwn-1)
    295295              iwn = iwn + 1
    296296            end do
     
    756756              iband = config%i_band_from_reordered_g_sw(jg)
    757757              local_od = od_sw(jg,jlev,jcol) + od_sw_aerosol(iband,jlev)
    758               if (local_od > 0.0_jprb .and. od_sw_aerosol(iband,jlev) > 0.0_jprb) then
     758              if (local_od > 0.0_jprb .AND. od_sw_aerosol(iband,jlev) > 0.0_jprb) then
    759759                local_scat = ssa_sw(jg,jlev,jcol) * od_sw(jg,jlev,jcol) &
    760760                     &  + scat_sw_aerosol(iband,jlev)
     
    785785              iband = config%i_band_from_reordered_g_lw(jg)
    786786              local_od = od_lw(jg,jlev,jcol) + od_lw_aerosol(iband,jlev)
    787               if (local_od > 0.0_jprb .and. od_lw_aerosol(iband,jlev) > 0.0_jprb) then
     787              if (local_od > 0.0_jprb .AND. od_lw_aerosol(iband,jlev) > 0.0_jprb) then
    788788                ! All scattering is due to aerosols, therefore the
    789789                ! asymmetry factor is equal to the value for aerosols
  • LMDZ6/branches/Amaury_dev/libf/phylmd/ecrad/radiation/radiation_aerosol_optics_data.F90

    r5159 r5185  
    378378    end if
    379379
    380     if (n_type_philic > 0 .and. nrh > 0) then
     380    if (n_type_philic > 0 .AND. nrh > 0) then
    381381      if (n_bands_sw > 0) then
    382382        allocate(this%mass_ext_sw_philic(n_bands_sw, nrh, n_type_philic))
  • LMDZ6/branches/Amaury_dev/libf/phylmd/ecrad/radiation/radiation_aerosol_optics_description.F90

    r5159 r5185  
    168168      ! Check if we have a match
    169169      if (to_string(this%code_philic(:,ja)) == code_str &
    170            &  .and. trim(to_string(this%optical_model_philic(:,ja))) &
     170           &  .AND. trim(to_string(this%optical_model_philic(:,ja))) &
    171171           &          == optical_model_str) then
    172172        this%is_preferred_philic(ja) = .true.
     
    178178    DO ja = 1,size(this%bin_phobic)
    179179      if (to_string(this%code_phobic(:,ja)) == code_str &
    180            &  .and. trim(to_string(this%optical_model_phobic(:,ja))) &
     180           &  .AND. trim(to_string(this%optical_model_phobic(:,ja))) &
    181181           &          == optical_model_str) then
    182182        this%is_preferred_phobic(ja) = .true.
     
    259259        if (to_string(this%code_philic(:,ja)) == code_str) then
    260260          ! Aerosol code matches
    261           if (present(ibin) .and. this%bin_philic(ja) > 0) then
     261          if (present(ibin) .AND. this%bin_philic(ja) > 0) then
    262262            if (ibin > 0) then
    263263              if (ibin == this%bin_philic(ja)) then
     
    291291            current_score = current_score + 2
    292292          end if
    293           if (current_score > 0 .and. this%is_preferred_philic(ja)) then
     293          if (current_score > 0 .AND. this%is_preferred_philic(ja)) then
    294294            current_score = current_score + 1
    295295          end if
     
    299299            score = current_score
    300300            is_ambiguous = .false.
    301           else if (current_score > 0 .and. current_score == score) then
     301          else if (current_score > 0 .AND. current_score == score) then
    302302            is_ambiguous = .true.
    303303          end if
     
    310310        if (to_string(this%code_phobic(:,ja)) == code_str) then
    311311          ! Aerosol code matches
    312           if (present(ibin) .and. this%bin_phobic(ja) > 0) then
     312          if (present(ibin) .AND. this%bin_phobic(ja) > 0) then
    313313            if (ibin > 0) then
    314314              if (ibin == this%bin_phobic(ja)) then
     
    342342            current_score = current_score + 2
    343343          end if
    344           if (current_score > 0 .and. this%is_preferred_phobic(ja)) then
     344          if (current_score > 0 .AND. this%is_preferred_phobic(ja)) then
    345345            current_score = current_score + 1
    346346          end if
     
    350350            score = current_score
    351351            is_ambiguous = .false.
    352           else if (current_score > 0 .and. current_score == score) then
     352          else if (current_score > 0 .AND. current_score == score) then
    353353            is_ambiguous = .true.
    354354          end if         
  • LMDZ6/branches/Amaury_dev/libf/phylmd/ecrad/radiation/radiation_check.F90

    r5159 r5185  
    4848    if (allocated(var)) then
    4949
    50       if (present(i1) .and. present(i2)) then
     50      if (present(i1) .AND. present(i2)) then
    5151        varmin = minval(var(i1:i2))
    5252        varmax = maxval(var(i1:i2))
     
    6262        is_bad = .true.
    6363        if (do_fix) then
    64           if (present(i1) .and. present(i2)) then
     64          if (present(i1) .AND. present(i2)) then
    6565            var(i1:i2) = max(boundmin, min(boundmax, var(i1:i2)))
    6666          else
     
    105105    if (allocated(var)) then
    106106
    107       if (present(i1) .and. present(i2)) then
     107      if (present(i1) .AND. present(i2)) then
    108108        ii1 = i1
    109109        ii2 = i2
     
    112112        ii2 = ubound(var,1)
    113113      end if
    114       if (present(j1) .and. present(j2)) then
     114      if (present(j1) .AND. present(j2)) then
    115115        jj1 = j1
    116116        jj2 = j2
     
    168168    if (allocated(var)) then
    169169
    170       if (present(i1) .and. present(i2)) then
     170      if (present(i1) .AND. present(i2)) then
    171171        ii1 = i1
    172172        ii2 = i2
     
    175175        ii2 = ubound(var,1)
    176176      end if
    177       if (present(j1) .and. present(j2)) then
     177      if (present(j1) .AND. present(j2)) then
    178178        jj1 = j1
    179179        jj2 = j2
     
    182182        jj2 = ubound(var,2)
    183183      end if
    184       if (present(k1) .and. present(k2)) then
     184      if (present(k1) .AND. present(k2)) then
    185185        kk1 = k1
    186186        kk2 = k2
  • LMDZ6/branches/Amaury_dev/libf/phylmd/ecrad/radiation/radiation_cloud_generator.F90

    r5159 r5185  
    213213          trigger = rand_top(jg) * total_cloud_cover
    214214          jlev = ibegin
    215           DO while (trigger > cum_cloud_cover(jlev) .and. jlev < iend)
     215          DO while (trigger > cum_cloud_cover(jlev) .AND. jlev < iend)
    216216            jlev = jlev + 1
    217217          end do
     
    693693
    694694          ! For each spectral interval, has the first cloud appeared at this level?
    695           first_cloud(jg) = (trigger(jg) <= cum_cloud_cover(jlev) .and. .not. found_cloud(jg))
     695          first_cloud(jg) = (trigger(jg) <= cum_cloud_cover(jlev) .AND. .not. found_cloud(jg))
    696696
    697697          ! ...if so, add to found_cloud
     
    703703          ! prev_cloud)
    704704          is_cloud(jg) = first_cloud(jg) &
    705                &  .or. found_cloud(jg) .and. merge(rand_cloud(jg,jlev)*frac(jlev-1) &
     705               &  .or. found_cloud(jg) .AND. merge(rand_cloud(jg,jlev)*frac(jlev-1) &
    706706               &               < frac(jlev)+frac(jlev-1)-pair_cloud_cover(jlev-1), &
    707707               &             rand_cloud(jg,jlev)*(cum_cloud_cover(jlev-1) - frac(jlev-1)) &
     
    716716          rand_inhom(jg,jlev) = merge(merge(rand_inhom(jg,jlev-1), rand_inhom(jg,jlev), &
    717717               &                           rand_inhom2(jg,jlev) < overlap_param_inhom(jlev-1) &
    718                &                           .and. prev_cloud(jg)), &
     718               &                           .AND. prev_cloud(jg)), &
    719719               &                     0.0_jprb, is_cloud(jg))
    720720        end do
  • LMDZ6/branches/Amaury_dev/libf/phylmd/ecrad/radiation/radiation_cloud_optics.F90

    r5159 r5185  
    137137      end if
    138138    else if (config%i_ice_model == IIceModelBaran &
    139          &  .and. size(config%cloud_optics%ice_coeff_lw, 2) &
     139         &  .AND. size(config%cloud_optics%ice_coeff_lw, 2) &
    140140         &  /= NIceOpticsCoeffsBaran) then
    141141      write(nulerr,'(a,i0,a,i0,a,i0,a)') &
     
    145145      call radiation_abort()
    146146    else if (config%i_ice_model == IIceModelBaran2016 &
    147          &  .and. size(config%cloud_optics%ice_coeff_lw, 2) &
     147         &  .AND. size(config%cloud_optics%ice_coeff_lw, 2) &
    148148         &  /= NIceOpticsCoeffsBaran2016) then
    149149      write(nulerr,'(a,i0,a,i0,a,i0,a)') &
  • LMDZ6/branches/Amaury_dev/libf/phylmd/ecrad/radiation/radiation_config.F90

    r5159 r5185  
    852852    use_updated_solar_spectrum    = this%use_updated_solar_spectrum
    853853
    854     if (present(file_name) .and. present(unit)) then
     854    if (present(file_name) .AND. present(unit)) then
    855855      write(nulerr,'(a)') '*** Error: cannot specify both file_name and unit in call to config_type%read'
    856856      call radiation_abort('Radiation configuration error')
    857     else if (.not. present(file_name) .and. .not. present(unit)) then
     857    else if (.not. present(file_name) .AND. .not. present(unit)) then
    858858      write(nulerr,'(a)') '*** Error: neither file_name nor unit specified in call to config_type%read'
    859859      call radiation_abort('Radiation configuration error')
     
    10651065
    10661066    ! Will clouds be used at all?
    1067     if ((this%do_sw .and. this%i_solver_sw /= ISolverCloudless) &
    1068          &  .or. (this%do_lw .and. this%i_solver_lw /= ISolverCloudless)) then
     1067    if ((this%do_sw .AND. this%i_solver_sw /= ISolverCloudless) &
     1068         &  .or. (this%do_lw .AND. this%i_solver_lw /= ISolverCloudless)) then
    10691069      this%do_clouds = .true.
    10701070    else
     
    10731073
    10741074    if (this%use_general_cloud_optics .or. this%use_general_aerosol_optics) then
    1075       if (this%do_sw .and. this%do_cloud_aerosol_per_sw_g_point &
    1076            &  .and. this%i_gas_model_sw == IGasModelIFSRRTMG) then
     1075      if (this%do_sw .AND. this%do_cloud_aerosol_per_sw_g_point &
     1076           &  .AND. this%i_gas_model_sw == IGasModelIFSRRTMG) then
    10771077        write(nulout,'(a)') 'Warning: RRTMG SW only supports cloud/aerosol/surface optical properties per band, not per g-point'
    10781078        this%do_cloud_aerosol_per_sw_g_point = .false.
    10791079      end if
    1080       if (this%do_lw .and. this%do_cloud_aerosol_per_lw_g_point &
    1081            &  .and. this%i_gas_model_lw == IGasModelIFSRRTMG) then
     1080      if (this%do_lw .AND. this%do_cloud_aerosol_per_lw_g_point &
     1081           &  .AND. this%i_gas_model_lw == IGasModelIFSRRTMG) then
    10821082        write(nulout,'(a)') 'Warning: RRTMG LW only supports cloud/aerosol/surface optical properties per band, not per g-point'
    10831083        this%do_cloud_aerosol_per_lw_g_point = .false.
     
    11131113
    11141114    ! Check consistency of models
    1115     if (this%do_canopy_fluxes_sw .and. .not. this%do_surface_sw_spectral_flux) then
     1115    if (this%do_canopy_fluxes_sw .AND. .not. this%do_surface_sw_spectral_flux) then
    11161116      if (this%iverbosesetup >= 1) then
    11171117        write(nulout,'(a)') 'Warning: turning on do_surface_sw_spectral_flux as required by do_canopy_fluxes_sw'
     
    11211121
    11221122    ! Will clouds be used at all?
    1123     if ((this%do_sw .and. this%i_solver_sw /= ISolverCloudless) &
    1124          &  .or. (this%do_lw .and. this%i_solver_lw /= ISolverCloudless)) then
     1123    if ((this%do_sw .AND. this%i_solver_sw /= ISolverCloudless) &
     1124         &  .or. (this%do_lw .AND. this%i_solver_lw /= ISolverCloudless)) then
    11251125      this%do_clouds = .true.
    11261126    else
     
    11331133         & .or. this%i_solver_sw == ISolverTripleclouds &
    11341134         & .or. this%i_solver_lw == ISolverTripleclouds) &
    1135          & .and. this%i_overlap_scheme /= IOverlapExponentialRandom) then
     1135         & .AND. this%i_overlap_scheme /= IOverlapExponentialRandom) then
    11361136      write(nulerr,'(a)') '*** Error: SPARTACUS/Tripleclouds solvers can only do Exponential-Random overlap'
    11371137      call radiation_abort('Radiation configuration error')
    11381138    end if
    11391139
    1140     if (jprb < jprd .and. this%iverbosesetup >= 1 &
    1141          &  .and. (this%i_solver_sw == ISolverSPARTACUS &
     1140    if (jprb < jprd .AND. this%iverbosesetup >= 1 &
     1141         &  .AND. (this%i_solver_sw == ISolverSPARTACUS &
    11421142         &    .or. this%i_solver_lw == ISolverSPARTACUS)) then
    11431143      write(nulout,'(a)') 'Warning: the SPARTACUS solver may be unstable in single precision'
     
    12971297    end if
    12981298
    1299     if (this%use_aerosols .and. this%n_aerosol_types == 0) then
     1299    if (this%use_aerosols .AND. this%n_aerosol_types == 0) then
    13001300      if (this%iverbosesetup >= 2) then
    13011301        write(nulout, '(a)') 'Aerosols on but n_aerosol_types=0: optical properties to be computed outside ecRad'
     
    13241324    end if
    13251325
    1326     if (this%i_solver_sw == ISolverSPARTACUS .and. this%do_sw_delta_scaling_with_gases) then
     1326    if (this%i_solver_sw == ISolverSPARTACUS .AND. this%do_sw_delta_scaling_with_gases) then
    13271327      write(nulerr,'(a)') '*** Error: SW delta-Eddington scaling with gases not possible with SPARTACUS solver'
    13281328      call radiation_abort('Radiation configuration error')
    13291329    end if
    13301330
    1331     if ((this%do_lw .and. this%do_sw) .and. &
     1331    if ((this%do_lw .AND. this%do_sw) .AND. &
    13321332         & (     (      this%i_solver_sw == ISolverHomogeneous  &
    1333          &        .and. this%i_solver_lw /= ISolverHomogeneous) &
     1333         &        .AND. this%i_solver_lw /= ISolverHomogeneous) &
    13341334         &  .or. (      this%i_solver_sw /= ISolverHomogeneous  &
    1335          &        .and. this%i_solver_lw == ISolverHomogeneous) &
     1335         &        .AND. this%i_solver_lw == ISolverHomogeneous) &
    13361336         & ) ) then
    13371337      write(nulerr,'(a)') '*** Error: if one solver is "Homogeneous" then the other must be'
     
    13411341    ! Set is_homogeneous if the active solvers are homogeneous, since
    13421342    ! this affects how "in-cloud" water contents are computed
    1343     if (        (this%do_sw .and. this%i_solver_sw == ISolverHomogeneous) &
    1344          & .or. (this%do_lw .and. this%i_solver_lw == ISolverHomogeneous)) then
     1343    if (        (this%do_sw .AND. this%i_solver_sw == ISolverHomogeneous) &
     1344         & .or. (this%do_lw .AND. this%i_solver_lw == ISolverHomogeneous)) then
    13451345      this%is_homogeneous = .true.
    13461346    end if
     
    16691669           &  wavelength1, ' to ', wavelength2, ' m is outside shortwave band'
    16701670      call radiation_abort('Radiation configuration error')
    1671     else if (this%iverbosesetup >= 2 .and. present(weighting_name)) then
     1671    else if (this%iverbosesetup >= 2 .AND. present(weighting_name)) then
    16721672      write(nulout,'(a,a,a,f6.0,a,f6.0,a)') 'Spectral weights for ', &
    16731673           &  weighting_name, ' (', wavenumber1, ' to ', &
     
    17411741    mapping = mapping_local(2:ninterval+1,:)
    17421742
    1743     if (this%iverbosesetup >= 2 .and. present(weighting_name)) then
     1743    if (this%iverbosesetup >= 2 .AND. present(weighting_name)) then
    17441744      write(nulout,'(a,a)') 'Spectral mapping generated for ', &
    17451745           &  weighting_name
  • LMDZ6/branches/Amaury_dev/libf/phylmd/ecrad/radiation/radiation_ecckd.F90

    r5159 r5185  
    376376      DO jwav = 1,nwav-1
    377377        if (wavenumber(jwav) < wavenumber_grid(jwav_grid) &
    378              &  .and. wavenumber(jwav+1) >= wavenumber_grid(jwav_grid)) then
     378             &  .AND. wavenumber(jwav+1) >= wavenumber_grid(jwav_grid)) then
    379379          ! Linear interpolation - this is not perfect
    380380          ssi_grid(jwav_grid) = (ssi(jwav)*(wavenumber(jwav+1)-wavenumber_grid(jwav_grid)) &
     
    650650
    651651      ! Rayleigh scattering
    652       if (this%is_sw .and. present(rayleigh_od_fl)) then
     652      if (this%is_sw .AND. present(rayleigh_od_fl)) then
    653653        DO jlev = 1,nlev
    654654          rayleigh_od_fl(:,jlev,jcol) = global_multiplier &
     
    875875
    876876      ! Rayleigh scattering
    877       if (this%is_sw .and. present(rayleigh_od_fl)) then
     877      if (this%is_sw .AND. present(rayleigh_od_fl)) then
    878878        DO jcol = istartcol,iendcol
    879879          DO jlev = 1,nlev
  • LMDZ6/branches/Amaury_dev/libf/phylmd/ecrad/radiation/radiation_ecckd_interface.F90

    r5159 r5185  
    3939    if (lhook) call dr_hook('radiation_ecckd_interface:setup_gas_optics',0,hook_handle)
    4040
    41     if (config%do_sw .and. config%i_gas_model_sw == IGasModelECCKD) then
     41    if (config%do_sw .AND. config%i_gas_model_sw == IGasModelECCKD) then
    4242
    4343      ! Read shortwave ecCKD gas optics NetCDF file
     
    8484    end if
    8585
    86     if (config%do_lw .and. config%i_gas_model_lw == IGasModelECCKD) then
     86    if (config%do_lw .AND. config%i_gas_model_lw == IGasModelECCKD) then
    8787
    8888      ! Read longwave ecCKD gas optics NetCDF file
     
    255255    end if
    256256   
    257     if (config%do_sw .and. config%i_gas_model_sw == IGasModelECCKD) then
     257    if (config%do_sw .AND. config%i_gas_model_sw == IGasModelECCKD) then
    258258
    259259      if (is_volume_mixing_ratio) then
     
    293293    end if
    294294
    295     if (config%do_lw .and. config%i_gas_model_lw == IGasModelECCKD) then
     295    if (config%do_lw .AND. config%i_gas_model_lw == IGasModelECCKD) then
    296296
    297297      if (is_volume_mixing_ratio) then
  • LMDZ6/branches/Amaury_dev/libf/phylmd/ecrad/radiation/radiation_flux.F90

    r5159 r5185  
    414414    if (lhook) call dr_hook('radiation_flux:calc_surface_spectral',0,hook_handle)
    415415
    416     if (config%do_sw .and. config%do_surface_sw_spectral_flux) then
     416    if (config%do_sw .AND. config%do_surface_sw_spectral_flux) then
    417417
    418418      if (use_indexed_sum_vec) then
     
    473473
    474474    ! Fluxes in bands required for canopy radiative transfer
    475     if (config%do_sw .and. config%do_canopy_fluxes_sw) then
     475    if (config%do_sw .AND. config%do_canopy_fluxes_sw) then
    476476      if (config%use_canopy_full_spectrum_sw) then
    477477        this%sw_dn_diffuse_surf_canopy(:,istartcol:iendcol) = this%sw_dn_diffuse_surf_g(:,istartcol:iendcol)
     
    525525    end if ! do_canopy_fluxes_sw
    526526
    527     if (config%do_lw .and. config%do_canopy_fluxes_lw) then
     527    if (config%do_lw .AND. config%do_canopy_fluxes_lw) then
    528528      if (config%use_canopy_full_spectrum_lw) then
    529529        this%lw_dn_surf_canopy(:,istartcol:iendcol) = this%lw_dn_surf_g(:,istartcol:iendcol)
     
    592592    if (lhook) call dr_hook('radiation_flux:calc_toa_spectral',0,hook_handle)
    593593
    594     if (config%do_sw .and. config%do_toa_spectral_flux) then
     594    if (config%do_sw .AND. config%do_toa_spectral_flux) then
    595595
    596596      if (use_indexed_sum_vec) then
     
    627627    end if
    628628
    629     if (config%do_lw .and. config%do_toa_spectral_flux) then
     629    if (config%do_lw .AND. config%do_toa_spectral_flux) then
    630630
    631631      if (use_indexed_sum_vec) then
  • LMDZ6/branches/Amaury_dev/libf/phylmd/ecrad/radiation/radiation_gas.F90

    r5159 r5185  
    380380      if (this%is_present(igas)) then
    381381        if (iunits == IMassMixingRatio &
    382              &   .and. this%iunits(igas) == IVolumeMixingRatio) then
     382             &   .AND. this%iunits(igas) == IVolumeMixingRatio) then
    383383          sf = sf * GasMolarMass(igas) / AirMolarMass
    384384        else if (iunits == IVolumeMixingRatio &
    385              &   .and. this%iunits(igas) == IMassMixingRatio) then
     385             &   .AND. this%iunits(igas) == IMassMixingRatio) then
    386386          sf = sf * AirMolarMass / GasMolarMass(igas)
    387387        end if
     
    417417    scaling = this%scale_factor
    418418    DO jg = 1,NMaxGases
    419       if (iunits == IMassMixingRatio .and. this%iunits(jg) == IVolumeMixingRatio) then
     419      if (iunits == IMassMixingRatio .AND. this%iunits(jg) == IVolumeMixingRatio) then
    420420        scaling(jg) = scaling(jg) * GasMolarMass(jg) / AirMolarMass
    421       else if (iunits == IVolumeMixingRatio .and. this%iunits(jg) == IMassMixingRatio) then
     421      else if (iunits == IVolumeMixingRatio .AND. this%iunits(jg) == IMassMixingRatio) then
    422422        scaling(jg) = scaling(jg) * AirMolarMass / GasMolarMass(jg)
    423423      end if
     
    544544    else
    545545      if (iunits == IMassMixingRatio &
    546            &   .and. this%iunits(igas) == IVolumeMixingRatio) then
     546           &   .AND. this%iunits(igas) == IVolumeMixingRatio) then
    547547        sf = sf * GasMolarMass(igas) / AirMolarMass
    548548      else if (iunits == IVolumeMixingRatio &
    549            &   .and. this%iunits(igas) == IMassMixingRatio) then
     549           &   .AND. this%iunits(igas) == IMassMixingRatio) then
    550550        sf = sf * AirMolarMass / GasMolarMass(igas)
    551551      end if
  • LMDZ6/branches/Amaury_dev/libf/phylmd/ecrad/radiation/radiation_homogeneous_lw.F90

    r5159 r5185  
    221221                       &     / od_total
    222222                end where
    223                 where (ssa_total > 0.0_jprb .and. od_total > 0.0_jprb)
     223                where (ssa_total > 0.0_jprb .AND. od_total > 0.0_jprb)
    224224                  g_total = (g(:,jlev,jcol)*ssa(:,jlev,jcol)*od(:,jlev,jcol) &
    225225                       &     +   g_cloud(config%i_band_from_reordered_g_lw,jlev,jcol) &
     
    233233                       &     * od_cloud_g / od_total
    234234                end where
    235                 where (ssa_total > 0.0_jprb .and. od_total > 0.0_jprb)
     235                where (ssa_total > 0.0_jprb .AND. od_total > 0.0_jprb)
    236236                  g_total = g_cloud(config%i_band_from_reordered_g_lw,jlev,jcol) &
    237237                       &     * ssa_cloud(config%i_band_from_reordered_g_lw,jlev,jcol) &
  • LMDZ6/branches/Amaury_dev/libf/phylmd/ecrad/radiation/radiation_homogeneous_sw.F90

    r5159 r5185  
    244244                     &     / od_total
    245245              end where
    246               where (ssa_total > 0.0_jprb .and. od_total > 0.0_jprb)
     246              where (ssa_total > 0.0_jprb .AND. od_total > 0.0_jprb)
    247247                g_total = (g(:,jlev,jcol)*ssa(:,jlev,jcol)*od(:,jlev,jcol) &
    248248                     &     +   g_cloud(config%i_band_from_reordered_g_sw,jlev,jcol) &
  • LMDZ6/branches/Amaury_dev/libf/phylmd/ecrad/radiation/radiation_ifs_rrtm.F90

    r5159 r5185  
    8181    if (lhook) call dr_hook('radiation_ifs_rrtm:setup_gas_optics',0,hook_handle)
    8282
    83     do_sw = (config%do_sw .and. config%i_gas_model_sw == IGasModelIFSRRTMG)
    84     do_lw = (config%do_lw .and. config%i_gas_model_lw == IGasModelIFSRRTMG)
     83    do_sw = (config%do_sw .AND. config%i_gas_model_sw == IGasModelIFSRRTMG)
     84    do_lw = (config%do_lw .AND. config%i_gas_model_lw == IGasModelIFSRRTMG)
    8585   
    8686    ! The IFS implementation of RRTMG uses many global variables.  In
     
    373373    if (lhook) call dr_hook('radiation_ifs_rrtm:gas_optics',0,hook_handle)
    374374
    375     do_sw = (config%do_sw .and. config%i_gas_model_sw == IGasModelIFSRRTMG)
    376     do_lw = (config%do_lw .and. config%i_gas_model_lw == IGasModelIFSRRTMG)
     375    do_sw = (config%do_sw .AND. config%i_gas_model_sw == IGasModelIFSRRTMG)
     376    do_lw = (config%do_lw .AND. config%i_gas_model_lw == IGasModelIFSRRTMG)
    377377
    378378    ! Compute start and end levels for indexing the gas mixing ratio
     
    670670      DO jcol = istartcol,iendcol
    671671        temperature = thermodynamics%temperature_hl(jcol,jlev+ilevoffset)
    672         if (temperature < 339.0_jprb .and. temperature >= 160.0_jprb) then
     672        if (temperature < 339.0_jprb .AND. temperature >= 160.0_jprb) then
    673673          ! Linear interpolation between -113 and 66 degC
    674674          ind(jcol)  = int(temperature - 159.0_jprb)
     
    796796    DO jcol = istartcol,iendcol
    797797      Tsurf = temperature(jcol)
    798       if (Tsurf < 339.0_jprb .and. Tsurf >= 160.0_jprb) then
     798      if (Tsurf < 339.0_jprb .AND. Tsurf >= 160.0_jprb) then
    799799        ! Linear interpolation between -113 and 66 degC
    800800        ind(jcol)  = int(Tsurf - 159.0_jprb)
  • LMDZ6/branches/Amaury_dev/libf/phylmd/ecrad/radiation/radiation_interface.F90

    r5159 r5185  
    8383
    8484    if (config%do_lw_aerosol_scattering &
    85          & .and. .not. config%do_lw_cloud_scattering) then
     85         & .AND. .not. config%do_lw_cloud_scattering) then
    8686      write(nulerr, '(a)') '*** Error: longwave aerosol scattering requires longwave cloud scattering'
    8787      call radiation_abort('Radiation configuration error')
     
    114114    ! solver_lw as they will be needed.
    115115    if (config%do_lw_cloud_scattering &
    116          &  .and. config%i_solver_lw == ISolverMcICA) then
     116         &  .AND. config%i_solver_lw == ISolverMcICA) then
    117117      config%n_g_lw_if_scattering = config%n_g_lw
    118118    end if
     
    404404      ! a NetCDF file
    405405      if (config%do_save_radiative_properties) then
    406         if (istartcol == 1 .and. iendcol == ncol) then
     406        if (istartcol == 1 .AND. iendcol == ncol) then
    407407          rad_prop_file_name = rad_prop_base_file_name // ".nc"
    408408        else
  • LMDZ6/branches/Amaury_dev/libf/phylmd/ecrad/radiation/radiation_save.F90

    r5159 r5185  
    8787
    8888    if (config%i_gas_model_lw == IGasModelMonochromatic &
    89          .and. config%mono_lw_wavelength > 0.0_jprb) then
     89         .AND. config%mono_lw_wavelength > 0.0_jprb) then
    9090      lw_units_str = 'W m-3'
    9191    else
     
    127127    end if
    128128
    129     if (config%do_lw .and. config%do_canopy_fluxes_lw) then
     129    if (config%do_lw .AND. config%do_canopy_fluxes_lw) then
    130130      call out_file%define_dimension("canopy_band_lw", &
    131131           &  size(flux%lw_dn_surf_canopy, 1))
    132132    end if
    133     if (config%do_sw .and. config%do_canopy_fluxes_sw) then
     133    if (config%do_sw .AND. config%do_canopy_fluxes_sw) then
    134134      call out_file%define_dimension("canopy_band_sw", &
    135135           &  size(flux%sw_dn_diffuse_surf_canopy, 1))
     
    328328    end if
    329329   
    330     if (config%do_lw .and. config%do_clouds) then
     330    if (config%do_lw .AND. config%do_clouds) then
    331331      call out_file%define_variable("cloud_cover_lw", &
    332332           &  dim1_name="column", units_str="1", &
     
    334334           &  standard_name="cloud_area_fraction")
    335335    end if
    336     if (config%do_sw .and. config%do_clouds) then
     336    if (config%do_sw .AND. config%do_clouds) then
    337337      call out_file%define_variable("cloud_cover_sw", &
    338338           &  dim1_name="column", units_str="1", &
     
    444444    end if
    445445
    446     if (config%do_lw .and. config%do_clouds) then
     446    if (config%do_lw .AND. config%do_clouds) then
    447447      call out_file%put("cloud_cover_lw", flux%cloud_cover_lw)
    448448    end if
    449     if (config%do_sw .and. config%do_clouds) then
     449    if (config%do_sw .AND. config%do_clouds) then
    450450      call out_file%put("cloud_cover_sw", flux%cloud_cover_sw)
    451451    end if
     
    516516
    517517    if (config%i_gas_model_lw == IGasModelMonochromatic &
    518          .and. config%mono_lw_wavelength > 0.0_jprb) then
     518         .AND. config%mono_lw_wavelength > 0.0_jprb) then
    519519      lw_units_str = 'W m-3'
    520520    else
     
    543543    call out_file%define_dimension("half_level", n_lev_plus1)
    544544
    545     if (config%do_lw .and. config%do_canopy_fluxes_lw) then
     545    if (config%do_lw .AND. config%do_canopy_fluxes_lw) then
    546546      call out_file%define_dimension("canopy_band_lw", &
    547547           &  size(flux%lw_dn_surf_canopy, 1))
    548548    end if
    549     if (config%do_sw .and. config%do_canopy_fluxes_sw) then
     549    if (config%do_sw .AND. config%do_canopy_fluxes_sw) then
    550550      call out_file%define_dimension("canopy_band_sw", &
    551551           &  size(flux%sw_dn_diffuse_surf_canopy, 1))
     
    838838         &  units_str="Pa", long_name="Pressure on half-levels")
    839839
    840     if (allocated(thermodynamics%h2o_sat_liq) .and. config%use_aerosols) then
     840    if (allocated(thermodynamics%h2o_sat_liq) .AND. config%use_aerosols) then
    841841      call out_file%define_variable("q_sat_liquid", &
    842842           &  dim2_name="column", dim1_name="level", &
     
    953953    call out_file%put("pressure_hl", thermodynamics%pressure_hl(istartcol:iendcol,:))
    954954
    955     if (allocated(thermodynamics%h2o_sat_liq) .and. config%use_aerosols) then
     955    if (allocated(thermodynamics%h2o_sat_liq) .AND. config%use_aerosols) then
    956956      call out_file%put("q_sat_liquid", thermodynamics%h2o_sat_liq(istartcol:iendcol,:))
    957957    end if
     
    10741074    nlev = nlev - 1
    10751075   
    1076     do_aerosol = config%use_aerosols .and. present(aerosol)
     1076    do_aerosol = config%use_aerosols .AND. present(aerosol)
    10771077
    10781078    ! Open the file
     
    11691169         &   units_str="1", long_name="Ozone mass mixing ratio")
    11701170    DO jgas = 1,NMaxGases
    1171       if (gas%is_present(jgas) .and. jgas /= IH2O .and. jgas /= IO3) then
     1171      if (gas%is_present(jgas) .AND. jgas /= IH2O .AND. jgas /= IO3) then
    11721172        write(var_name,'(a,a)') trim(GasLowerCaseName(jgas)), '_vmr'
    11731173        write(long_name,'(a,a)') trim(GasName(jgas)), ' volume mixing ratio'
     
    12441244    end if
    12451245    call out_file%put("lw_emissivity", single_level%lw_emissivity)
    1246     if (config%do_clouds .and. allocated(single_level%iseed)) then
     1246    if (config%do_clouds .AND. allocated(single_level%iseed)) then
    12471247      allocate(seed(ncol))
    12481248      seed = single_level%iseed
     
    12601260    call out_file%put("o3_mmr", mixing_ratio)
    12611261    DO jgas = 1,NMaxGases
    1262       if (gas%is_present(jgas) .and. jgas /= IH2O .and. jgas /= IO3) then
     1262      if (gas%is_present(jgas) .AND. jgas /= IH2O .AND. jgas /= IO3) then
    12631263        write(var_name,'(a,a)') trim(GasLowerCaseName(jgas)), '_vmr'
    12641264        call gas%get(jgas, IVolumeMixingRatio, mixing_ratio)
  • LMDZ6/branches/Amaury_dev/libf/phylmd/ecrad/radiation/radiation_single_level.F90

    r5159 r5185  
    325325    end if
    326326
    327     if (config%do_lw .and. present(lw_albedo)) then
     327    if (config%do_lw .AND. present(lw_albedo)) then
    328328      if (config%use_canopy_full_spectrum_lw) then
    329329        if (config%n_g_lw /= size(this%lw_emissivity,2)) then
  • LMDZ6/branches/Amaury_dev/libf/phylmd/ecrad/radiation/radiation_spartacus_lw.F90

    r5159 r5185  
    421421          ! region and the sky is overcast then 3D calculations must
    422422          ! be turned off as there will be only one region
    423           if (config%do_3d_effects .and. &
    424                &  allocated(cloud%inv_cloud_effective_size) .and. &
    425                &  .not. (nreg == 2 .and. cloud%fraction(jcol,jlev) &
     423          if (config%do_3d_effects .AND. &
     424               &  allocated(cloud%inv_cloud_effective_size) .AND. &
     425               &  .not. (nreg == 2 .AND. cloud%fraction(jcol,jlev) &
    426426               &  > 1.0_jprb-config%cloud_fraction_threshold)) then
    427427            if (cloud%inv_cloud_effective_size(jcol,jlev) &
     
    586586            ! 3D effects for any further g-points
    587587            if (ng3D == ng &
    588                  &  .and. od_region(jg,1) > config%max_gas_od_3D) then
     588                 &  .AND. od_region(jg,1) > config%max_gas_od_3D) then
    589589              ng3D = jg-1
    590590            end if
     
    637637          ! of the cloud
    638638          if (config%do_lw_side_emissivity &
    639              & .and. region_fracs(1,jlev,jcol) > 0.0_jprb .and. region_fracs(2,jlev,jcol) > 0.0_jprb &
    640              & .and. config%do_3d_effects &
    641              & .and. cloud%inv_cloud_effective_size(jcol,jlev) > 0.0_jprb) then
     639             & .AND. region_fracs(1,jlev,jcol) > 0.0_jprb .AND. region_fracs(2,jlev,jcol) > 0.0_jprb &
     640             & .AND. config%do_3d_effects &
     641             & .AND. cloud%inv_cloud_effective_size(jcol,jlev) > 0.0_jprb) then
    642642            aspect_ratio = 1.0_jprb / (min(cloud%inv_cloud_effective_size(jcol,jlev), &
    643643                 &                         1.0_jprb / config%min_cloud_effective_size) &
     
    894894        ! source below a layer interface to the equivalent values
    895895        ! just above
    896         if (is_clear_sky_layer(jlev) .and. is_clear_sky_layer(jlev-1)) then
     896        if (is_clear_sky_layer(jlev) .AND. is_clear_sky_layer(jlev-1)) then
    897897          ! If both layers are cloud free, this is trivial...
    898898          total_albedo(:,:,:,jlev) = 0.0_jprb
     
    10141014        ! Account for overlap rules in translating fluxes just above
    10151015        ! a layer interface to the values just below
    1016         if (is_clear_sky_layer(jlev) .and. is_clear_sky_layer(jlev+1)) then
     1016        if (is_clear_sky_layer(jlev) .AND. is_clear_sky_layer(jlev+1)) then
    10171017          flux_dn_below = flux_dn_above
    10181018        else
  • LMDZ6/branches/Amaury_dev/libf/phylmd/ecrad/radiation/radiation_spartacus_sw.F90

    r5159 r5185  
    493493          end if
    494494
    495           if (config%do_3d_effects .and. &
    496                &  allocated(cloud%inv_cloud_effective_size) .and. &
    497                &  .not. (nreg == 2 .and. cloud%fraction(jcol,jlev) &
     495          if (config%do_3d_effects .AND. &
     496               &  allocated(cloud%inv_cloud_effective_size) .AND. &
     497               &  .not. (nreg == 2 .AND. cloud%fraction(jcol,jlev) &
    498498               &  > 1.0-config%cloud_fraction_threshold)) then
    499499            if (cloud%inv_cloud_effective_size(jcol,jlev) > 0.0_jprb) then
     
    662662            ! 3D effects for any further g-points
    663663            if (ng3D == ng &
    664                  &  .and. od_region(jg,1) > config%max_gas_od_3D) then
     664                 &  .AND. od_region(jg,1) > config%max_gas_od_3D) then
    665665              ng3D = jg-1
    666666            end if
     
    935935        if ((config%i_3d_sw_entrapment == IEntrapmentExplicitNonFractal &
    936936             &  .or. config%i_3d_sw_entrapment == IEntrapmentExplicit) &
    937              &  .and. jlev >= i_cloud_top) then
     937             &  .AND. jlev >= i_cloud_top) then
    938938#else
    939939        if (config%i_3d_sw_entrapment == IEntrapmentExplicitNonFractal &
     
    969969        ! Account for cloud overlap when converting albedo and source
    970970        ! below a layer interface to the equivalent values just above
    971         if (is_clear_sky_layer(jlev) .and. is_clear_sky_layer(jlev-1)) then
     971        if (is_clear_sky_layer(jlev) .AND. is_clear_sky_layer(jlev-1)) then
    972972          ! If both layers are cloud free, this is trivial...
    973973          total_albedo(:,:,:,jlev) = 0.0_jprb
     
    12171217                       &  / max(config%cloud_fraction_threshold, region_fracs(jreg,jlev,jcol))
    12181218                  DO jreg4 = 1,nreg ! VIA first lower region (jreg2 is second lower region)
    1219                     if (.not. (jreg4 == jreg .and. jreg4 /= jreg2)) then
     1219                    if (.not. (jreg4 == jreg .AND. jreg4 /= jreg2)) then
    12201220                      albedo_part(:,jreg3,jreg) = albedo_part(:,jreg3,jreg) + entrapment(:,jreg3,jreg) &
    12211221                           &  * v_matrix(jreg4,jreg,jlev,jcol) * total_albedo_below(:,jreg2,jreg4)
     
    13051305                       &  / max(config%cloud_fraction_threshold, region_fracs(jreg,jlev,jcol))
    13061306                  DO jreg4 = 1,nreg
    1307                     if (.not. (jreg4 == jreg .and. jreg4 /= jreg2)) then
     1307                    if (.not. (jreg4 == jreg .AND. jreg4 /= jreg2)) then
    13081308                     albedo_part(:,jreg3,jreg) = albedo_part(:,jreg3,jreg) + entrapment(:,jreg3,jreg) &
    13091309                           &  * v_matrix(jreg4,jreg,jlev,jcol) * total_albedo_below_direct(:,jreg2,jreg4)
     
    13291329        if ((config%i_3d_sw_entrapment == IEntrapmentExplicitNonFractal &
    13301330             &  .or. config%i_3d_sw_entrapment == IEntrapmentExplicit) &
    1331              &  .and. .not. (is_clear_sky_layer(jlev) .and. is_clear_sky_layer(jlev-1))) then
     1331             &  .AND. .not. (is_clear_sky_layer(jlev) .AND. is_clear_sky_layer(jlev-1))) then
    13321332          ! Horizontal migration distances are averaged when
    13331333          ! applying overlap rules, so equation is
     
    15251525        ! Account for overlap rules in translating fluxes just above
    15261526        ! a layer interface to the values just below
    1527         if (is_clear_sky_layer(jlev) .and. is_clear_sky_layer(jlev+1)) then
     1527        if (is_clear_sky_layer(jlev) .AND. is_clear_sky_layer(jlev+1)) then
    15281528          ! Regions in current layer map directly on to regions in
    15291529          ! layer below
  • LMDZ6/branches/Amaury_dev/libf/phylmd/ecrad/radiation/radiation_spectral_definition.F90

    r5159 r5185  
    202202      find_wavenumber = 1
    203203      DO while (wavenumber > this%wavenumber2(find_wavenumber) &
    204            &    .and. find_wavenumber < this%nwav)
     204           &    .AND. find_wavenumber < this%nwav)
    205205        find_wavenumber = find_wavenumber + 1
    206206      end do
     
    290290          ! will be applicable
    291291          if (wavenumber(jwav) >= this%wavenumber1_band(jband) &
    292                & .and. wavenumber(jwav) <= this%wavenumber2_band(jband)) then
     292               & .AND. wavenumber(jwav) <= this%wavenumber2_band(jband)) then
    293293            if (jwav > 1) then
    294294              wavenum1 = max(this%wavenumber1_band(jband), &
     
    432432                 &       / (this%wavenumber2(isd1)-this%wavenumber1(isd1))
    433433          else
    434             if (isd2 >= 1 .and. isd2 <= this%nwav) then
     434            if (isd2 >= 1 .AND. isd2 <= this%nwav) then
    435435              ! Right part of triangle
    436436              weight(isd2) = weight(isd2) + 0.5_jprb * (wavenum2-this%wavenumber1(isd2))**2 &
     
    696696        wavenumber2_bound = 0.01_jprb / wavelength_bound(jint-1)
    697697        where (wavenumber_mid > wavenumber1_bound &
    698              & .and. wavenumber_mid <= wavenumber2_bound)
     698             & .AND. wavenumber_mid <= wavenumber2_bound)
    699699          i_input = i_intervals(jint)
    700700        end where
  • LMDZ6/branches/Amaury_dev/libf/phylmd/ecrad/radiation/radiation_tripleclouds_lw.F90

    r5159 r5185  
    325325                       &     / od_total
    326326                end where
    327                 where (ssa_total > 0.0_jprb .and. od_total > 0.0_jprb)
     327                where (ssa_total > 0.0_jprb .AND. od_total > 0.0_jprb)
    328328                  g_total = (g(:,jlev,jcol)*ssa(:,jlev,jcol)*od(:,jlev,jcol) &
    329329                       &     +   g_cloud(config%i_band_from_reordered_g_lw,jlev,jcol) &
     
    337337                       &     * od_cloud_new / od_total
    338338                end where
    339                 where (ssa_total > 0.0_jprb .and. od_total > 0.0_jprb)
     339                where (ssa_total > 0.0_jprb .AND. od_total > 0.0_jprb)
    340340                  g_total = g_cloud(config%i_band_from_reordered_g_lw,jlev,jcol) &
    341341                       &     * ssa_cloud(config%i_band_from_reordered_g_lw,jlev,jcol) &
     
    418418        ! Account for cloud overlap when converting albedo below a
    419419        ! layer interface to the equivalent values just above
    420         if (is_clear_sky_layer(jlev) .and. is_clear_sky_layer(jlev-1)) then
     420        if (is_clear_sky_layer(jlev) .AND. is_clear_sky_layer(jlev-1)) then
    421421          total_albedo(:,:,jlev) = total_albedo_below(:,:)
    422422          total_source(:,:,jlev) = total_source_below(:,:)
     
    518518
    519519        if (.not. (is_clear_sky_layer(jlev) &
    520              &    .and. is_clear_sky_layer(jlev+1))) then
     520             &    .AND. is_clear_sky_layer(jlev+1))) then
    521521          ! Account for overlap rules in translating fluxes just above
    522522          ! a layer interface to the values just below
  • LMDZ6/branches/Amaury_dev/libf/phylmd/ecrad/radiation/radiation_tripleclouds_lw.F90.or

    r4946 r5185  
    340340                       &     / od_total
    341341                end where
    342                 where (ssa_total > 0.0_jprb .and. od_total > 0.0_jprb)
     342                where (ssa_total > 0.0_jprb .AND. od_total > 0.0_jprb)
    343343                  g_total = (g(:,jlev,jcol)*ssa(:,jlev,jcol)*od(:,jlev,jcol) &
    344344                       &     +   g_cloud(config%i_band_from_reordered_g_lw,jlev,jcol) &
     
    352352                       &     * od_cloud_new / od_total
    353353                end where
    354                 where (ssa_total > 0.0_jprb .and. od_total > 0.0_jprb)
     354                where (ssa_total > 0.0_jprb .AND. od_total > 0.0_jprb)
    355355                  g_total = g_cloud(config%i_band_from_reordered_g_lw,jlev,jcol) &
    356356                       &     * ssa_cloud(config%i_band_from_reordered_g_lw,jlev,jcol) &
     
    433433        ! Account for cloud overlap when converting albedo below a
    434434        ! layer interface to the equivalent values just above
    435         if (is_clear_sky_layer(jlev) .and. is_clear_sky_layer(jlev-1)) then
     435        if (is_clear_sky_layer(jlev) .AND. is_clear_sky_layer(jlev-1)) then
    436436          total_albedo(:,:,jlev) = total_albedo_below(:,:)
    437437          total_source(:,:,jlev) = total_source_below(:,:)
     
    550550
    551551        if (.not. (is_clear_sky_layer(jlev) &
    552              &    .and. is_clear_sky_layer(jlev+1))) then
     552             &    .AND. is_clear_sky_layer(jlev+1))) then
    553553          ! Account for overlap rules in translating fluxes just above
    554554          ! a layer interface to the values just below
  • LMDZ6/branches/Amaury_dev/libf/phylmd/ecrad/radiation/radiation_tripleclouds_sw.F90

    r5159 r5185  
    1818!   2017-10-23  R. Hogan  Renamed single-character variables
    1919!   2018-10-08  R. Hogan  Call calc_region_properties
    20 !   2019-01-02  R. Hogan  Fixed problem of do_save_spectral_flux .and. .not. do_sw_direct
     20!   2019-01-02  R. Hogan  Fixed problem of do_save_spectral_flux .AND. .not. do_sw_direct
    2121!   2020-09-18  R. Hogan  Replaced some array expressions with loops for speed
    2222!   2021-10-01  P. Ukkonen Performance optimizations: batched computations
     
    392392        ! Account for cloud overlap when converting albedo below a
    393393        ! layer interface to the equivalent values just above
    394         if (is_clear_sky_layer(jlev) .and. is_clear_sky_layer(jlev-1)) then
     394        if (is_clear_sky_layer(jlev) .AND. is_clear_sky_layer(jlev-1)) then
    395395          total_albedo(:,:,jlev)        = total_albedo_below(:,:)
    396396          total_albedo_direct(:,:,jlev) = total_albedo_below_direct(:,:)
     
    539539       
    540540        if (.not. (is_clear_sky_layer(jlev) &
    541              &    .and. is_clear_sky_layer(jlev+1))) then
     541             &    .AND. is_clear_sky_layer(jlev+1))) then
    542542          ! Account for overlap rules in translating fluxes just above
    543543          ! a layer interface to the values just below
  • LMDZ6/branches/Amaury_dev/libf/phylmd/ecrad/utilities/easy_netcdf.F90

    r5159 r5185  
    763763    DO j = 1, ndims
    764764      n = n * ndimlens(j)
    765       if (j > 1 .and. ndimlens(j) > 1) then
     765      if (j > 1 .AND. ndimlens(j) > 1) then
    766766        write(nulerr,'(a,a,a)') '*** Error reading NetCDF variable ', &
    767767             & var_name, &
     
    821821    DO j = 1, ndims
    822822      n = n * ndimlens(j)
    823       if (j > 1 .and. ndimlens(j) > 1) then
     823      if (j > 1 .AND. ndimlens(j) > 1) then
    824824        write(nulerr,'(a,a,a)') '*** Error reading NetCDF variable ', &
    825825             & var_name, &
     
    880880    DO j = 1, ndims
    881881      n = n * ndimlens(j)
    882       if (j > 1 .and. ndimlens(j) > 1) then
     882      if (j > 1 .AND. ndimlens(j) > 1) then
    883883        write(nulerr,'(a,a,a)') '*** Error reading NetCDF variable ', &
    884884             & var_name, &
     
    940940    DO j = 1, ndims-1
    941941      n = n * ndimlens(j)
    942       if (j > 1 .and. ndimlens(j) > 1) then
     942      if (j > 1 .AND. ndimlens(j) > 1) then
    943943        write(nulerr,'(a,a,a)') '*** Error reading 1D slice from NetCDF variable ', &
    944944             & var_name, &
     
    10231023    DO j = 1, ndims
    10241024      ntotal = ntotal * ndimlens(j)
    1025       if (j > 2 .and. ndimlens(j) > 1) then
     1025      if (j > 2 .AND. ndimlens(j) > 1) then
    10261026        write(nulerr,'(a,a,a)') '*** Error reading NetCDF variable ', &
    10271027           & var_name, &
     
    11351135    DO j = 1, ndims
    11361136      ntotal = ntotal * ndimlens(j)
    1137       if (j > 2 .and. ndimlens(j) > 1) then
     1137      if (j > 2 .AND. ndimlens(j) > 1) then
    11381138        write(nulerr,'(a,a,a)') '*** Error reading NetCDF variable ', &
    11391139           & var_name, &
     
    12541254    DO j = 1, ndims-1
    12551255      ntotal = ntotal * ndimlens(j)
    1256       if (j > 2 .and. ndimlens(j) > 1) then
     1256      if (j > 2 .AND. ndimlens(j) > 1) then
    12571257        write(nulerr,'(a,a,a)') '*** Error reading 2D slice from NetCDF variable ', &
    12581258           & var_name, &
     
    13781378    DO j = 1, ndims
    13791379      ntotal = ntotal * ndimlens(j)
    1380       if (j > 3 .and. ndimlens(j) > 1) then
     1380      if (j > 3 .AND. ndimlens(j) > 1) then
    13811381        write(nulerr,'(a,a,a)') '*** Error reading NetCDF variable ', &
    13821382           & var_name, &
     
    15141514    DO j = 1, ndims-1
    15151515      ntotal = ntotal * ndimlens(j)
    1516       if (j > 3 .and. ndimlens(j) > 1) then
     1516      if (j > 3 .AND. ndimlens(j) > 1) then
    15171517        write(nulerr,'(a,a,a)') '*** Error reading 3D slice from NetCDF variable ', &
    15181518           & var_name, &
     
    16561656    DO j = 1, ndims
    16571657      ntotal = ntotal * ndimlens(j)
    1658       if (j > 4 .and. ndimlens(j) > 1) then
     1658      if (j > 4 .AND. ndimlens(j) > 1) then
    16591659        write(nulerr,'(a,a,a)') '*** Error reading NetCDF variable ', &
    16601660           & var_name, &
     
    19871987    end if
    19881988
    1989     if (present(dim1_name) .and. ndims_input >= 1) then
     1989    if (present(dim1_name) .AND. ndims_input >= 1) then
    19901990      ! Variable is at least one dimensional
    19911991      ndims_local = 1
     
    19961996        call my_abort('Error writing NetCDF file')
    19971997      end if
    1998       if (present(dim2_name) .and. ndims_input >= 2) then
     1998      if (present(dim2_name) .AND. ndims_input >= 2) then
    19991999        ! Variable is at least two dimensional
    20002000        ndims_local = 2
     
    20052005          call my_abort('Error writing NetCDF file')
    20062006        end if
    2007         if (present(dim3_name) .and. ndims_input >= 3) then
     2007        if (present(dim3_name) .AND. ndims_input >= 3) then
    20082008          ! Variable is at least three dimensional
    20092009          ndims_local = 3
     
    20142014            call my_abort('Error writing NetCDF file')
    20152015          end if
    2016           if (present(dim4_name) .and. ndims_input >= 4) then
     2016          if (present(dim4_name) .AND. ndims_input >= 4) then
    20172017            ! Variable is at least three dimensional
    20182018            ndims_local = 4
     
    24722472    ! Check the total size of the variable to be stored (but receiving
    24732473    ! ntotal is zero then there must be an unlimited dimension)
    2474     if (ntotal /= size(var,kind=jpib) .and. ntotal /= 0) then
     2474    if (ntotal /= size(var,kind=jpib) .AND. ntotal /= 0) then
    24752475      write(nulerr,'(a,i0,a,a,a,i0)') '*** Error: attempt to write matrix of total size ', &
    24762476           & nvarlen, ' to ', var_name, ' which has total size ', ntotal
     
    25512551      write(var_slice_name,'(a,a,i0,a)') var_name, '(:,:,', index3, ')'
    25522552    end if
    2553     if (ntotal /= size(var,kind=jpib) .and. ntotal /= 0) then
     2553    if (ntotal /= size(var,kind=jpib) .AND. ntotal /= 0) then
    25542554      write(nulerr,'(a,i0,a,a,a,i0)') '*** Error: attempt to write matrix of total size ', &
    25552555           & nvarlen, ' to ', trim(var_slice_name), ' which has total size ', ntotal
  • LMDZ6/branches/Amaury_dev/libf/phylmd/ecrad/utilities/print_matrix.F90

    r5158 r5185  
    4747          write(unit_local,'(f16.8,$)') mat(i,j)
    4848       end do
    49        if (present(name) .and. i == size(mat,1)) then
     49       if (present(name) .AND. i == size(mat,1)) then
    5050         write(unit_local,'(a)') ']'
    5151       else
Note: See TracChangeset for help on using the changeset viewer.