Ignore:
Timestamp:
Aug 13, 2025, 7:53:49 PM (4 months ago)
Author:
gmilcareck
Message:

Remove all "call abort" and "stop" statement in LMDZ.GENERIC and replacing them by call abort_physic().

Location:
trunk/LMDZ.GENERIC/libf/dynphy_lonlat/phystd
Files:
8 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.GENERIC/libf/dynphy_lonlat/phystd/datareadnc.F

    r3713 r3893  
    127127        write(*,*)' http://www.lmd.jussieu.fr/~lmdz/planets/'//
    128128     &             'generic/datagcm/'
    129         STOP
     129        call abort_physic("datareadnc",
     130     &      "cannot open file surface file",1)
    130131      ENDIF
    131132
  • trunk/LMDZ.GENERIC/libf/dynphy_lonlat/phystd/defrun_new.F

    r2354 r3893  
    249249           
    250250           IF( ABS(clon - clonn).GE. 0.001 )  THEN
    251              PRINT *,' La valeur de clon passee par run.def est '
    252      *       ,'differente de celle lue sur le fichier start '
    253              STOP
     251             call abort_physic("defrun_new",
     252     &        "Value mismatch of clon in run.def and start file",1)
    254253           ENDIF
    255254c
     
    259258 
    260259           IF( ABS(clat - clatt).GE. 0.001 )  THEN
    261              PRINT *,' La valeur de clat passee par run.def est '
    262      *       ,'differente de celle lue sur le fichier start '
    263              STOP
     260             call abort_physic("defrun_new",
     261     &        "Value mismatch of clat in run.def and start file",1)
    264262           ENDIF
    265263
     
    275273             write(*,*)'place de alphax, alphay. cf. dyn3d). '
    276274             write(*,*)
    277              stop
     275             call abort_physic("defrun_new",
     276     &            "ERREUR : dans run.def, grossismx =0",1)
    278277           end if
    279278
    280279           IF( ABS(grossismx - grossismxx).GE. 0.001 )  THEN
    281280             PRINT *,' La valeur de grossismx passee par run.def est '
    282      *       ,'differente de celle lue sur le fichier  start =',
     281     *       ,'differente de celle lue sur le fichier start =',
    283282     *        grossismx
    284283             if (grossismx.eq.0) then
     
    287286                 grossismx=grossismxx
    288287             else
    289                    STOP
     288              call abort_physic("defrun_new",
     289     &        "Value mismatch of grossismx in run.def and start file",1)
    290290             endif
    291291           ENDIF
     
    303303                 grossismy=grossismyy
    304304             else
    305                    STOP
     305              call abort_physic("defrun_new",
     306     &        "Value mismatch of grossismy in run.def and start file",1)
    306307             endif
    307308           ENDIF
     
    309310
    310311           IF( grossismx.LT.1. )  THEN
    311              PRINT *,' ***  ATTENTION !! grossismx < 1 .   *** '
    312              STOP
     312             call abort_physic("defrun_new",
     313     &            "ATTENTION !! grossismx < 1",1)
    313314           ELSE
    314315             alphax = 1. - 1./ grossismx
     
    316317
    317318           IF( grossismy.LT.1. )  THEN
    318              PRINT *,' ***  ATTENTION !! grossismy < 1 .   *** '
    319              STOP
     319             call abort_physic("defrun_new",
     320     &            "ATTENTION !! grossismy < 1",1)
    320321           ELSE
    321322             alphay = 1. - 1./ grossismy
     
    334335                PRINT *,' *** fxyhypb lu sur le fichier start est F ',
    335336     *          'alors  qu il est  T  sur  run.def  ***'
    336                 STOP
     337                call abort_physic("defrun_new",
     338     &               "fxyhypb=F dans start alors que =T dans run.def",1)
    337339             ENDIF
    338340           ELSE
     
    341343                PRINT *,' ***  fxyhypb lu sur le fichier start est T ',
    342344     *         'alors  qu il est  F  sur  run.def  ****  '
    343                 STOP
     345                call abort_physic("defrun_new",
     346     &               "fxyhypb=T dans start alors que =F dans run.def",1)
    344347             ENDIF
    345348           ENDIF
     
    348351
    349352           IF( fxyhypb )  THEN
    350               IF( ABS(dzoomx - dzoomxx).GE. 0.001 )  THEN
    351                 PRINT *,' La valeur de dzoomx passee par run.def est '
    352      *          ,'differente de celle lue sur le fichier  start '
    353                 STOP
    354               ENDIF
     353            IF( ABS(dzoomx - dzoomxx).GE. 0.001 )  THEN
     354             call abort_physic("defrun_new",
     355     &       "Value mismatch of dzoomx between run.def and startfile",1)
     356            ENDIF
    355357           ENDIF
    356358
     
    359361
    360362           IF( fxyhypb )  THEN
    361               IF( ABS(dzoomy - dzoomyy).GE. 0.001 )  THEN
    362                 PRINT *,' La valeur de dzoomy passee par run.def est '
    363      *          ,'differente de celle lue sur le fichier  start '
    364                 STOP
    365               ENDIF
     363            IF( ABS(dzoomy - dzoomyy).GE. 0.001 )  THEN
     364             call abort_physic("defrun_new",
     365     &       "Value mismatch of dzoomy between run.def and startfile",1)
     366            ENDIF
    366367           ENDIF
    367368
     
    374375           IF( fxyhypb )  THEN
    375376              IF( ABS(taux - tauxx).GE. 0.001 )  THEN
    376                 WRITE(6,*)' La valeur de taux passee par run.def est',
     377               WRITE(6,*)' La valeur de taux passee par run.def est',
    377378     *             'differente de celle lue sur le fichier  start '
    378                 CALL ABORT
     379               call abort_physic("defrun_new",
     380     &         "Value mismatch of taux between run.def and startfile",1)
    379381              ENDIF
    380382
    381383              IF( ABS(tauy - tauyy).GE. 0.001 )  THEN
    382                 WRITE(6,*)' La valeur de tauy passee par run.def est',
     384               WRITE(6,*)' La valeur de tauy passee par run.def est',
    383385     *          'differente de celle lue sur le fichier  start '
    384                 CALL ABORT
     386               call abort_physic("defrun_new",
     387     &         "Value mismatch of tauy between run.def and startfile",1)
    385388              ENDIF
    386389           ENDIF
     
    416419
    417420           IF( grossismx.LT.1. )  THEN
    418             PRINT *,' ***  ATTENTION !! grossismx < 1 .   *** '
    419             STOP
     421            call abort_physic("defrun_new",
     422     &           "ATTENTION !! grossismx < 1",1)
    420423           ELSE
    421424             alphax = 1. - 1./ grossismx
     
    423426
    424427           IF( grossismy.LT.1. )  THEN
    425              PRINT *,' ***  ATTENTION !! grossismy < 1 .   *** '
    426              STOP
     428             call abort_physic("defrun_new",
     429     &            "ATTENTION !! grossismy < 1",1)
    427430           ELSE
    428431             alphay = 1. - 1./ grossismy
     
    513516      ELSE
    514517        write(tapeerr,*) ' WHERE IS run.def ? WE NEED IT !!!!!!!!!!!!!!'
    515         stop
     518        call abort_physic("defrun_new","Unable to find run.def",1)
    516519      ENDIF ! of IF(ierr.eq.0)
    517520
     
    525528      else     
    526529c        Avec Zoom
    527          if (.not.fxyhypb) stop 'With zoom, fxyhypb should be set to T
    528      &in run.def for this version... -> STOP ! '     
     530         if (.not.fxyhypb) call abort_physic("defrun_new",
     531     &   "With zoom, fxyhypb should be T in run.def for this version",1)
    529532      end if
    530533#else
    531       write(*,*) "defrun_new should not be used in parallel mode!"
    532       stop
     534      call abort_physic("defrun_new",
     535     &    "defrun_new should not be used in parallel mode",1)   
    533536#endif
    534537! of #ifndef CPP_PARA
  • trunk/LMDZ.GENERIC/libf/dynphy_lonlat/phystd/grid_noro1.F

    r1422 r3893  
    109109      IF (imar.GT.2200 .OR. jmar.GT.1100) THEN
    110110         PRINT*, 'imar ou jmar trop grand', imar, jmar
    111          CALL ABORT
     111         CALL abort_physic("grid_noro1.F","imar ou jmar trop grand",1)
    112112      ENDIF
    113113
    114114      IF(imdep.ne.iusn.or.jmdep.ne.jusn)then
    115115         print *,' imdep ou jmdep mal dimensionnes:',imdep,jmdep
    116          call abort
     116         call abort_physic("grid_noro1.F",
     117     &        "imdep ou jmdep mal dimensionnes",1)
    117118      ENDIF
    118119
    119120      IF(imar+1.gt.iim+1.or.jmar.gt.jjm+1)THEN
    120121        print *,' imar ou jmar mal dimensionnes:',imar,jmar
    121         call abort
     122        call abort_physic("grid_noro1.F",
     123     &       "imar ou jmar mal dimensionnes",1)
    122124      ENDIF
    123125c
  • trunk/LMDZ.GENERIC/libf/dynphy_lonlat/phystd/inichim_newstart.F90

    r3073 r3893  
    9494                write(*,*) "calchim: error reading line of tracers"
    9595                write(*,*) "   (first lines of traceur.def) "
    96                 stop
     96                call abort_physic("traceur.def","error reading line of tracers",1)
    9797             ENDIF
    9898           ENDDO
    9999        ENDIF ! if modern or standard traceur.def
    100100      else
    101          write(*,*) "calchim: error opening traceur.def in inichim_newstart"
    102          stop
     101         call abort_physic("inichim_newstart","Unable to open traceur.def",1)
    103102      endif
    104103
     
    165164            else
    166165               write(*,*) 'inichim_newstart: error opening ', fil
    167                stop
     166               call abort_physic("inichim_newstart", "Unable to open chemimal profile file",1)
    168167            endif
    169168            close(90)
     
    181180                     pqx(ilon,ilat,ilay,iq) = 1-sum(pqx(ilon,ilat,ilay,:))
    182181                     if (pqx(ilon,ilat,ilay,iq)<=0.) then
    183                         write(*,*) 'inichim_newstart: vmr tot > 1 not possible'
    184                         stop
     182                        call abort_physic("inichim_newstart","vmr tot > 1 not possible",1)
    185183                     end if
    186184                  end do
     
    192190      end do
    193191      if (.not.foundback) then
    194          write(*,*) 'inichim_newstart: you need to set a background gas'
    195          write(*,*) '            by qx=1. in traceur.def'
    196          stop
     192         call abort_physic("inichim_newstart","you need to set a background gas by qx=1. in traceur.def",1)
    197193      end if
    198194
  • trunk/LMDZ.GENERIC/libf/dynphy_lonlat/phystd/lect_start_archive.F

    r3423 r3893  
    319319      ierr = NF_INQ_VARID (nid, "controle", nvarid)
    320320      IF (ierr .NE. NF_NOERR) THEN
    321          PRINT*, "Lect_start_archive: champ <controle> not found"
    322          CALL abort
     321         CALL abort_physic("lect_start_archive",
     322     &        "Field <controle> not found",1)
    323323      ENDIF
    324324#ifdef NC_DOUBLE
     
    328328#endif
    329329      IF (ierr .NE. NF_NOERR) THEN
    330          PRINT*, "lect_start_archive: Lecture echoue pour <controle>"
    331          CALL abort
     330         CALL abort_physic("lect_start_archive",
     331     &        "Lecture echoue pour <controle>",1)
    332332      ENDIF
    333333c
     
    340340      ierr = NF_INQ_VARID (nid, "rlonv", nvarid)
    341341      IF (ierr .NE. NF_NOERR) THEN
    342          PRINT*, "lect_start_archive: Field <rlonv> not found"
    343          CALL abort
     342         CALL abort_physic("lect_start_archive",
     343     &        "Field <rlonv> not found",1)
    344344      ENDIF
    345345#ifdef NC_DOUBLE
     
    349349#endif
    350350      IF (ierr .NE. NF_NOERR) THEN
    351          PRINT*, "lect_start_archive: Failed loading <rlonv>"
    352          CALL abort
     351         CALL abort_physic("lect_start_archive",
     352     &        "Failed loading <rlonv>",1)
    353353      ENDIF
    354354c
    355355      ierr = NF_INQ_VARID (nid, "rlatu", nvarid)
    356356      IF (ierr .NE. NF_NOERR) THEN
    357          PRINT*, "lect_start_archive: Field <rlatu> not found"
    358          CALL abort
     357         CALL abort_physic("lect_start_archive",
     358     &        "Field <rlatu> not found",1)
    359359      ENDIF
    360360#ifdef NC_DOUBLE
     
    364364#endif
    365365      IF (ierr .NE. NF_NOERR) THEN
    366          PRINT*, "lect_start_archive: Failed loading <rlatu>"
    367          CALL abort
     366         CALL abort_physic("lect_start_archive",
     367     &        "Failed loading <rlatu>",1)
    368368      ENDIF
    369369c
    370370      ierr = NF_INQ_VARID (nid, "rlonu", nvarid)
    371371      IF (ierr .NE. NF_NOERR) THEN
    372          PRINT*, "lect_start_archive: Field <rlonu> not found"
    373          CALL abort
     372         CALL abort_physic("lect_start_archive",
     373     &        "Field <rlonu> not found",1)
    374374      ENDIF
    375375#ifdef NC_DOUBLE
     
    379379#endif
    380380      IF (ierr .NE. NF_NOERR) THEN
    381          PRINT*, "lect_start_archive: Failed loading <rlonu>"
    382          CALL abort
     381         CALL abort_physic("lect_start_archive",
     382     &        "Failed loading <rlonu>",1)
    383383      ENDIF
    384384c
    385385      ierr = NF_INQ_VARID (nid, "rlatv", nvarid)
    386386      IF (ierr .NE. NF_NOERR) THEN
    387          PRINT*, "lect_start_archive: Field <rlatv> not found"
    388          CALL abort
     387         CALL abort_physic("lect_start_archive",
     388     &        "Field <rlatv> not found",1)
    389389      ENDIF
    390390#ifdef NC_DOUBLE
     
    394394#endif
    395395      IF (ierr .NE. NF_NOERR) THEN
    396          PRINT*, "lect_start_archive: Failed loading <rlatv>"
    397          CALL abort
     396         CALL abort_physic("lect_start_archive",
     397     &        "Failed loading <rlatv>",1)
    398398      ENDIF
    399399c
     
    426426         IF (ierr .NE. NF_NOERR) THEN
    427427            PRINT*, "Nothing to do..."
    428             CALL abort
     428            CALL abort_physic("lect_start_archive",
     429     &           "Field <bps> or <sig_s> not found",1)
    429430         ENDIF
    430431      ENDIF
     
    435436#endif
    436437      IF (ierr .NE. NF_NOERR) THEN
    437          PRINT*, "lect_start_archive: Failed loading <bps>"
    438          CALL abort
     438         CALL abort_physic("lect_start_archive",
     439     &        "Failed loading <bps>",1)
    439440      END IF
    440441
     
    460461#endif
    461462       if (ierr .NE. NF_NOERR) then
    462          PRINT*, "lect_start_archive: Failed reading <soildepth>"
    463          CALL abort
     463         CALL abort_physic("lect_start_archive",
     464     &        "Failed reading <soildepth>",1)
    464465       endif
    465466
     
    488489#endif
    489490       if (ierr .NE. NF_NOERR) then
    490          PRINT*, "lect_start_archive: Failed reading <soildepth>"
    491          CALL abort
     491         CALL abort_physic("lect_start_archive",
     492     &        "Failed reading <soildepth>",1)
    492493       endif
    493494      endif ! of if (depthinterpol)
     
    513514#endif
    514515       if (ierr .NE. NF_NOERR) then
    515          PRINT*, "lect_start_archive: Failed reading <inertiedat>"
    516          CALL abort
     516         CALL abort_physic("lect_start_archive",
     517     &        "Failed reading <inertiedat>",1)
    517518       endif
    518519      endif
     
    524525      ierr = NF_INQ_VARID (nid, "phisinit", nvarid)
    525526      IF (ierr .NE. NF_NOERR) THEN
    526          PRINT*, "lect_start_archive: Field <phisinit> not found"
    527          CALL abort
     527         CALL abort_physic("lect_start_archive",
     528     &        "Field <phisinit> not found",1)
    528529      ENDIF
    529530#ifdef NC_DOUBLE
     
    533534#endif
    534535      IF (ierr .NE. NF_NOERR) THEN
    535          PRINT*, "lect_start_archive: Failed loading <phisinit>"
    536          CALL abort
     536         CALL abort_physic("lect_start_archive",
     537     &        "Failed loading <phisinit>",1)
    537538      ENDIF
    538539
     
    553554         ierr = NF_INQ_DIMID (nid, "temps", nvarid)
    554555         IF (ierr .NE. NF_NOERR) THEN
    555             PRINT*, "lect_start_archive: Field <Time> not found"
    556             CALL abort
     556            CALL abort_physic("lect_start_archive",
     557     &           "Field <Time> not found",1)
    557558         endif
    558559      ENDIF
     
    568569#endif
    569570      IF (ierr .NE. NF_NOERR) THEN
    570          PRINT*, "lect_start_archive: Failed loading <Time>"
    571          CALL abort
     571         CALL abort_physic("lect_start_archive",
     572     &        "Failed loading <Time>",1)
    572573      ENDIF
    573574c
     
    626627      ierr = NF_INQ_VARID (nid, "emis", nvarid)
    627628      IF (ierr .NE. NF_NOERR) THEN
    628          PRINT*, "lect_start_archive: Field <emis> not found"
    629          CALL abort
     629         CALL abort_physic("lect_start_archive",
     630     &        "Field <emis> not found",1)
    630631      ENDIF
    631632#ifdef NC_DOUBLE
     
    635636#endif
    636637      IF (ierr .NE. NF_NOERR) THEN
    637          PRINT*, "lect_start_archive: Failed loading <emis>"
    638          CALL abort
     638         CALL abort_physic("lect_start_archive",
     639     &        "Failed loading <emis>",1)
    639640      ENDIF
    640641c
    641642      ierr = NF_INQ_VARID (nid, "ps", nvarid)
    642643      IF (ierr .NE. NF_NOERR) THEN
    643          PRINT*, "lect_start_archive: Field <ps> not found"
    644          CALL abort
     644         CALL abort_physic("lect_start_archive",
     645     &        "Field <ps> not found",1)
    645646      ENDIF
    646647#ifdef NC_DOUBLE
     
    650651#endif
    651652      IF (ierr .NE. NF_NOERR) THEN
    652          PRINT*, "lect_start_archive: Failed loading <ps>"
    653          CALL abort
     653         CALL abort_physic("lect_start_archive",
     654     &        "Failed loading <ps>",1)
    654655      ENDIF
    655656c
    656657      ierr = NF_INQ_VARID (nid, "tsurf", nvarid)
    657658      IF (ierr .NE. NF_NOERR) THEN
    658          PRINT*, "lect_start_archive: Field <tsurf> not found"
    659          CALL abort
     659         CALL abort_physic("lect_start_archive",
     660     &        "Field <tsurf> not found",1)
    660661      ENDIF
    661662#ifdef NC_DOUBLE
     
    665666#endif
    666667      IF (ierr .NE. NF_NOERR) THEN
    667          PRINT*, "lect_start_archive: Failed loading <tsurf>"
    668          CALL abort
     668         CALL abort_physic("lect_start_archive",
     669     &        "Failed loading <tsurf>",1)
    669670      ENDIF
    670671c
    671672      ierr = NF_INQ_VARID (nid, "q2surf", nvarid)
    672673      IF (ierr .NE. NF_NOERR) THEN
    673          PRINT*, "lect_start_archive: Field <q2surf> not found"
    674          CALL abort
     674         CALL abort_physic("lect_start_archive",
     675     &        "Field <q2surf> not found",1)
    675676      ENDIF
    676677#ifdef NC_DOUBLE
     
    680681#endif
    681682      IF (ierr .NE. NF_NOERR) THEN
    682          PRINT*, "lect_start_archive: Failed loading <q2surf>"
    683          CALL abort
     683         CALL abort_physic("lect_start_archive",
     684     &        "Failed loading <q2surf>",1)
    684685      ENDIF
    685686c
     
    837838            PRINT*, "lect_start_archive: ",
    838839     &              "Field <","Tg"//str2,"> not found"
    839             CALL abort
     840            CALL abort_physic("lect_start_archive",
     841     &           "Field <Tg> not found",1)
    840842         ENDIF
    841843#ifdef NC_DOUBLE
     
    849851            PRINT*, "lect_start_archive: ",
    850852     &            "Failed reading <","Tg"//str2,">"
    851             CALL abort
     853            CALL abort_physic("lect_start_archive",
     854     &           "Failed reading <Tg>",1)
    852855         ENDIF
    853856c
     
    862865       ierr=NF_INQ_VARID(nid,"tsoil",nvarid)
    863866       if (ierr.ne.NF_NOERR) then
    864         write(*,*)"lect_start_archive: Cannot find <tsoil>"
    865         call abort
     867        CALL abort_physic("lect_start_archive",
     868     &       "Cannot find <tsoil>",1)
    866869       else
    867870#ifdef NC_DOUBLE
     
    884887      ierr = NF_INQ_VARID (nid,"temp", nvarid)
    885888      IF (ierr .NE. NF_NOERR) THEN
    886          PRINT*, "lect_start_archive: Field <temp> not found"
    887          CALL abort
     889         CALL abort_physic("lect_start_archive",
     890     &        "Field <temp> not found",1)
    888891      ENDIF
    889892#ifdef NC_DOUBLE
     
    893896#endif
    894897      IF (ierr .NE. NF_NOERR) THEN
    895          PRINT*, "lect_start_archive: Failed loading <temp>"
    896          CALL abort
     898         CALL abort_physic("lect_start_archive",
     899     &        "Failed loading <temp>",1)
    897900      ENDIF
    898901c
    899902      ierr = NF_INQ_VARID (nid,"u", nvarid)
    900903      IF (ierr .NE. NF_NOERR) THEN
    901          PRINT*, "lect_start_archive: Field <u> not found"
    902          CALL abort
     904         CALL abort_physic("lect_start_archive",
     905     &        "Field <u> not found",1)
    903906      ENDIF
    904907#ifdef NC_DOUBLE
     
    908911#endif
    909912      IF (ierr .NE. NF_NOERR) THEN
    910          PRINT*, "lect_start_archive: Failed loading <u>"
    911          CALL abort
     913         CALL abort_physic("lect_start_archive",
     914     &        "Failed loading <u>",1)
    912915      ENDIF
    913916c
    914917      ierr = NF_INQ_VARID (nid,"v", nvarid)
    915918      IF (ierr .NE. NF_NOERR) THEN
    916          PRINT*, "lect_start_archive: Field <v> not found"
    917          CALL abort
     919         CALL abort_physic("lect_start_archive",
     920     &        "Field <v> not found",1)
    918921      ENDIF
    919922#ifdef NC_DOUBLE
     
    923926#endif
    924927      IF (ierr .NE. NF_NOERR) THEN
    925          PRINT*, "lect_start_archive: Failed loading <v>"
    926          CALL abort
     928         CALL abort_physic("lect_start_archive",
     929     &        "Failed loading <v>",1)
    927930      ENDIF
    928931c
    929932      ierr = NF_INQ_VARID (nid,"q2atm", nvarid)
    930933      IF (ierr .NE. NF_NOERR) THEN
    931          PRINT*, "lect_start_archive: Field <q2atm> not found"
    932          CALL abort
     934         CALL abort_physic("lect_start_archive",
     935     &        "Field <q2atm> not found",1)
    933936      ENDIF
    934937#ifdef NC_DOUBLE
     
    938941#endif
    939942      IF (ierr .NE. NF_NOERR) THEN
    940          PRINT*, "lect_start_archive: Failed loading <q2atm>"
    941          CALL abort
     943         CALL abort_physic("lect_start_archive",
     944     &        "Failed loading <q2atm>",1)
    942945      ENDIF
    943946c
     
    989992#endif
    990993        IF (ierr .NE. NF_NOERR) THEN
    991           PRINT*, "lect_start_archive: Failed loading <du_nonoro_gwd>"
    992           CALL abort
     994          CALL abort_physic("lect_start_archive",
     995     &         "Failed loading <du_nonoro_gwd>",1)
    993996        ENDIF
    994997      ENDIF
     
    10071010#endif
    10081011        IF (ierr .NE. NF_NOERR) THEN
    1009           PRINT*, "lect_start_archive: Failed loading <dv_nonoro_gwd>"
    1010           CALL abort
     1012          CALL abort_physic("lect_start_archive",
     1013     &         "Failed loading <dv_nonoro_gwd>",1)
    10111014        ENDIF
    10121015      ENDIF
     
    10251028#endif
    10261029        IF (ierr .NE. NF_NOERR) THEN
    1027           PRINT*, "lect_start_archive: Failed loading <east_gwstress>"
    1028           CALL abort
     1030          CALL abort_physic("lect_start_archive",
     1031     &         "Failed loading <east_gwstress>",1)
    10291032        ENDIF
    10301033      ENDIF
     
    10431046#endif
    10441047        IF (ierr .NE. NF_NOERR) THEN
    1045           PRINT*, "lect_start_archive: Failed loading <west_gwstress>"
    1046           CALL abort
     1048          CALL abort_physic("lect_start_archive",
     1049     &         "Failed loading <west_gwstress>",1)
    10471050        ENDIF
    10481051      ENDIF
  • trunk/LMDZ.GENERIC/libf/dynphy_lonlat/phystd/newstart.F

    r3836 r3893  
    259259          write(6,*)' Problem opening file:',fichnom
    260260          write(6,*)' ierr = ', ierr
    261           CALL ABORT
     261          CALL abort_physic("newstart",
     262     &         "Problem opening start_archive.nc file",1)
    262263        ENDIF
    263264        tab0 = 50
     
    275276          write(6,*)' Problem opening file:',fichnom
    276277          write(6,*)' ierr = ', ierr
    277           CALL ABORT
     278          CALL abort_physic("newstart",
     279     &         "Problem opening start.nc file", 1)
    278280        ENDIF
    279281 
     
    283285          write(6,*)' Problem opening file:',fichnom
    284286          write(6,*)' ierr = ', ierr
    285           CALL ABORT
     287          CALL abort_physic("newstart",
     288     &         "Problem opening startfi.nc file", 1)
    286289        ENDIF
    287290
     
    10951098        ! check that there is indeed a water vapor tracer
    10961099        if (igcm_h2o_vap.eq.0) then
    1097           write(*,*) "No water vapour tracer! Can't use this option"
    1098           stop
     1100          call abort_physic("newstart",
     1101     &         "No water vapour tracer! Can't use wetstart",1)
    10991102        endif
    11001103          DO l=1,llm
     
    11151118        else if (trim(modif) .eq. 'noglacier') then
    11161119           if (igcm_h2o_ice.eq.0) then
    1117              write(*,*) "No water ice tracer! Can't use this option"
    1118              stop
     1120             call abort_physic("newstart",
     1121     &            "No water ice tracer! Can't use noglacier",1)
    11191122           endif
    11201123           do ig=1,ngridmx
     
    11321135        else if (trim(modif) .eq. 'watercapn') then
    11331136           if (igcm_h2o_ice.eq.0) then
    1134              write(*,*) "No water ice tracer! Can't use this option"
    1135              stop
     1137             call abort_physic("newstart",
     1138     &            "No water ice tracer! Can't use watercapn",1)
    11361139           endif
    11371140
     
    11581161        else if (trim(modif) .eq. 'watercaps') then
    11591162           if (igcm_h2o_ice.eq.0) then
    1160               write(*,*) "No water ice tracer! Can't use this option"
    1161               stop
     1163              call abort_physic("newstart",
     1164     &             "No water ice tracer! Can't use watercaps",1)
    11621165           endif
    11631166
     
    11851188        else if (trim(modif) .eq. 'noacglac') then
    11861189           if (igcm_h2o_ice.eq.0) then
    1187              write(*,*) "No water ice tracer! Can't use this option"
    1188              stop
     1190             call abort_physic("newstart",
     1191     &            "No water ice tracer! Can't use noacglac",1)
    11891192           endif
    11901193          DO j=1,jjp1       
     
    12141217        else if (trim(modif) .eq. 'oborealis') then
    12151218           if (igcm_h2o_ice.eq.0) then
    1216              write(*,*) "No water ice tracer! Can't use this option"
    1217              stop
     1219             call abort_physic("newstart",
     1220     &            "No water ice tracer! Can't use oborealis",1)
    12181221           endif
    12191222          DO j=1,jjp1       
     
    12461249        else if (trim(modif) .eq. 'iborealis') then
    12471250           if (igcm_h2o_ice.eq.0) then
    1248              write(*,*) "No water ice tracer! Can't use this option"
    1249              stop
     1251             call abort_physic("newstart",
     1252     &            "No water ice tracer! Can't use iborealis",1)
    12501253           endif
    12511254          DO j=1,jjp1       
     
    12701273        else if (trim(modif) .eq. 'oceanball') then
    12711274           if (igcm_h2o_ice.eq.0) then
    1272              write(*,*) "No water ice tracer! Can't use this option"
    1273              stop
     1275             call abort_physic("newstart",
     1276     &            "No water ice tracer! Can't use oceanball",1)
    12741277           endif
    12751278          DO j=1,jjp1       
     
    12991302        else if (trim(modif) .eq. 'iceball') then
    13001303           if (igcm_h2o_ice.eq.0) then
    1301              write(*,*) "No water ice tracer! Can't use this option"
    1302              stop
     1304             call abort_physic("newstart",
     1305     &            "No water ice tracer! Can't use iceball",1)
    13031306           endif
    13041307          DO j=1,jjp1       
  • trunk/LMDZ.GENERIC/libf/dynphy_lonlat/phystd/start2archive.F

    r3836 r3893  
    179179       IF (ierr.NE.NF_NOERR) THEN
    180180         write(6,*)' Pb d''ouverture du fichier'//trim(fichnom)
    181         CALL ABORT
     181        CALL abort_physic("start2archive",
     182     &       "Pb d'ouverture du ficher start.nc",1)
    182183       ENDIF
    183184                                               
    184185      ierr = NF_INQ_VARID (nid1, "controle", varid)
    185186      IF (ierr .NE. NF_NOERR) THEN
    186        PRINT*, "start2archive: Le champ <controle> est absent"
    187        CALL abort
     187       CALL abort_physic("start2archive",
     188     &      "Le champ <controle> est absent",1)
    188189      ENDIF
    189190#ifdef NC_DOUBLE
     
    193194#endif
    194195       IF (ierr .NE. NF_NOERR) THEN
    195           PRINT*, "start2archive: Lecture echoue pour <controle>"
    196           CALL abort
     196          CALL abort_physic("start2archive",
     197     &         "Lecture echoue pour <controle>",1)
    197198       ENDIF
    198199
     
    204205       IF (ierr.NE.NF_NOERR) THEN
    205206         write(6,*)' Pb d''ouverture du fichier'//trim(fichnom)
    206         CALL ABORT
     207        CALL abort_physic("start2archive",
     208     &       "Pb d'ouverture du ficher startfi.nc",1)
    207209       ENDIF
    208210      ierr = NF_INQ_DIMID(nid1,"subsurface_layers",varid)
    209211      IF (ierr .NE. NF_NOERR) THEN
    210        PRINT*, "start2archive: No subsurface_layers dimension!!"
    211        CALL abort
     212       CALL abort_physic("start2archive",
     213     &      "No subsurface_layers dimension",1)
    212214      ENDIF
    213215      ierr = NF_INQ_DIMLEN(nid1,varid,nsoilmx)
    214216      IF (ierr .NE. NF_NOERR) THEN
    215        PRINT*, "start2archive: Failed reading subsurface_layers value!!"
    216        CALL abort
     217       CALL abort_physic("start2archive",
     218     &      "Failed reading subsurface_layers value",1)
    217219      ENDIF
    218220      ierr = NF_CLOSE(nid1)
     
    265267       IF (ierr.NE.NF_NOERR) THEN
    266268         write(6,*)' Pb d''ouverture du fichier'//trim(fichnom)
    267         CALL ABORT
     269        CALL abort_physic("start2archive",
     270     &       "Pb d'ouverture du ficher startfi.nc",1)
    268271       ENDIF
    269272                                               
    270273      ierr = NF_INQ_VARID (nid1, "controle", varid)
    271274      IF (ierr .NE. NF_NOERR) THEN
    272        PRINT*, "start2archive: Le champ <controle> est absent"
    273        CALL abort
     275       CALL abort_physic("start2archive",
     276     &       "Le champ <controle> est absent",1)
    274277      ENDIF
    275278#ifdef NC_DOUBLE
     
    279282#endif
    280283       IF (ierr .NE. NF_NOERR) THEN
    281           PRINT*, "start2archive: Lecture echoue pour <controle>"
    282           CALL abort
     284          CALL abort_physic("start2archive",
     285     &         "Lecture echoue pour <controle>",1)
    283286       ENDIF
    284287
     
    290293c-----------------------------------------------------------------------
    291294!mars a voir      if ((day_ini_fi.ne.day_ini).or.(abs(timefi-timedyn).gt.1.e-10))
    292       if ((day_ini_fi.ne.day_ini))
    293      &  stop ' Probleme de Synchro entre start et startfi !!!'
     295      if ((day_ini_fi.ne.day_ini)) then
     296        call abort_physic("start2archive",
     297     &       "Probleme de Synchro entre start et startfi",1)
     298      endif
    294299
    295300
     
    447452      if (ierr.ne.NF_NOERR) then
    448453         write(*,*) "time matter ",NF_STRERROR(ierr)
    449          stop
     454         call abort_physic("start2archive",
     455     &        "Wibbly wobbly timey wimey error",1)
    450456      endif
    451457
  • trunk/LMDZ.GENERIC/libf/dynphy_lonlat/phystd/write_archive.F

    r3100 r3893  
    116116              write(*,*) "***** PUT_VAR problem in write_archive"
    117117              write(*,*) "***** with ",trim(nom)," ",nf_STRERROR(ierr)
    118               call abort
     118              call abort_physic("write_archive",
     119     &             "PUT_VAR problem in write_archive", 1)
    119120           endif
    120121
     
    133134          ierr=NF_INQ_DIMID(nid,"subsurface_layers",id(3))
    134135          if (ierr.ne.NF_NOERR) then
    135            write(*,*)"write_archive: dimension <subsurface_layers>",
    136      &               " is missing !!!"
    137            call abort
     136           call abort_physic("write_archive",
     137     &          "dimension <subsurface_layers> is missing",1)
    138138          endif
    139139          ierr=NF_INQ_DIMID(nid,"Time",id(4))
     
    175175          ierr=NF_INQ_DIMID(nid,"ocean_layers",id(3))
    176176          if (ierr.ne.NF_NOERR) then
    177            write(*,*)"write_archive: dimension <ocean_layers>",
    178      &               " is missing !!!"
    179            call abort
     177           call abort_physic("write_archive",
     178     &          "dimension <ocean_layers> is missing",1)
    180179          endif
    181180          ierr=NF_INQ_DIMID(nid,"Time",id(4))
     
    246245              write(*,*) "***** PUT_VAR problem in write_archive"
    247246              write(*,*) "***** with ",nom,nf_STRERROR(ierr)
    248               call abort
     247              call abort_physic("write_archive",
     248     &             "PUT_VAR problem in write_archive",1)
    249249           endif
    250250
     
    282282              write(*,*) "***** PUT_VAR problem in write_archive"
    283283              write(*,*) "***** with ",nom,nf_STRERROR(ierr)
    284               call abort
     284              call abort_physic("write_archive",
     285     &             "PUT_VAR problem in write_archive",1)
    285286           endif
    286287
    287288        else
    288289          write(*,*) "write_archive: dim=",dim," ?!?"
    289           call abort
     290          call abort_physic("write_archive",
     291     &         "dim problem in write_archive",1)
    290292        endif ! of if (dim.eq.3) else if (dim.eq.-3) ....
    291293
Note: See TracChangeset for help on using the changeset viewer.