Changeset 5067


Ignore:
Timestamp:
Jul 18, 2024, 12:11:41 PM (7 weeks ago)
Author:
abarral
Message:

(lint) replace obsolete operators

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/dyn3d/guide_mod.F90

    r4470 r5067  
    123123    CALL getpar('iguide_sav',4,iguide_sav,'freq. sauvegarde guidage')
    124124    ! frequences f>0: fx/jour; f<0: tous les f jours; f=0: 1 seule fois.
    125     IF (iguide_sav.GT.0) THEN
     125    IF (iguide_sav>0) THEN
    126126       iguide_sav=day_step/iguide_sav
    127127    ELSE if (iguide_sav == 0) then
     
    143143    CALL getpar('iguide_read',4,iguide_read,'freq. lecture guidage')
    144144    CALL getpar('iguide_int',4,iguide_int,'freq. interpolation vert')
    145     IF (iguide_int.EQ.0) THEN
     145    IF (iguide_int==0) THEN
    146146        iguide_int=1
    147     ELSEIF (iguide_int.GT.0) THEN
     147    ELSEIF (iguide_int>0) THEN
    148148        iguide_int=day_step/iguide_int
    149149    ELSE
     
    171171! ---------------------------------------------
    172172    ncidpl=-99
    173     if (guide_plevs.EQ.1) then
    174        if (ncidpl.eq.-99) then
     173    if (guide_plevs==1) then
     174       if (ncidpl==-99) then
    175175          rcod=nf90_open('apbp.nc',Nf90_NOWRITe, ncidpl)
    176           if (rcod.NE.NF90_NOERR) THEN
     176          if (rcod/=NF90_NOERR) THEN
    177177             abort_message=' Nudging error -> no file apbp.nc'
    178178             CALL abort_gcm(modname,abort_message,1)
    179179          endif
    180180       endif
    181     elseif (guide_plevs.EQ.2) then
    182        if (ncidpl.EQ.-99) then
     181    elseif (guide_plevs==2) then
     182       if (ncidpl==-99) then
    183183          rcod=nf90_open('P.nc',Nf90_NOWRITe,ncidpl)
    184           if (rcod.NE.NF90_NOERR) THEN
     184          if (rcod/=NF90_NOERR) THEN
    185185             abort_message=' Nudging error -> no file P.nc'
    186186             CALL abort_gcm(modname,abort_message,1)
     
    189189
    190190    elseif (guide_u) then
    191            if (ncidpl.eq.-99) then
     191           if (ncidpl==-99) then
    192192               rcod=nf90_open('u.nc',Nf90_NOWRITe,ncidpl)
    193                if (rcod.NE.NF90_NOERR) THEN
     193               if (rcod/=NF90_NOERR) THEN
    194194                  CALL abort_gcm(modname, &
    195195                       ' Nudging error -> no file u.nc',1)
     
    198198
    199199    elseif (guide_v) then
    200            if (ncidpl.eq.-99) then
     200           if (ncidpl==-99) then
    201201               rcod=nf90_open('v.nc',nf90_nowrite,ncidpl)
    202                if (rcod.NE.NF90_NOERR) THEN
     202               if (rcod/=NF90_NOERR) THEN
    203203                  CALL abort_gcm(modname, &
    204204                       ' Nudging error -> no file v.nc',1)
     
    206206           endif
    207207    elseif (guide_T) then
    208            if (ncidpl.eq.-99) then
     208           if (ncidpl==-99) then
    209209               rcod=nf90_open('T.nc',nf90_nowrite,ncidpl)
    210                if (rcod.NE.NF90_NOERR) THEN
     210               if (rcod/=NF90_NOERR) THEN
    211211                  CALL abort_gcm(modname, &
    212212                       ' Nudging error -> no file T.nc',1)
     
    214214           endif
    215215    elseif (guide_Q) then
    216            if (ncidpl.eq.-99) then
     216           if (ncidpl==-99) then
    217217               rcod=nf90_open('hur.nc',nf90_nowrite, ncidpl)
    218                if (rcod.NE.NF90_NOERR) THEN
     218               if (rcod/=NF90_NOERR) THEN
    219219                  CALL abort_gcm(modname, &
    220220                       ' Nudging error -> no file hur.nc',1)
     
    225225    endif
    226226    error=NF_INQ_DIMID(ncidpl,'LEVEL',rid)
    227     IF (error.NE.NF90_NOERR) error=NF_INQ_DIMID(ncidpl,'PRESSURE',rid)
    228     IF (error.NE.NF90_NOERR) THEN
     227    IF (error/=NF90_NOERR) error=NF_INQ_DIMID(ncidpl,'PRESSURE',rid)
     228    IF (error/=NF90_NOERR) THEN
    229229        CALL abort_gcm(modname,'Nudging: error reading pressure levels',1)
    230230    ENDIF
     
    306306    ENDIF
    307307
    308     IF (guide_plevs.EQ.2) THEN
     308    IF (guide_plevs==2) THEN
    309309        ALLOCATE(pnat1(iip1,jjp1,nlevnc), stat = error)
    310310        IF (error /= 0) CALL abort_gcm(modname,abort_message,1)
     
    314314    ENDIF
    315315
    316     IF (guide_P.OR.guide_plevs.EQ.1) THEN
     316    IF (guide_P.OR.guide_plevs==1) THEN
    317317        ALLOCATE(psnat1(iip1,jjp1), stat = error)
    318318        IF (error /= 0) CALL abort_gcm(modname,abort_message,1)
     
    341341    IF (guide_T) tnat1=tnat2
    342342    IF (guide_Q) qnat1=qnat2
    343     IF (guide_plevs.EQ.2) pnat1=pnat2
    344     IF (guide_P.OR.guide_plevs.EQ.1) psnat1=psnat2
     343    IF (guide_plevs==2) pnat1=pnat2
     344    IF (guide_P.OR.guide_plevs==1) psnat1=psnat2
    345345
    346346  END SUBROUTINE guide_init
     
    440440! Lecture des fichiers de guidage ?
    441441!-----------------------------------------------------------------------
    442     IF (iguide_read.NE.0) THEN
     442    IF (iguide_read/=0) THEN
    443443      ditau=real(itau)
    444444      dday_step=real(day_step)
    445       IF (iguide_read.LT.0) THEN
     445      IF (iguide_read<0) THEN
    446446          tau=ditau/dday_step/REAL(iguide_read)
    447447      ELSE
     
    449449      ENDIF
    450450      reste=tau-AINT(tau)
    451       IF (reste.EQ.0.) THEN
    452           IF (itau_test.EQ.itau) THEN
     451      IF (reste==0.) THEN
     452          IF (itau_test==itau) THEN
    453453            write(lunout,*)trim(modname)//' second pass in advreel at itau=',&
    454454            itau
     
    460460              IF (guide_T) tnat1=tnat2
    461461              IF (guide_Q) qnat1=qnat2
    462               IF (guide_plevs.EQ.2) pnat1=pnat2
    463               IF (guide_P.OR.guide_plevs.EQ.1) psnat1=psnat2
     462              IF (guide_plevs==2) pnat1=pnat2
     463              IF (guide_P.OR.guide_plevs==1) psnat1=psnat2
    464464              step_rea=step_rea+1
    465465              itau_test=itau
     
    482482! Interpolation et conversion des champs de guidage
    483483!-----------------------------------------------------------------------
    484     IF (MOD(itau,iguide_int).EQ.0) THEN
     484    IF (MOD(itau,iguide_int)==0) THEN
    485485        CALL guide_interp(ps,teta)
    486486    ENDIF
    487487! Repartition entre 2 etats de guidage
    488     IF (iguide_read.NE.0) THEN
     488    IF (iguide_read/=0) THEN
    489489        tau=reste
    490490    ELSE
     
    496496!-----------------------------------------------------------------------
    497497! Sauvegarde du guidage?
    498     f_out=((MOD(itau,iguide_sav).EQ.0).AND.guide_sav) 
     498    f_out=((MOD(itau,iguide_sav)==0).AND.guide_sav)
    499499    IF (f_out) THEN
    500500      ! compute pressures at layer interfaces
     
    633633        IF (guide_reg) THEN
    634634            DO i=1,iim
    635                 IF (lond(i).LT.lon_min_g) imin(1)=i
    636                 IF (lond(i).LE.lon_max_g) imax(1)=i
     635                IF (lond(i)<lon_min_g) imin(1)=i
     636                IF (lond(i)<=lon_max_g) imax(1)=i
    637637            ENDDO
    638638            lond=rlonv*180./pi
    639639            DO i=1,iim
    640                 IF (lond(i).LT.lon_min_g) imin(2)=i
    641                 IF (lond(i).LE.lon_max_g) imax(2)=i
     640                IF (lond(i)<lon_min_g) imin(2)=i
     641                IF (lond(i)<=lon_max_g) imax(2)=i
    642642            ENDDO
    643643        ENDIF
     
    960960            do j=1,pjm
    961961                do i=1,pim
    962                     if (typ.eq.2) then
     962                    if (typ==2) then
    963963                       zlat=rlatu(j)*180./pi
    964964                       zlon=rlonu(i)*180./pi
    965                     elseif (typ.eq.1) then
     965                    elseif (typ==1) then
    966966                       zlat=rlatu(j)*180./pi
    967967                       zlon=rlonv(i)*180./pi
    968                     elseif (typ.eq.3) then
     968                    elseif (typ==3) then
    969969                       zlat=rlatv(j)*180./pi
    970970                       zlon=rlonv(i)*180./pi
     
    10051005            enddo
    10061006        enddo
    1007         IF (typ.EQ.2) THEN
     1007        IF (typ==2) THEN
    10081008            do j=1,jjp1
    10091009                do i=1,iim
     
    10131013            enddo
    10141014        ENDIF
    1015         IF (typ.EQ.3) THEN
     1015        IF (typ==3) THEN
    10161016            do j=1,jjm
    10171017                do i=1,iip1
     
    10351035            enddo
    10361036            ! Calcul de gamma
    1037             if (abs(grossismx-1.).lt.0.1.or.abs(grossismy-1.).lt.0.1) then
     1037            if (abs(grossismx-1.)<0.1.or.abs(grossismy-1.)<0.1) then
    10381038              write(*,*)trim(modname)//' ATTENTION modele peu zoome'
    10391039              write(*,*)trim(modname)//' ATTENTION on prend une constante de guidage cste'
     
    10421042              gamma=(dxdy_max-2.*dxdy_min)/(dxdy_max-dxdy_min)
    10431043              write(*,*)trim(modname)//' gamma=',gamma
    1044               if (gamma.lt.1.e-5) then
     1044              if (gamma<1.e-5) then
    10451045                write(*,*)trim(modname)//' gamma =',gamma,'<1e-5'
    10461046                abort_message='stopped'
     
    10571057        do j=1,pjm
    10581058            do i=1,pim
    1059                 if (typ.eq.1) then
     1059                if (typ==1) then
    10601060                   dxdy_=dxdys(i,j)
    10611061                   zlat=rlatu(j)*180./pi
    1062                 elseif (typ.eq.2) then
     1062                elseif (typ==2) then
    10631063                   dxdy_=dxdyu(i,j)
    10641064                   zlat=rlatu(j)*180./pi
    1065                 elseif (typ.eq.3) then
     1065                elseif (typ==3) then
    10661066                   dxdy_=dxdyv(i,j)
    10671067                   zlat=rlatv(j)*180./pi
    10681068                endif
    1069                 if (abs(grossismx-1.).lt.0.1.or.abs(grossismy-1.).lt.0.1) then
     1069                if (abs(grossismx-1.)<0.1.or.abs(grossismy-1.)<0.1) then
    10701070                ! pour une grille reguliere, xi=xxx**0=1 -> alpha=alphamin
    10711071                    alpha(i,j)=alphamin
     
    10731073                    xi=((dxdy_max-dxdy_)/(dxdy_max-dxdy_min))**gamma
    10741074                    xi=min(xi,1.)
    1075                     if(lat_min_g.le.zlat .and. zlat.le.lat_max_g) then
     1075                    if(lat_min_g<=zlat .and. zlat<=lat_max_g) then
    10761076                        alpha(i,j)=xi*alphamin+(1.-xi)*alphamax
    10771077                    else
     
    11181118         write(*,*) trim(modname)//': opening nudging files '
    11191119! Niveaux de pression si non constants
    1120          if (guide_plevs.EQ.1) then
     1120         if (guide_plevs==1) then
    11211121             write(*,*) trim(modname)//' Reading nudging on model levels'
    11221122             rcode = nf90_open('apbp.nc', nf90_nowrite, ncidpl)
    1123              IF (rcode.NE.NF90_NOERR) THEN
     1123             IF (rcode/=NF90_NOERR) THEN
    11241124              abort_message='Nudging: error -> no file apbp.nc'
    11251125              CALL abort_gcm(modname,abort_message,1)
    11261126             ENDIF
    11271127             rcode = nf90_inq_varid(ncidpl, 'AP', varidap)
    1128              IF (rcode.NE.NF90_NOERR) THEN
     1128             IF (rcode/=NF90_NOERR) THEN
    11291129              abort_message='Nudging: error -> no AP variable in file apbp.nc'
    11301130              CALL abort_gcm(modname,abort_message,1)
    11311131             ENDIF
    11321132             rcode = nf90_inq_varid(ncidpl, 'BP', varidbp)
    1133              IF (rcode.NE.NF90_NOERR) THEN
     1133             IF (rcode/=NF90_NOERR) THEN
    11341134              abort_message='Nudging: error -> no BP variable in file apbp.nc'
    11351135              CALL abort_gcm(modname,abort_message,1)
     
    11391139
    11401140! Pression si guidage sur niveaux P variables
    1141          if (guide_plevs.EQ.2) then
     1141         if (guide_plevs==2) then
    11421142             rcode = nf90_open('P.nc', nf90_nowrite, ncidp)
    1143              IF (rcode.NE.NF90_NOERR) THEN
     1143             IF (rcode/=NF90_NOERR) THEN
    11441144              abort_message='Nudging: error -> no file P.nc'
    11451145              CALL abort_gcm(modname,abort_message,1)
    11461146             ENDIF
    11471147             rcode = nf90_inq_varid(ncidp, 'PRES', varidp)
    1148              IF (rcode.NE.NF90_NOERR) THEN
     1148             IF (rcode/=NF90_NOERR) THEN
    11491149              abort_message='Nudging: error -> no PRES variable in file P.nc'
    11501150              CALL abort_gcm(modname,abort_message,1)
    11511151             ENDIF
    11521152             write(*,*) trim(modname)//' ncidp,varidp',ncidp,varidp
    1153              if (ncidpl.eq.-99) ncidpl=ncidp
     1153             if (ncidpl==-99) ncidpl=ncidp
    11541154         endif
    11551155
     
    11571157         if (guide_u) then
    11581158             rcode = nf90_open('u.nc', nf90_nowrite, ncidu)
    1159              IF (rcode.NE.NF90_NOERR) THEN
     1159             IF (rcode/=NF90_NOERR) THEN
    11601160              abort_message='Nudging: error -> no file u.nc'
    11611161              CALL abort_gcm(modname,abort_message,1)
    11621162             ENDIF
    11631163             rcode = nf90_inq_varid(ncidu, 'UWND', varidu)
    1164              IF (rcode.NE.NF90_NOERR) THEN
     1164             IF (rcode/=NF90_NOERR) THEN
    11651165              abort_message='Nudging: error -> no UWND variable in file u.nc'
    11661166              CALL abort_gcm(modname,abort_message,1)
    11671167             ENDIF
    11681168             write(*,*) trim(modname)//' ncidu,varidu',ncidu,varidu
    1169              if (ncidpl.eq.-99) ncidpl=ncidu
     1169             if (ncidpl==-99) ncidpl=ncidu
    11701170
    11711171             status=NF90_INQ_DIMID(ncidu, "LONU", dimid)
    11721172             status=NF90_INQUIRE_DIMENSION(ncidu,dimid,namedim,lendim)
    1173              IF (lendim .NE. iip1) THEN
     1173             IF (lendim /= iip1) THEN
    11741174                abort_message='dimension LONU different from iip1 in u.nc'
    11751175                CALL abort_gcm(modname,abort_message,1)
     
    11781178             status=NF90_INQ_DIMID(ncidu, "LATU", dimid)
    11791179             status=NF90_INQUIRE_DIMENSION(ncidu,dimid,namedim,lendim)
    1180              IF (lendim .NE. jjp1) THEN
     1180             IF (lendim /= jjp1) THEN
    11811181                abort_message='dimension LATU different from jjp1 in u.nc'
    11821182                CALL abort_gcm(modname,abort_message,1)
     
    11881188         if (guide_v) then
    11891189             rcode = nf90_open('v.nc', nf90_nowrite, ncidv)
    1190              IF (rcode.NE.NF90_NOERR) THEN
     1190             IF (rcode/=NF90_NOERR) THEN
    11911191              abort_message='Nudging: error -> no file v.nc'
    11921192              CALL abort_gcm(modname,abort_message,1)
    11931193             ENDIF
    11941194             rcode = nf90_inq_varid(ncidv, 'VWND', varidv)
    1195              IF (rcode.NE.NF90_NOERR) THEN
     1195             IF (rcode/=NF90_NOERR) THEN
    11961196              abort_message='Nudging: error -> no VWND variable in file v.nc'
    11971197              CALL abort_gcm(modname,abort_message,1)
    11981198             ENDIF
    11991199             write(*,*) trim(modname)//' ncidv,varidv',ncidv,varidv
    1200              if (ncidpl.eq.-99) ncidpl=ncidv
     1200             if (ncidpl==-99) ncidpl=ncidv
    12011201             
    12021202             status=NF90_INQ_DIMID(ncidv, "LONV", dimid)
    12031203             status=NF90_INQUIRE_DIMENSION(ncidv,dimid,namedim,lendim)
    12041204             
    1205                 IF (lendim .NE. iip1) THEN
     1205                IF (lendim /= iip1) THEN
    12061206                abort_message='dimension LONV different from iip1 in v.nc'
    12071207                CALL abort_gcm(modname,abort_message,1)
     
    12111211             status=NF90_INQ_DIMID(ncidv, "LATV", dimid)
    12121212             status=NF90_INQUIRE_DIMENSION(ncidv,dimid,namedim,lendim)
    1213              IF (lendim .NE. jjm) THEN
     1213             IF (lendim /= jjm) THEN
    12141214                abort_message='dimension LATV different from jjm in v.nc'
    12151215                CALL abort_gcm(modname,abort_message,1)
     
    12211221         if (guide_T) then
    12221222             rcode = nf90_open('T.nc', nf90_nowrite, ncidt)
    1223              IF (rcode.NE.NF90_NOERR) THEN
     1223             IF (rcode/=NF90_NOERR) THEN
    12241224              abort_message='Nudging: error -> no file T.nc'
    12251225              CALL abort_gcm(modname,abort_message,1)
    12261226             ENDIF
    12271227             rcode = nf90_inq_varid(ncidt, 'AIR', varidt)
    1228              IF (rcode.NE.NF90_NOERR) THEN
     1228             IF (rcode/=NF90_NOERR) THEN
    12291229              abort_message='Nudging: error -> no AIR variable in file T.nc'
    12301230              CALL abort_gcm(modname,abort_message,1)
    12311231             ENDIF
    12321232             write(*,*) trim(modname)//' ncidT,varidT',ncidt,varidt
    1233              if (ncidpl.eq.-99) ncidpl=ncidt
     1233             if (ncidpl==-99) ncidpl=ncidt
    12341234
    12351235             status=NF90_INQ_DIMID(ncidt, "LONV", dimid)
    12361236             status=NF90_INQUIRE_DIMENSION(ncidt,dimid,namedim,lendim)
    1237              IF (lendim .NE. iip1) THEN
     1237             IF (lendim /= iip1) THEN
    12381238                abort_message='dimension LONV different from iip1 in T.nc'
    12391239                CALL abort_gcm(modname,abort_message,1)
     
    12421242             status=NF90_INQ_DIMID(ncidt, "LATU", dimid)
    12431243             status=NF90_INQUIRE_DIMENSION(ncidt,dimid,namedim,lendim)
    1244              IF (lendim .NE. jjp1) THEN
     1244             IF (lendim /= jjp1) THEN
    12451245                abort_message='dimension LATU different from jjp1 in T.nc'
    12461246                CALL abort_gcm(modname,abort_message,1)
     
    12521252         if (guide_Q) then
    12531253             rcode = nf90_open('hur.nc', nf90_nowrite, ncidQ)
    1254              IF (rcode.NE.NF90_NOERR) THEN
     1254             IF (rcode/=NF90_NOERR) THEN
    12551255              abort_message='Nudging: error -> no file hur.nc'
    12561256              CALL abort_gcm(modname,abort_message,1)
    12571257             ENDIF
    12581258             rcode = nf90_inq_varid(ncidQ, 'RH', varidQ)
    1259              IF (rcode.NE.NF90_NOERR) THEN
     1259             IF (rcode/=NF90_NOERR) THEN
    12601260              abort_message='Nudging: error -> no RH variable in file hur.nc'
    12611261              CALL abort_gcm(modname,abort_message,1)
    12621262             ENDIF
    12631263             write(*,*) trim(modname)//' ncidQ,varidQ',ncidQ,varidQ
    1264              if (ncidpl.eq.-99) ncidpl=ncidQ
     1264             if (ncidpl==-99) ncidpl=ncidQ
    12651265
    12661266             status=NF90_INQ_DIMID(ncidQ, "LONV", dimid)
    12671267             status=NF90_INQUIRE_DIMENSION(ncidQ,dimid,namedim,lendim)
    1268              IF (lendim .NE. iip1) THEN
     1268             IF (lendim /= iip1) THEN
    12691269                abort_message='dimension LONV different from iip1 in hur.nc'
    12701270                CALL abort_gcm(modname,abort_message,1)
     
    12731273             status=NF90_INQ_DIMID(ncidQ, "LATU", dimid)
    12741274             status=NF90_INQUIRE_DIMENSION(ncidQ,dimid,namedim,lendim)
    1275              IF (lendim .NE. jjp1) THEN
     1275             IF (lendim /= jjp1) THEN
    12761276                abort_message='dimension LATU different from jjp1 in hur.nc'
    12771277                CALL abort_gcm(modname,abort_message,1)
     
    12831283         if ((guide_P).OR.(guide_modele)) then
    12841284             rcode = nf90_open('ps.nc', nf90_nowrite, ncidps)
    1285              IF (rcode.NE.NF90_NOERR) THEN
     1285             IF (rcode/=NF90_NOERR) THEN
    12861286              abort_message='Nudging: error -> no file ps.nc'
    12871287              CALL abort_gcm(modname,abort_message,1)
    12881288             ENDIF
    12891289             rcode = nf90_inq_varid(ncidps, 'SP', varidps)
    1290              IF (rcode.NE.NF90_NOERR) THEN
     1290             IF (rcode/=NF90_NOERR) THEN
    12911291              abort_message='Nudging: error -> no SP variable in file ps.nc'
    12921292              CALL abort_gcm(modname,abort_message,1)
     
    12951295         endif
    12961296! Coordonnee verticale
    1297          if (guide_plevs.EQ.0) then
     1297         if (guide_plevs==0) then
    12981298              rcode = nf90_inq_varid(ncidpl, 'LEVEL', varidpl)
    1299               IF (rcode.NE.0) rcode = nf90_inq_varid(ncidpl, 'PRESSURE', varidpl)
     1299              IF (rcode/=0) rcode = nf90_inq_varid(ncidpl, 'PRESSURE', varidpl)
    13001300              write(*,*) trim(modname)//' ncidpl,varidpl',ncidpl,varidpl
    13011301         endif
    13021302! Coefs ap, bp pour calcul de la pression aux differents niveaux
    1303          if (guide_plevs.EQ.1) then
     1303         if (guide_plevs==1) then
    13041304             status=NF90_GET_VAR(ncidpl,varidap,apnc,[1],[nlevnc])
    13051305             status=NF90_GET_VAR(ncidpl,varidbp,bpnc,[1],[nlevnc])
    1306          ELSEIF (guide_plevs.EQ.0) THEN
     1306         ELSEIF (guide_plevs==0) THEN
    13071307             status=NF90_GET_VAR(ncidpl,varidpl,apnc,[1],[nlevnc])
    13081308!FC Pour les corrections la pression est deja en Pascals on commente la ligne ci-dessous
     
    13291329
    13301330! Pression
    1331      if (guide_plevs.EQ.2) then
     1331     if (guide_plevs==2) then
    13321332         status=NF90_GET_VAR(ncidp,varidp,pnat2,start,count)
    13331333         IF (invert_y) THEN
     
    14211421         write(*,*)trim(modname)//' : opening nudging files '
    14221422! Ap et Bp si niveaux de pression hybrides
    1423          if (guide_plevs.EQ.1) then
     1423         if (guide_plevs==1) then
    14241424           write(*,*)trim(modname)//' Reading nudging on model levels'
    14251425           rcode = nf90_open('apbp.nc', nf90_nowrite, ncidpl)
    1426            IF (rcode.NE.NF90_NOERR) THEN
     1426           IF (rcode/=NF90_NOERR) THEN
    14271427             abort_message='Nudging: error -> no file apbp.nc'
    14281428           CALL abort_gcm(modname,abort_message,1)
    14291429           ENDIF
    14301430           rcode = nf90_inq_varid(ncidpl, 'AP', varidap)
    1431            IF (rcode.NE.NF90_NOERR) THEN
     1431           IF (rcode/=NF90_NOERR) THEN
    14321432             abort_message='Nudging: error -> no AP variable in file apbp.nc'
    14331433           CALL abort_gcm(modname,abort_message,1)
    14341434           ENDIF
    14351435           rcode = nf90_inq_varid(ncidpl, 'BP', varidbp)
    1436            IF (rcode.NE.NF90_NOERR) THEN
     1436           IF (rcode/=NF90_NOERR) THEN
    14371437             abort_message='Nudging: error -> no BP variable in file apbp.nc'
    14381438             CALL abort_gcm(modname,abort_message,1)
     
    14411441         endif
    14421442! Pression
    1443          if (guide_plevs.EQ.2) then
     1443         if (guide_plevs==2) then
    14441444           rcode = nf90_open('P.nc', nf90_nowrite, ncidp)
    1445            IF (rcode.NE.NF90_NOERR) THEN
     1445           IF (rcode/=NF90_NOERR) THEN
    14461446             abort_message='Nudging: error -> no file P.nc'
    14471447             CALL abort_gcm(modname,abort_message,1)
    14481448           ENDIF
    14491449           rcode = nf90_inq_varid(ncidp, 'PRES', varidp)
    1450            IF (rcode.NE.NF90_NOERR) THEN
     1450           IF (rcode/=NF90_NOERR) THEN
    14511451             abort_message='Nudging: error -> no PRES variable in file P.nc'
    14521452             CALL abort_gcm(modname,abort_message,1)
    14531453           ENDIF
    14541454           write(*,*)trim(modname)//' ncidp,varidp',ncidp,varidp
    1455            if (ncidpl.eq.-99) ncidpl=ncidp
     1455           if (ncidpl==-99) ncidpl=ncidp
    14561456         endif
    14571457! Vent zonal
    14581458         if (guide_u) then
    14591459           rcode = nf90_open('u.nc', nf90_nowrite, ncidu)
    1460            IF (rcode.NE.NF90_NOERR) THEN
     1460           IF (rcode/=NF90_NOERR) THEN
    14611461             abort_message='Nudging: error -> no file u.nc'
    14621462             CALL abort_gcm(modname,abort_message,1)
    14631463           ENDIF
    14641464           rcode = nf90_inq_varid(ncidu, 'UWND', varidu)
    1465            IF (rcode.NE.NF90_NOERR) THEN
     1465           IF (rcode/=NF90_NOERR) THEN
    14661466             abort_message='Nudging: error -> no UWND variable in file u.nc'
    14671467             CALL abort_gcm(modname,abort_message,1)
    14681468           ENDIF
    14691469           write(*,*)trim(modname)//' ncidu,varidu',ncidu,varidu
    1470            if (ncidpl.eq.-99) ncidpl=ncidu
     1470           if (ncidpl==-99) ncidpl=ncidu
    14711471         endif
    14721472! Vent meridien
    14731473         if (guide_v) then
    14741474           rcode = nf90_open('v.nc', nf90_nowrite, ncidv)
    1475            IF (rcode.NE.NF90_NOERR) THEN
     1475           IF (rcode/=NF90_NOERR) THEN
    14761476             abort_message='Nudging: error -> no file v.nc'
    14771477             CALL abort_gcm(modname,abort_message,1)
    14781478           ENDIF
    14791479           rcode = nf90_inq_varid(ncidv, 'VWND', varidv)
    1480            IF (rcode.NE.NF90_NOERR) THEN
     1480           IF (rcode/=NF90_NOERR) THEN
    14811481             abort_message='Nudging: error -> no VWND variable in file v.nc'
    14821482             CALL abort_gcm(modname,abort_message,1)
    14831483           ENDIF
    14841484           write(*,*)trim(modname)//' ncidv,varidv',ncidv,varidv
    1485            if (ncidpl.eq.-99) ncidpl=ncidv
     1485           if (ncidpl==-99) ncidpl=ncidv
    14861486         endif
    14871487! Temperature
    14881488         if (guide_T) then
    14891489           rcode = nf90_open('T.nc', nf90_nowrite, ncidt)
    1490            IF (rcode.NE.NF90_NOERR) THEN
     1490           IF (rcode/=NF90_NOERR) THEN
    14911491             abort_message='Nudging: error -> no file T.nc'
    14921492             CALL abort_gcm(modname,abort_message,1)
    14931493           ENDIF
    14941494           rcode = nf90_inq_varid(ncidt, 'AIR', varidt)
    1495            IF (rcode.NE.NF90_NOERR) THEN
     1495           IF (rcode/=NF90_NOERR) THEN
    14961496             abort_message='Nudging: error -> no AIR variable in file T.nc'
    14971497             CALL abort_gcm(modname,abort_message,1)
    14981498           ENDIF
    14991499           write(*,*)trim(modname)//' ncidT,varidT',ncidt,varidt
    1500            if (ncidpl.eq.-99) ncidpl=ncidt
     1500           if (ncidpl==-99) ncidpl=ncidt
    15011501         endif
    15021502! Humidite
    15031503         if (guide_Q) then
    15041504           rcode = nf90_open('hur.nc', nf90_nowrite, ncidQ)
    1505            IF (rcode.NE.NF90_NOERR) THEN
     1505           IF (rcode/=NF90_NOERR) THEN
    15061506             abort_message='Nudging: error -> no file hur.nc'
    15071507             CALL abort_gcm(modname,abort_message,1)
    15081508           ENDIF
    15091509           rcode = nf90_inq_varid(ncidQ, 'RH', varidQ)
    1510            IF (rcode.NE.NF90_NOERR) THEN
     1510           IF (rcode/=NF90_NOERR) THEN
    15111511             abort_message='Nudging: error -> no RH,variable in file hur.nc'
    15121512             CALL abort_gcm(modname,abort_message,1)
    15131513           ENDIF
    15141514           write(*,*)trim(modname)//' ncidQ,varidQ',ncidQ,varidQ
    1515            if (ncidpl.eq.-99) ncidpl=ncidQ
     1515           if (ncidpl==-99) ncidpl=ncidQ
    15161516         endif
    15171517! Pression de surface
    15181518         if ((guide_P).OR.(guide_modele)) then
    15191519           rcode = nf90_open('ps.nc', nf90_nowrite, ncidps)
    1520            IF (rcode.NE.NF90_NOERR) THEN
     1520           IF (rcode/=NF90_NOERR) THEN
    15211521             abort_message='Nudging: error -> no file ps.nc'
    15221522             CALL abort_gcm(modname,abort_message,1)
    15231523           ENDIF
    15241524           rcode = nf90_inq_varid(ncidps, 'SP', varidps)
    1525            IF (rcode.NE.NF90_NOERR) THEN
     1525           IF (rcode/=NF90_NOERR) THEN
    15261526             abort_message='Nudging: error -> no SP variable in file ps.nc'
    15271527             CALL abort_gcm(modname,abort_message,1)
     
    15301530         endif
    15311531! Coordonnee verticale
    1532          if (guide_plevs.EQ.0) then
     1532         if (guide_plevs==0) then
    15331533           rcode = nf90_inq_varid(ncidpl, 'LEVEL', varidpl)
    1534            IF (rcode.NE.0) rcode = nf90_inq_varid(ncidpl, 'PRESSURE', varidpl)
     1534           IF (rcode/=0) rcode = nf90_inq_varid(ncidpl, 'PRESSURE', varidpl)
    15351535           write(*,*)trim(modname)//' ncidpl,varidpl',ncidpl,varidpl
    15361536         endif
    15371537! Coefs ap, bp pour calcul de la pression aux differents niveaux
    1538          if (guide_plevs.EQ.1) then
     1538         if (guide_plevs==1) then
    15391539             status=NF90_GET_VAR(ncidpl,varidap,apnc,[1],[nlevnc])
    15401540             status=NF90_GET_VAR(ncidpl,varidbp,bpnc,[1],[nlevnc])
    1541          elseif (guide_plevs.EQ.0) THEN
     1541         elseif (guide_plevs==0) THEN
    15421542             status=NF90_GET_VAR(ncidpl,varidpl,apnc,[1],[nlevnc])
    15431543             apnc=apnc*100.! conversion en Pascals
     
    15631563
    15641564!  Pression
    1565      if (guide_plevs.EQ.2) then
     1565     if (guide_plevs==2) then
    15661566         status=NF90_GET_VAR(ncidp,varidp,zu,start,count)
    15671567         DO i=1,iip1
     
    16291629
    16301630!  Pression de surface
    1631      if ((guide_P).OR.(guide_plevs.EQ.1))  then
     1631     if ((guide_P).OR.(guide_plevs==1))  then
    16321632         start(3)=timestep
    16331633         start(4)=0
     
    16811681
    16821682    write(*,*)trim(modname)//': output timestep',timestep,'var ',varname
    1683     IF (timestep.EQ.0) THEN
     1683    IF (timestep==0) THEN
    16841684! ----------------------------------------------
    16851685! initialisation fichier de sortie
     
    18281828    do l=1,nl
    18291829        do i=2,iim-1
    1830             if(abs(x(i,l)).gt.1.e10) then
     1830            if(abs(x(i,l))>1.e10) then
    18311831               zz=0.5*(x(i-1,l)+x(i+1,l))
    18321832              print*,'correction ',i,l,x(i,l),zz
Note: See TracChangeset for help on using the changeset viewer.