Changeset 5070


Ignore:
Timestamp:
Jul 18, 2024, 3:06:28 PM (7 weeks ago)
Author:
abarral
Message:

(lint) replace obsolete operators in guide_loc_mod.F90

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/dyn3dmem/guide_loc_mod.F90

    r5069 r5070  
    125125    CALL getpar('iguide_sav',4,iguide_sav,'freq. sauvegarde guidage')
    126126    ! frequences f>0: fx/jour; f<0: tous les f jours; f=0: 1 seule fois.
    127     IF (iguide_sav.GT.0) THEN
     127    IF (iguide_sav>0) THEN
    128128       iguide_sav=day_step/iguide_sav
    129129    ELSE if (iguide_sav == 0) then
     
    145145    CALL getpar('iguide_read',4,iguide_read,'freq. lecture guidage')
    146146    CALL getpar('iguide_int',4,iguide_int,'freq. interpolation vert')
    147     IF (iguide_int.EQ.0) THEN
     147    IF (iguide_int==0) THEN
    148148        iguide_int=1
    149     ELSEIF (iguide_int.GT.0) THEN
     149    ELSEIF (iguide_int>0) THEN
    150150        iguide_int=day_step/iguide_int
    151151    ELSE
     
    173173! ---------------------------------------------
    174174    ncidpl=-99
    175     if (guide_plevs.EQ.1) then
    176        if (ncidpl.eq.-99) then
     175    if (guide_plevs==1) then
     176       if (ncidpl==-99) then
    177177          rcod=nf90_open('apbp.nc',Nf90_NOWRITe, ncidpl)
    178           if (rcod.NE.NF_NOERR) THEN
     178          if (rcod/=NF_NOERR) THEN
    179179             abort_message=' Nudging error -> no file apbp.nc'
    180180             CALL abort_gcm(modname,abort_message,1)
    181181          endif
    182182       endif
    183     elseif (guide_plevs.EQ.2) then
    184        if (ncidpl.EQ.-99) then
     183    elseif (guide_plevs==2) then
     184       if (ncidpl==-99) then
    185185          rcod=nf90_open('P.nc',Nf90_NOWRITe,ncidpl)
    186           if (rcod.NE.NF_NOERR) THEN
     186          if (rcod/=NF_NOERR) THEN
    187187             abort_message=' Nudging error -> no file P.nc'
    188188             CALL abort_gcm(modname,abort_message,1)
     
    191191
    192192    elseif (guide_u) then
    193        if (ncidpl.eq.-99) then
     193       if (ncidpl==-99) then
    194194          rcod=nf90_open('u.nc',Nf90_NOWRITe,ncidpl)
    195           if (rcod.NE.NF_NOERR) THEN
     195          if (rcod/=NF_NOERR) THEN
    196196             abort_message=' Nudging error -> no file u.nc'
    197197             CALL abort_gcm(modname,abort_message,1)
     
    202202
    203203    elseif (guide_v) then
    204        if (ncidpl.eq.-99) then
     204       if (ncidpl==-99) then
    205205          rcod=nf90_open('v.nc',nf90_nowrite,ncidpl)
    206           if (rcod.NE.NF_NOERR) THEN
     206          if (rcod/=NF_NOERR) THEN
    207207             abort_message=' Nudging error -> no file v.nc'
    208208             CALL abort_gcm(modname,abort_message,1)
     
    212212   
    213213    elseif (guide_T) then
    214        if (ncidpl.eq.-99) then
     214       if (ncidpl==-99) then
    215215          rcod=nf90_open('T.nc',nf90_nowrite,ncidpl)
    216           if (rcod.NE.NF_NOERR) THEN
     216          if (rcod/=NF_NOERR) THEN
    217217             abort_message=' Nudging error -> no file T.nc'
    218218             CALL abort_gcm(modname,abort_message,1)
     
    223223
    224224    elseif (guide_Q) then
    225        if (ncidpl.eq.-99) then
     225       if (ncidpl==-99) then
    226226          rcod=nf90_open('hur.nc',nf90_nowrite, ncidpl)
    227           if (rcod.NE.NF_NOERR) THEN
     227          if (rcod/=NF_NOERR) THEN
    228228             abort_message=' Nudging error -> no file hur.nc'
    229229             CALL abort_gcm(modname,abort_message,1)
     
    234234    endif
    235235    error=NF_INQ_DIMID(ncidpl,'LEVEL',rid)
    236     IF (error.NE.NF_NOERR) error=NF_INQ_DIMID(ncidpl,'PRESSURE',rid)
    237     IF (error.NE.NF_NOERR) THEN
     236    IF (error/=NF_NOERR) error=NF_INQ_DIMID(ncidpl,'PRESSURE',rid)
     237    IF (error/=NF_NOERR) THEN
    238238        abort_message='Nudging: error reading pressure levels'
    239239        CALL abort_gcm(modname,abort_message,1)
     
    316316    ENDIF
    317317
    318     IF (guide_plevs.EQ.2) THEN
     318    IF (guide_plevs==2) THEN
    319319        ALLOCATE(pnat1(iip1,jjb_u:jje_u,nlevnc), stat = error)
    320320        IF (error /= 0) CALL abort_gcm(modname,abort_message,1)
     
    324324    ENDIF
    325325
    326     IF (guide_P.OR.guide_plevs.EQ.1) THEN
     326    IF (guide_P.OR.guide_plevs==1) THEN
    327327        ALLOCATE(psnat1(iip1,jjb_u:jje_u), stat = error)
    328328        IF (error /= 0) CALL abort_gcm(modname,abort_message,1)
     
    351351    IF (guide_T) tnat1=tnat2
    352352    IF (guide_Q) qnat1=qnat2
    353     IF (guide_plevs.EQ.2) pnat1=pnat2
    354     IF (guide_P.OR.guide_plevs.EQ.1) psnat1=psnat2
     353    IF (guide_plevs==2) pnat1=pnat2
     354    IF (guide_P.OR.guide_plevs==1) psnat1=psnat2
    355355
    356356  END SUBROUTINE guide_init
     
    488488! Lecture des fichiers de guidage ?
    489489!-----------------------------------------------------------------------
    490     IF (iguide_read.NE.0) THEN
     490    IF (iguide_read/=0) THEN
    491491      ditau=real(itau)
    492492      dday_step=real(day_step)
    493       IF (iguide_read.LT.0) THEN
     493      IF (iguide_read<0) THEN
    494494          tau=ditau/dday_step/REAL(iguide_read)
    495495      ELSE
     
    497497      ENDIF
    498498      reste=tau-AINT(tau)
    499       IF (reste.EQ.0.) THEN
    500           IF (itau_test.EQ.itau) THEN
     499      IF (reste==0.) THEN
     500          IF (itau_test==itau) THEN
    501501            write(*,*)trim(modname)//' second pass in advreel at itau=',&
    502502            itau
     
    508508              IF (guide_T) tnat1(:,jjbu:jjeu,:)=tnat2(:,jjbu:jjeu,:)
    509509              IF (guide_Q) qnat1(:,jjbu:jjeu,:)=qnat2(:,jjbu:jjeu,:)
    510               IF (guide_plevs.EQ.2) pnat1(:,jjbu:jjeu,:)=pnat2(:,jjbu:jjeu,:)
    511               IF (guide_P.OR.guide_plevs.EQ.1) psnat1(:,jjbu:jjeu)=psnat2(:,jjbu:jjeu)
     510              IF (guide_plevs==2) pnat1(:,jjbu:jjeu,:)=pnat2(:,jjbu:jjeu,:)
     511              IF (guide_P.OR.guide_plevs==1) psnat1(:,jjbu:jjeu)=psnat2(:,jjbu:jjeu)
    512512!$OMP END MASTER
    513513!$OMP BARRIER
     
    540540! Interpolation et conversion des champs de guidage
    541541!-----------------------------------------------------------------------
    542     IF (MOD(itau,iguide_int).EQ.0) THEN
     542    IF (MOD(itau,iguide_int)==0) THEN
    543543        CALL guide_interp(ps,teta)
    544544    ENDIF
    545545! Repartition entre 2 etats de guidage
    546     IF (iguide_read.NE.0) THEN
     546    IF (iguide_read/=0) THEN
    547547        tau=reste
    548548    ELSE
     
    560560!-----------------------------------------------------------------------
    561561! Sauvegarde du guidage?
    562     f_out=((MOD(itau,iguide_sav).EQ.0).AND.guide_sav) 
     562    f_out=((MOD(itau,iguide_sav)==0).AND.guide_sav)
    563563    IF (f_out) THEN
    564564
     
    803803        IF (guide_reg) THEN
    804804            DO i=1,iim
    805                 IF (lond(i).LT.lon_min_g) imin(1)=i
    806                 IF (lond(i).LE.lon_max_g) imax(1)=i
     805                IF (lond(i)<lon_min_g) imin(1)=i
     806                IF (lond(i)<=lon_max_g) imax(1)=i
    807807            ENDDO
    808808            lond=rlonv*180./pi
    809809            DO i=1,iim
    810                 IF (lond(i).LT.lon_min_g) imin(2)=i
    811                 IF (lond(i).LE.lon_max_g) imax(2)=i
     810                IF (lond(i)<lon_min_g) imin(2)=i
     811                IF (lond(i)<=lon_max_g) imax(2)=i
    812812            ENDDO
    813813        ENDIF
     
    875875        IF (guide_reg) THEN
    876876            DO i=1,iim
    877                 IF (lond(i).LT.lon_min_g) imin(1)=i
    878                 IF (lond(i).LE.lon_max_g) imax(1)=i
     877                IF (lond(i)<lon_min_g) imin(1)=i
     878                IF (lond(i)<=lon_max_g) imax(1)=i
    879879            ENDDO
    880880            lond=rlonv*180./pi
    881881            DO i=1,iim
    882                 IF (lond(i).LT.lon_min_g) imin(2)=i
    883                 IF (lond(i).LE.lon_max_g) imax(2)=i
     882                IF (lond(i)<lon_min_g) imin(2)=i
     883                IF (lond(i)<=lon_max_g) imax(2)=i
    884884            ENDDO
    885885        ENDIF
     
    982982   
    983983   
    984     IF (guide_plevs.EQ.0) THEN
     984    IF (guide_plevs==0) THEN
    985985!$OMP DO
    986986        DO l=1,nlevnc
     
    10481048
    10491049!    ....  Calcul de pls , pression au milieu des couches ,en Pascals
    1050     IF (guide_plevs.EQ.1) THEN
     1050    IF (guide_plevs==1) THEN
    10511051!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    10521052        DO l=1,llm
     
    11271127    IF (guide_T) THEN
    11281128        ! Calcul des nouvelles valeurs des niveaux de pression du guidage
    1129         IF (guide_plevs.EQ.1) THEN
     1129        IF (guide_plevs==1) THEN
    11301130!$OMP DO
    11311131            DO l=1,nlevnc
     
    11371137                ENDDO
    11381138            ENDDO
    1139         ELSE IF (guide_plevs.EQ.2) THEN
     1139        ELSE IF (guide_plevs==2) THEN
    11401140!$OMP DO
    11411141            DO l=1,nlevnc
     
    11941194    IF (guide_Q) THEN
    11951195        ! Calcul des nouvelles valeurs des niveaux de pression du guidage
    1196         IF (guide_plevs.EQ.1) THEN
     1196        IF (guide_plevs==1) THEN
    11971197!$OMP DO
    11981198            DO l=1,nlevnc
     
    12041204                ENDDO
    12051205            ENDDO
    1206         ELSE IF (guide_plevs.EQ.2) THEN
     1206        ELSE IF (guide_plevs==2) THEN
    12071207!$OMP DO
    12081208            DO l=1,nlevnc
     
    12661266    IF (guide_u) THEN
    12671267        ! Calcul des nouvelles valeurs des niveaux de pression du guidage
    1268         IF (guide_plevs.EQ.1) THEN
     1268        IF (guide_plevs==1) THEN
    12691269!$OMP DO
    12701270            DO l=1,nlevnc
     
    12801280                ENDDO
    12811281            ENDDO
    1282         ELSE IF (guide_plevs.EQ.2) THEN
     1282        ELSE IF (guide_plevs==2) THEN
    12831283!$OMP DO
    12841284            DO l=1,nlevnc
     
    13341334    IF (guide_v) THEN
    13351335        ! Calcul des nouvelles valeurs des niveaux de pression du guidage
    1336         IF (guide_plevs.EQ.1) THEN
     1336        IF (guide_plevs==1) THEN
    13371337         CALL Register_Hallo_u(psnat1,1,1,2,2,1,Req)
    13381338         CALL Register_Hallo_u(psnat2,1,1,2,2,1,Req)
     
    13521352                ENDDO
    13531353            ENDDO
    1354         ELSE IF (guide_plevs.EQ.2) THEN
     1354        ELSE IF (guide_plevs==2) THEN
    13551355         CALL Register_Hallo_u(pnat1,llm,1,2,2,1,Req)
    13561356         CALL Register_Hallo_u(pnat2,llm,1,2,2,1,Req)
     
    14441444            do j=jjb,jje
    14451445                do i=1,pim
    1446                     if (typ.eq.2) then
     1446                    if (typ==2) then
    14471447                       zlat=rlatu(j)*180./pi
    14481448                       zlon=rlonu(i)*180./pi
    1449                     elseif (typ.eq.1) then
     1449                    elseif (typ==1) then
    14501450                       zlat=rlatu(j)*180./pi
    14511451                       zlon=rlonv(i)*180./pi
    1452                     elseif (typ.eq.3) then
     1452                    elseif (typ==3) then
    14531453                       zlat=rlatv(j)*180./pi
    14541454                       zlon=rlonv(i)*180./pi
     
    14891489            enddo
    14901490        enddo
    1491         IF (typ.EQ.2) THEN
     1491        IF (typ==2) THEN
    14921492            do j=1,jjp1
    14931493                do i=1,iim
     
    14971497            enddo
    14981498        ENDIF
    1499         IF (typ.EQ.3) THEN
     1499        IF (typ==3) THEN
    15001500            do j=1,jjm
    15011501                do i=1,iip1
     
    15191519            enddo
    15201520            ! Calcul de gamma
    1521             if (abs(grossismx-1.).lt.0.1.or.abs(grossismy-1.).lt.0.1) then
     1521            if (abs(grossismx-1.)<0.1.or.abs(grossismy-1.)<0.1) then
    15221522              write(*,*)trim(modname)//' ATTENTION modele peu zoome'
    15231523              write(*,*)trim(modname)//' ATTENTION on prend une constante de guidage cste'
     
    15261526              gamma=(dxdy_max-2.*dxdy_min)/(dxdy_max-dxdy_min)
    15271527              write(*,*)trim(modname)//' gamma=',gamma
    1528               if (gamma.lt.1.e-5) then
     1528              if (gamma<1.e-5) then
    15291529                write(*,*)trim(modname)//' gamma =',gamma,'<1e-5'
    15301530                CALL abort_gcm("guide_loc_mod","stopped",1)
     
    15401540        do j=jjb,jje
    15411541            do i=1,pim
    1542                 if (typ.eq.1) then
     1542                if (typ==1) then
    15431543                   dxdy_=dxdys(i,j)
    15441544                   zlat=rlatu(j)*180./pi
    1545                 elseif (typ.eq.2) then
     1545                elseif (typ==2) then
    15461546                   dxdy_=dxdyu(i,j)
    15471547                   zlat=rlatu(j)*180./pi
    1548                 elseif (typ.eq.3) then
     1548                elseif (typ==3) then
    15491549                   dxdy_=dxdyv(i,j)
    15501550                   zlat=rlatv(j)*180./pi
    15511551                endif
    1552                 if (abs(grossismx-1.).lt.0.1.or.abs(grossismy-1.).lt.0.1) then
     1552                if (abs(grossismx-1.)<0.1.or.abs(grossismy-1.)<0.1) then
    15531553                ! pour une grille reguliere, xi=xxx**0=1 -> alpha=alphamin
    15541554                    alpha(i,j)=alphamin
     
    15561556                    xi=((dxdy_max-dxdy_)/(dxdy_max-dxdy_min))**gamma
    15571557                    xi=min(xi,1.)
    1558                     if(lat_min_g.le.zlat .and. zlat.le.lat_max_g) then
     1558                    if(lat_min_g<=zlat .and. zlat<=lat_max_g) then
    15591559                        alpha(i,j)=xi*alphamin+(1.-xi)*alphamax
    15601560                    else
     
    16001600         write(*,*),trim(modname)//': opening nudging files '
    16011601! Ap et Bp si Niveaux de pression hybrides
    1602          if (guide_plevs.EQ.1) then
     1602         if (guide_plevs==1) then
    16031603             write(*,*),trim(modname)//' Reading nudging on model levels'
    16041604             rcode = nf90_open('apbp.nc', nf90_nowrite, ncidpl)
    1605              IF (rcode.NE.NF_NOERR) THEN
     1605             IF (rcode/=NF_NOERR) THEN
    16061606              abort_message='Nudging: error -> no file apbp.nc'
    16071607              CALL abort_gcm(modname,abort_message,1)
    16081608             ENDIF
    16091609             rcode = nf90_inq_varid(ncidpl, 'AP', varidap)
    1610              IF (rcode.NE.NF_NOERR) THEN
     1610             IF (rcode/=NF_NOERR) THEN
    16111611              abort_message='Nudging: error -> no AP variable in file apbp.nc'
    16121612              CALL abort_gcm(modname,abort_message,1)
    16131613             ENDIF
    16141614             rcode = nf90_inq_varid(ncidpl, 'BP', varidbp)
    1615              IF (rcode.NE.NF_NOERR) THEN
     1615             IF (rcode/=NF_NOERR) THEN
    16161616              abort_message='Nudging: error -> no BP variable in file apbp.nc'
    16171617              CALL abort_gcm(modname,abort_message,1)
     
    16211621         
    16221622! Pression si guidage sur niveaux P variables
    1623          if (guide_plevs.EQ.2) then
     1623         if (guide_plevs==2) then
    16241624             rcode = nf90_open('P.nc', nf90_nowrite, ncidp)
    1625              IF (rcode.NE.NF_NOERR) THEN
     1625             IF (rcode/=NF_NOERR) THEN
    16261626              abort_message='Nudging: error -> no file P.nc'
    16271627              CALL abort_gcm(modname,abort_message,1)
    16281628             ENDIF
    16291629             rcode = nf90_inq_varid(ncidp, 'PRES', varidp)
    1630              IF (rcode.NE.NF_NOERR) THEN
     1630             IF (rcode/=NF_NOERR) THEN
    16311631              abort_message='Nudging: error -> no PRES variable in file P.nc'
    16321632              CALL abort_gcm(modname,abort_message,1)
    16331633             ENDIF
    16341634             write(*,*),trim(modname)//' ncidp,varidp',ncidp,varidp
    1635              if (ncidpl.eq.-99) ncidpl=ncidp
     1635             if (ncidpl==-99) ncidpl=ncidp
    16361636         endif
    16371637
     
    16391639         if (guide_u) then
    16401640             rcode = nf90_open('u.nc', nf90_nowrite, ncidu)
    1641              IF (rcode.NE.NF_NOERR) THEN
     1641             IF (rcode/=NF_NOERR) THEN
    16421642              abort_message='Nudging: error -> no file u.nc'
    16431643              CALL abort_gcm(modname,abort_message,1)
    16441644             ENDIF
    16451645             rcode = nf90_inq_varid(ncidu, 'UWND', varidu)
    1646              IF (rcode.NE.NF_NOERR) THEN
     1646             IF (rcode/=NF_NOERR) THEN
    16471647              abort_message='Nudging: error -> no UWND variable in file u.nc'
    16481648              CALL abort_gcm(modname,abort_message,1)
    16491649             ENDIF
    16501650             write(*,*),trim(modname)//' ncidu,varidu',ncidu,varidu
    1651              if (ncidpl.eq.-99) ncidpl=ncidu
     1651             if (ncidpl==-99) ncidpl=ncidu
    16521652
    16531653   
    16541654             status=NF90_INQ_DIMID(ncidu, "LONU", dimid)
    16551655             status=NF90_INQUIRE_DIMENSION(ncidu,dimid,namedim,lendim)
    1656              IF (lendim .NE. iip1) THEN
     1656             IF (lendim /= iip1) THEN
    16571657                abort_message='dimension LONU different from iip1 in u.nc'
    16581658                CALL abort_gcm(modname,abort_message,1)
     
    16611661             status=NF90_INQ_DIMID(ncidu, "LATU", dimid)
    16621662             status=NF90_INQUIRE_DIMENSION(ncidu,dimid,namedim,lendim)
    1663              IF (lendim .NE. jjp1) THEN
     1663             IF (lendim /= jjp1) THEN
    16641664                abort_message='dimension LATU different from jjp1 in u.nc'
    16651665                CALL abort_gcm(modname,abort_message,1)
     
    16711671         if (guide_v) then
    16721672             rcode = nf90_open('v.nc', nf90_nowrite, ncidv)
    1673              IF (rcode.NE.NF_NOERR) THEN
     1673             IF (rcode/=NF_NOERR) THEN
    16741674              abort_message='Nudging: error -> no file v.nc'
    16751675              CALL abort_gcm(modname,abort_message,1)
    16761676             ENDIF
    16771677             rcode = nf90_inq_varid(ncidv, 'VWND', varidv)
    1678              IF (rcode.NE.NF_NOERR) THEN
     1678             IF (rcode/=NF_NOERR) THEN
    16791679              abort_message='Nudging: error -> no VWND variable in file v.nc'
    16801680              CALL abort_gcm(modname,abort_message,1)
    16811681             ENDIF
    16821682             write(*,*),trim(modname)//' ncidv,varidv',ncidv,varidv
    1683              if (ncidpl.eq.-99) ncidpl=ncidv
     1683             if (ncidpl==-99) ncidpl=ncidv
    16841684             
    16851685             status=NF90_INQ_DIMID(ncidv, "LONV", dimid)
    16861686             status=NF90_INQUIRE_DIMENSION(ncidv,dimid,namedim,lendim)
    16871687             
    1688                 IF (lendim .NE. iip1) THEN
     1688                IF (lendim /= iip1) THEN
    16891689                abort_message='dimension LONV different from iip1 in v.nc'
    16901690                CALL abort_gcm(modname,abort_message,1)
     
    16941694             status=NF90_INQ_DIMID(ncidv, "LATV", dimid)
    16951695             status=NF90_INQUIRE_DIMENSION(ncidv,dimid,namedim,lendim)
    1696              IF (lendim .NE. jjm) THEN
     1696             IF (lendim /= jjm) THEN
    16971697                abort_message='dimension LATV different from jjm in v.nc'
    16981698                CALL abort_gcm(modname,abort_message,1)
     
    17041704         if (guide_T) then
    17051705             rcode = nf90_open('T.nc', nf90_nowrite, ncidt)
    1706              IF (rcode.NE.NF_NOERR) THEN
     1706             IF (rcode/=NF_NOERR) THEN
    17071707              abort_message='Nudging: error -> no file T.nc'
    17081708              CALL abort_gcm(modname,abort_message,1)
    17091709             ENDIF
    17101710             rcode = nf90_inq_varid(ncidt, 'AIR', varidt)
    1711              IF (rcode.NE.NF_NOERR) THEN
     1711             IF (rcode/=NF_NOERR) THEN
    17121712              abort_message='Nudging: error -> no AIR variable in file T.nc'
    17131713              CALL abort_gcm(modname,abort_message,1)
    17141714             ENDIF
    17151715             write(*,*),trim(modname)//' ncidT,varidT',ncidt,varidt
    1716              if (ncidpl.eq.-99) ncidpl=ncidt
     1716             if (ncidpl==-99) ncidpl=ncidt
    17171717
    17181718             status=NF90_INQ_DIMID(ncidt, "LONV", dimid)
    17191719             status=NF90_INQUIRE_DIMENSION(ncidt,dimid,namedim,lendim)
    1720              IF (lendim .NE. iip1) THEN
     1720             IF (lendim /= iip1) THEN
    17211721                abort_message='dimension LONV different from iip1 in T.nc'
    17221722                CALL abort_gcm(modname,abort_message,1)
     
    17251725             status=NF90_INQ_DIMID(ncidt, "LATU", dimid)
    17261726             status=NF90_INQUIRE_DIMENSION(ncidt,dimid,namedim,lendim)
    1727              IF (lendim .NE. jjp1) THEN
     1727             IF (lendim /= jjp1) THEN
    17281728                abort_message='dimension LATU different from jjp1 in T.nc'
    17291729                CALL abort_gcm(modname,abort_message,1)
     
    17351735         if (guide_Q) then
    17361736             rcode = nf90_open('hur.nc', nf90_nowrite, ncidQ)
    1737              IF (rcode.NE.NF_NOERR) THEN
     1737             IF (rcode/=NF_NOERR) THEN
    17381738              abort_message='Nudging: error -> no file hur.nc'
    17391739              CALL abort_gcm(modname,abort_message,1)
    17401740             ENDIF
    17411741             rcode = nf90_inq_varid(ncidQ, 'RH', varidQ)
    1742              IF (rcode.NE.NF_NOERR) THEN
     1742             IF (rcode/=NF_NOERR) THEN
    17431743              abort_message='Nudging: error -> no RH variable in file hur.nc'
    17441744              CALL abort_gcm(modname,abort_message,1)
    17451745             ENDIF
    17461746             write(*,*),trim(modname)//' ncidQ,varidQ',ncidQ,varidQ
    1747              if (ncidpl.eq.-99) ncidpl=ncidQ
     1747             if (ncidpl==-99) ncidpl=ncidQ
    17481748
    17491749
    17501750             status=NF90_INQ_DIMID(ncidQ, "LONV", dimid)
    17511751             status=NF90_INQUIRE_DIMENSION(ncidQ,dimid,namedim,lendim)
    1752              IF (lendim .NE. iip1) THEN
     1752             IF (lendim /= iip1) THEN
    17531753                abort_message='dimension LONV different from iip1 in hur.nc'
    17541754                CALL abort_gcm(modname,abort_message,1)
     
    17571757             status=NF90_INQ_DIMID(ncidQ, "LATU", dimid)
    17581758             status=NF90_INQUIRE_DIMENSION(ncidQ,dimid,namedim,lendim)
    1759              IF (lendim .NE. jjp1) THEN
     1759             IF (lendim /= jjp1) THEN
    17601760                abort_message='dimension LATU different from jjp1 in hur.nc'
    17611761                CALL abort_gcm(modname,abort_message,1)
     
    17651765         endif
    17661766! Pression de surface
    1767          if ((guide_P).OR.(guide_plevs.EQ.1)) then
     1767         if ((guide_P).OR.(guide_plevs==1)) then
    17681768             rcode = nf90_open('ps.nc', nf90_nowrite, ncidps)
    1769              IF (rcode.NE.NF_NOERR) THEN
     1769             IF (rcode/=NF_NOERR) THEN
    17701770              abort_message='Nudging: error -> no file ps.nc'
    17711771              CALL abort_gcm(modname,abort_message,1)
    17721772             ENDIF
    17731773             rcode = nf90_inq_varid(ncidps, 'SP', varidps)
    1774              IF (rcode.NE.NF_NOERR) THEN
     1774             IF (rcode/=NF_NOERR) THEN
    17751775              abort_message='Nudging: error -> no SP variable in file ps.nc'
    17761776              CALL abort_gcm(modname,abort_message,1)
     
    17791779         endif
    17801780! Coordonnee verticale
    1781          if (guide_plevs.EQ.0) then
     1781         if (guide_plevs==0) then
    17821782              rcode = nf90_inq_varid(ncidpl, 'LEVEL', varidpl)
    1783               IF (rcode.NE.0) rcode = nf90_inq_varid(ncidpl, 'PRESSURE', varidpl)
     1783              IF (rcode/=0) rcode = nf90_inq_varid(ncidpl, 'PRESSURE', varidpl)
    17841784              write(*,*),trim(modname)//' ncidpl,varidpl',ncidpl,varidpl
    17851785         endif
    17861786! Coefs ap, bp pour calcul de la pression aux differents niveaux
    1787          IF (guide_plevs.EQ.1) THEN
     1787         IF (guide_plevs==1) THEN
    17881788             status=nf_get_vara_rd(ncidpl,varidap,[1],[nlevnc],apnc)
    17891789             status=nf_get_vara_rd(ncidpl,varidbp,[1],[nlevnc],bpnc)
    1790          ELSEIF (guide_plevs.EQ.0) THEN
     1790         ELSEIF (guide_plevs==0) THEN
    17911791             status=nf_get_vara_rd(ncidpl,varidpl,[1],[nlevnc],apnc)
    17921792!FC Pour les corrections la pression est deja en Pascals on commente la ligne ci-dessous
     
    18141814     IF (invert_y) start(2)=jjp1-jje_u+1
    18151815! Pression
    1816      if (guide_plevs.EQ.2) then
     1816     if (guide_plevs==2) then
    18171817         status=nf_get_vara_rd(ncidp,varidp,start,count,pnat2)
    18181818         IF (invert_y) THEN
     
    18711871
    18721872!  Pression de surface
    1873      if ((guide_P).OR.(guide_plevs.EQ.1))  then
     1873     if ((guide_P).OR.(guide_plevs==1))  then
    18741874         start(2)=jjb_u
    18751875         start(3)=timestep
     
    19221922         write(*,*)trim(modname)//' : opening nudging files '
    19231923! Ap et Bp si niveaux de pression hybrides
    1924          if (guide_plevs.EQ.1) then
     1924         if (guide_plevs==1) then
    19251925           write(*,*)trim(modname)//' Reading nudging on model levels'
    19261926           rcode = nf90_open('apbp.nc', nf90_nowrite, ncidpl)
    1927            IF (rcode.NE.NF_NOERR) THEN
     1927           IF (rcode/=NF_NOERR) THEN
    19281928             abort_message='Nudging: error -> no file apbp.nc'
    19291929           CALL abort_gcm(modname,abort_message,1)
    19301930           ENDIF
    19311931           rcode = nf90_inq_varid(ncidpl, 'AP', varidap)
    1932            IF (rcode.NE.NF_NOERR) THEN
     1932           IF (rcode/=NF_NOERR) THEN
    19331933             abort_message='Nudging: error -> no AP variable in file apbp.nc'
    19341934           CALL abort_gcm(modname,abort_message,1)
    19351935           ENDIF
    19361936           rcode = nf90_inq_varid(ncidpl, 'BP', varidbp)
    1937            IF (rcode.NE.NF_NOERR) THEN
     1937           IF (rcode/=NF_NOERR) THEN
    19381938             abort_message='Nudging: error -> no BP variable in file apbp.nc'
    19391939             CALL abort_gcm(modname,abort_message,1)
     
    19421942         endif
    19431943! Pression
    1944          if (guide_plevs.EQ.2) then
     1944         if (guide_plevs==2) then
    19451945           rcode = nf90_open('P.nc', nf90_nowrite, ncidp)
    1946            IF (rcode.NE.NF_NOERR) THEN
     1946           IF (rcode/=NF_NOERR) THEN
    19471947             abort_message='Nudging: error -> no file P.nc'
    19481948             CALL abort_gcm(modname,abort_message,1)
    19491949           ENDIF
    19501950           rcode = nf90_inq_varid(ncidp, 'PRES', varidp)
    1951            IF (rcode.NE.NF_NOERR) THEN
     1951           IF (rcode/=NF_NOERR) THEN
    19521952             abort_message='Nudging: error -> no PRES variable in file P.nc'
    19531953             CALL abort_gcm(modname,abort_message,1)
    19541954           ENDIF
    19551955           write(*,*)trim(modname)//' ncidp,varidp',ncidp,varidp
    1956            if (ncidpl.eq.-99) ncidpl=ncidp
     1956           if (ncidpl==-99) ncidpl=ncidp
    19571957         endif
    19581958! Vent zonal
    19591959         if (guide_u) then
    19601960           rcode = nf90_open('u.nc', nf90_nowrite, ncidu)
    1961            IF (rcode.NE.NF_NOERR) THEN
     1961           IF (rcode/=NF_NOERR) THEN
    19621962             abort_message='Nudging: error -> no file u.nc'
    19631963             CALL abort_gcm(modname,abort_message,1)
    19641964           ENDIF
    19651965           rcode = nf90_inq_varid(ncidu, 'UWND', varidu)
    1966            IF (rcode.NE.NF_NOERR) THEN
     1966           IF (rcode/=NF_NOERR) THEN
    19671967             abort_message='Nudging: error -> no UWND variable in file u.nc'
    19681968             CALL abort_gcm(modname,abort_message,1)
    19691969           ENDIF
    19701970           write(*,*)trim(modname)//' ncidu,varidu',ncidu,varidu
    1971            if (ncidpl.eq.-99) ncidpl=ncidu
     1971           if (ncidpl==-99) ncidpl=ncidu
    19721972         endif
    19731973
     
    19751975         if (guide_v) then
    19761976           rcode = nf90_open('v.nc', nf90_nowrite, ncidv)
    1977            IF (rcode.NE.NF_NOERR) THEN
     1977           IF (rcode/=NF_NOERR) THEN
    19781978             abort_message='Nudging: error -> no file v.nc'
    19791979             CALL abort_gcm(modname,abort_message,1)
    19801980           ENDIF
    19811981           rcode = nf90_inq_varid(ncidv, 'VWND', varidv)
    1982            IF (rcode.NE.NF_NOERR) THEN
     1982           IF (rcode/=NF_NOERR) THEN
    19831983             abort_message='Nudging: error -> no VWND variable in file v.nc'
    19841984             CALL abort_gcm(modname,abort_message,1)
    19851985           ENDIF
    19861986           write(*,*)trim(modname)//' ncidv,varidv',ncidv,varidv
    1987            if (ncidpl.eq.-99) ncidpl=ncidv
     1987           if (ncidpl==-99) ncidpl=ncidv
    19881988        endif
    19891989! Temperature
    19901990         if (guide_T) then
    19911991           rcode = nf90_open('T.nc', nf90_nowrite, ncidt)
    1992            IF (rcode.NE.NF_NOERR) THEN
     1992           IF (rcode/=NF_NOERR) THEN
    19931993             abort_message='Nudging: error -> no file T.nc'
    19941994             CALL abort_gcm(modname,abort_message,1)
    19951995           ENDIF
    19961996           rcode = nf90_inq_varid(ncidt, 'AIR', varidt)
    1997            IF (rcode.NE.NF_NOERR) THEN
     1997           IF (rcode/=NF_NOERR) THEN
    19981998             abort_message='Nudging: error -> no AIR variable in file T.nc'
    19991999             CALL abort_gcm(modname,abort_message,1)
    20002000           ENDIF
    20012001           write(*,*)trim(modname)//' ncidT,varidT',ncidt,varidt
    2002            if (ncidpl.eq.-99) ncidpl=ncidt
     2002           if (ncidpl==-99) ncidpl=ncidt
    20032003         endif
    20042004! Humidite
    20052005         if (guide_Q) then
    20062006           rcode = nf90_open('hur.nc', nf90_nowrite, ncidQ)
    2007            IF (rcode.NE.NF_NOERR) THEN
     2007           IF (rcode/=NF_NOERR) THEN
    20082008             abort_message='Nudging: error -> no file hur.nc'
    20092009             CALL abort_gcm(modname,abort_message,1)
    20102010           ENDIF
    20112011           rcode = nf90_inq_varid(ncidQ, 'RH', varidQ)
    2012            IF (rcode.NE.NF_NOERR) THEN
     2012           IF (rcode/=NF_NOERR) THEN
    20132013             abort_message='Nudging: error -> no RH,variable in file hur.nc'
    20142014             CALL abort_gcm(modname,abort_message,1)
    20152015           ENDIF
    20162016           write(*,*)trim(modname)//' ncidQ,varidQ',ncidQ,varidQ
    2017            if (ncidpl.eq.-99) ncidpl=ncidQ
     2017           if (ncidpl==-99) ncidpl=ncidQ
    20182018         endif
    20192019! Pression de surface
    2020          if ((guide_P).OR.(guide_plevs.EQ.1)) then
     2020         if ((guide_P).OR.(guide_plevs==1)) then
    20212021           rcode = nf90_open('ps.nc', nf90_nowrite, ncidps)
    2022            IF (rcode.NE.NF_NOERR) THEN
     2022           IF (rcode/=NF_NOERR) THEN
    20232023             abort_message='Nudging: error -> no file ps.nc'
    20242024             CALL abort_gcm(modname,abort_message,1)
    20252025           ENDIF
    20262026           rcode = nf90_inq_varid(ncidps, 'SP', varidps)
    2027            IF (rcode.NE.NF_NOERR) THEN
     2027           IF (rcode/=NF_NOERR) THEN
    20282028             abort_message='Nudging: error -> no SP variable in file ps.nc'
    20292029             CALL abort_gcm(modname,abort_message,1)
     
    20322032         endif
    20332033! Coordonnee verticale
    2034          if (guide_plevs.EQ.0) then
     2034         if (guide_plevs==0) then
    20352035           rcode = nf90_inq_varid(ncidpl, 'LEVEL', varidpl)
    2036            IF (rcode.NE.0) rcode = nf90_inq_varid(ncidpl, 'PRESSURE', varidpl)
     2036           IF (rcode/=0) rcode = nf90_inq_varid(ncidpl, 'PRESSURE', varidpl)
    20372037           write(*,*)trim(modname)//' ncidpl,varidpl',ncidpl,varidpl
    20382038         endif
    20392039! Coefs ap, bp pour calcul de la pression aux differents niveaux
    2040          if (guide_plevs.EQ.1) then
     2040         if (guide_plevs==1) then
    20412041             status=nf_get_vara_rd(ncidpl,varidap,[1],[nlevnc],apnc)
    20422042             status=nf_get_vara_rd(ncidpl,varidbp,[1],[nlevnc],bpnc)
    2043          elseif (guide_plevs.EQ.0) THEN
     2043         elseif (guide_plevs==0) THEN
    20442044             status=nf_get_vara_rd(ncidpl,varidpl,[1],[nlevnc],apnc)
    20452045             apnc=apnc*100.! conversion en Pascals
     
    20662066     IF (invert_y) start(2)=jjp1-jje_u+1
    20672067!  Pression
    2068      if (guide_plevs.EQ.2) then
     2068     if (guide_plevs==2) then
    20692069         status=nf_get_vara_rd(ncidp,varidp,start,count,zu)
    20702070         DO i=1,iip1
     
    21402140
    21412141!  Pression de surface
    2142      if ((guide_P).OR.(guide_plevs.EQ.1))  then
     2142     if ((guide_P).OR.(guide_plevs==1))  then
    21432143         start(2)=jjb_u
    21442144         start(3)=timestep
     
    22252225   
    22262226!$OMP MASTER
    2227     IF (timestep.EQ.0) THEN
     2227    IF (timestep==0) THEN
    22282228! ----------------------------------------------
    22292229! initialisation fichier de sortie
     
    23742374    do l=1,nl
    23752375        do i=2,iim-1
    2376             if(abs(x(i,l)).gt.1.e10) then
     2376            if(abs(x(i,l))>1.e10) then
    23772377               zz=0.5*(x(i-1,l)+x(i+1,l))
    23782378              print*,'correction ',i,l,x(i,l),zz
Note: See TracChangeset for help on using the changeset viewer.