Changeset 4469


Ignore:
Timestamp:
Mar 10, 2023, 5:52:00 PM (14 months ago)
Author:
Laurent Fairhead
Message:

Replaced STOP instructions by calls to abort_gcm for a cleaner exit

Location:
LMDZ6/trunk/libf/dyn3dmem
Files:
14 edited

Legend:

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

    r4143 r4469  
    161161         !--------------------------------------------------------------------
    162162!           WRITE(*,*) 'advtrac 248: iq,q(1721,19,:)=',iq,q(1721,19,:)
    163             STOP 'advtrac : appel a vlspltqs :schema non parallelise'
     163            CALL abort_gcm("advtrac","appel a vlspltqs :schema non parallelise",1)
    164164!LF         CALL vlspltqs_p(q(1,1,1),2.,massem,wg,pbarug,pbarvg,dtvr,p,pk,teta )
    165165
     
    167167         CASE(12)  !--- Schema de Frederic Hourdin
    168168         !--------------------------------------------------------------------
    169             STOP 'advtrac : appel a vlspltqs :schema non parallelise'
     169            CALL abort_gcm("advtrac","appel a vlspltqs :schema non parallelise",1)
    170170            CALL adaptdt(iadv,dtbon,n,pbarug,massem)   ! pas de temps adaptatif
    171171            IF(n > 1) WRITE(*,*) 'WARNING horizontal dt=',dtbon,'dtvr=',dtvr,'n=',n
     
    177177         CASE(13)  !--- Pas de temps adaptatif
    178178         !--------------------------------------------------------------------
    179             STOP 'advtrac : schema non parallelise'
     179            CALL abort_gcm("advtrac","schema non parallelise",1)
    180180            CALL adaptdt(iadv,dtbon,n,pbarug,massem)
    181181            IF(n > 1) WRITE(*,*) 'WARNING horizontal dt=',dtbon,'dtvr=',dtvr,'n=',n
     
    187187         CASE(20)  !--- Schema de pente SLOPES
    188188         !--------------------------------------------------------------------
    189             STOP 'advtrac : schema non parallelise'
     189            CALL abort_gcm("advtrac","schema SLOPES non parallelise",1)
    190190            CALL pentes_ini (q(1,1,iq),wg,massem,pbarug,pbarvg,0)
    191191
     
    193193         CASE(30)  !--- Schema de Prather
    194194         !--------------------------------------------------------------------
    195             STOP 'advtrac : schema non parallelise'
     195            CALL abort_gcm("advtrac","schema prather non parallelise",1)
    196196            ! Pas de temps adaptatif
    197197            CALL adaptdt(iadv,dtbon,n,pbarug,massem)
     
    202202         CASE(11,16,17,18)   !--- Schemas PPM Lin et Rood
    203203         !--------------------------------------------------------------------
    204             STOP 'advtrac : schema non parallelise'
     204            CALL abort_gcm("advtrac","schema PPM non parallelise",1)
    205205            ! Test sur le flux horizontal
    206206            CALL adaptdt(iadv,dtbon,n,pbarug,massem)   ! pas de temps adaptatif
  • LMDZ6/trunk/libf/dyn3dmem/bilan_dyn_loc.F

    r2601 r4469  
    231231           WRITE(lunout,*)'dt_app=',dt_app
    232232           WRITE(lunout,*)'dt_cum=',dt_cum
    233            stop
     233           CALL abort_gcm("conf_gcmbilan_dyn_loc","stopped",1)
    234234        endif
    235235
  • LMDZ6/trunk/libf/dyn3dmem/conf_gcm.F90

    r4358 r4469  
    453453        write(lunout,*)'conf_gcm: La valeur de clat passee par run.def', &
    454454             ' est differente de celle lue sur le fichier  start '
    455         STOP
     455        CALL abort_gcm("conf_gcm","stopped",1)
    456456     ENDIF
    457457
     
    467467        write(lunout,*)'conf_gcm: La valeur de grossismx passee par ', &
    468468             'run.def est differente de celle lue sur le fichier  start '
    469         STOP
    470      ENDIF
     469        CALL abort_gcm("conf_gcm","stopped",1)
     470      ENDIF
    471471
    472472     !Config  Key  = grossismy
     
    481481        write(lunout,*)'conf_gcm: La valeur de grossismy passee par ', &
    482482             'run.def est differente de celle lue sur le fichier  start '
    483         STOP
     483        CALL abort_gcm("conf_gcm","stopped",1)
    484484     ENDIF
    485485
     
    487487        write(lunout,*) &
    488488             'conf_gcm: ***  ATTENTION !! grossismx < 1 .   *** '
    489         STOP
     489        CALL abort_gcm("conf_gcm","stopped",1)
    490490     ELSE
    491491        alphax = 1. - 1./ grossismx
     
    495495        write(lunout,*) &
    496496             'conf_gcm: ***  ATTENTION !! grossismy < 1 .   *** '
    497         STOP
     497        CALL abort_gcm("conf_gcm","stopped",1)
    498498     ELSE
    499499        alphay = 1. - 1./ grossismy
     
    517517           write(lunout,*)' *** fxyhypb lu sur le fichier start est ', &
    518518                'F alors  qu il est  T  sur  run.def  ***'
    519            STOP
     519           CALL abort_gcm("conf_gcm","stopped",1)
    520520        ENDIF
    521521     ELSE
     
    524524           write(lunout,*)' ***  fxyhypb lu sur le fichier start est ', &
    525525                'T alors  qu il est  F  sur  run.def  ****  '
    526            STOP
     526           CALL abort_gcm("conf_gcm","stopped",1)
    527527        ENDIF
    528528     ENDIF
     
    540540           write(lunout,*)'conf_gcm: La valeur de dzoomx passee par ', &
    541541                'run.def est differente de celle lue sur le fichier  start '
    542            STOP
     542           CALL abort_gcm("conf_gcm","stopped",1)
    543543        ENDIF
    544544     ENDIF
     
    556556           write(lunout,*)'conf_gcm: La valeur de dzoomy passee par ', &
    557557                'run.def est differente de celle lue sur le fichier  start '
    558            STOP
     558           CALL abort_gcm("conf_gcm","stopped",1)
    559559        ENDIF
    560560     ENDIF
     
    571571           write(lunout,*)'conf_gcm: La valeur de taux passee par ', &
    572572                'run.def est differente de celle lue sur le fichier  start '
    573            STOP
     573           CALL abort_gcm("conf_gcm","stopped",1)
    574574        ENDIF
    575575     ENDIF
     
    586586           write(lunout,*)'conf_gcm: La valeur de tauy passee par ', &
    587587                'run.def est differente de celle lue sur le fichier  start '
    588            STOP
     588        CALL abort_gcm("conf_gcm","stopped",1)
    589589        ENDIF
    590590     ENDIF
     
    607607              write(lunout,*)' *** ysinus lu sur le fichier start est F', &
    608608                   ' alors  qu il est  T  sur  run.def  ***'
    609               STOP
     609              CALL abort_gcm("conf_gcm","stopped",1)
    610610           ENDIF
    611611        ELSE
     
    614614              write(lunout,*)' *** ysinus lu sur le fichier start est T', &
    615615                   ' alors  qu il est  F  sur  run.def  ****  '
    616               STOP
     616              CALL abort_gcm("conf_gcm","stopped",1)
    617617           ENDIF
    618618        ENDIF
     
    754754     IF( grossismx.LT.1. )  THEN
    755755        write(lunout,*) 'conf_gcm: ***ATTENTION !! grossismx < 1 . *** '
    756         STOP
     756        CALL abort_gcm("conf_gcm","stopped",1)
    757757     ELSE
    758758        alphax = 1. - 1./ grossismx
     
    761761     IF( grossismy.LT.1. )  THEN
    762762        write(lunout,*) 'conf_gcm: ***ATTENTION !! grossismy < 1 . *** '
    763         STOP
     763        CALL abort_gcm("conf_gcm","stopped",1)
    764764     ELSE
    765765        alphay = 1. - 1./ grossismy
  • LMDZ6/trunk/libf/dyn3dmem/filtreg_p.F

    r1907 r4469  
    9999c-------------------------------------------------------c
    100100
    101       IF(ifiltre.EQ.1.or.ifiltre.EQ.-1)
    102      &     STOP'Pas de transformee simple dans cette version'
     101      IF(ifiltre.EQ.1.or.ifiltre.EQ.-1)
     102     & CALL abort_gcm("fitreg_p","Pas de transformee simple
     103     &dans cette version",1)
    103104     
    104105      IF( iter.EQ. 2 )  THEN
    105106         PRINT *,' Pas d iteration du filtre dans cette version !'
    106107     &        , ' Utiliser old_filtreg et repasser !'
    107          STOP
     108         CALL abort_gcm("fitreg_p","stopped",1)
    108109      ENDIF
    109110
     
    111112         PRINT *,' Cette routine ne calcule le filtre inverse que '
    112113     &        , ' sur la grille des scalaires !'
    113          STOP
     114         CALL abort_gcm("fitreg_p","stopped",1)
    114115      ENDIF
    115116
     
    117118         PRINT *,' Probleme dans filtreg car ifiltre NE 2 et NE -2'
    118119     &        , ' corriger et repasser !'
    119          STOP
    120       ENDIF
     120         CALL abort_gcm("fitreg_p","stopped",1)
     121       ENDIF
    121122c
    122123
     
    127128      IF( griscal )   THEN
    128129         IF( nlat. NE. jjp1 )  THEN
    129             PRINT  1111
    130             STOP
     130            CALL abort_gcm("fitreg_p","nlat. NE. jjp1",1)
    131131         ELSE
    132132c     
     
    146146      ELSE
    147147         IF( nlat.NE.jjm )  THEN
    148             PRINT  2222
    149             STOP
     148            CALL abort_gcm("fitreg_p","nlat. NE. jjm",1)
    150149         ELSE
    151150c
  • LMDZ6/trunk/libf/dyn3dmem/guide_loc_mod.F90

    r4246 r4469  
    502502            write(*,*)trim(modname)//' second pass in advreel at itau=',&
    503503            itau
    504             stop
     504            CALL abort_gcm("guide_loc_lod","stopped",1)
    505505          ELSE
    506506!$OMP MASTER
     
    15291529              if (gamma.lt.1.e-5) then
    15301530                write(*,*)trim(modname)//' gamma =',gamma,'<1e-5'
    1531                 stop
     1531                CALL abort_gcm("guide_loc_mod","stopped",1)
    15321532              endif
    15331533              gamma=log(0.5)/log(gamma)
  • LMDZ6/trunk/libf/dyn3dmem/mod_filtreg_p.F

    r2125 r4469  
    8585
    8686      INTEGER :: sdd1_type, sdd2_type
     87      CHARACTER (LEN=132) :: abort_message
    8788
    8889      IF (first) THEN
     
    103104
    104105      IF(ifiltre.EQ.1.or.ifiltre.EQ.-1)
    105      &     STOP'Pas de transformee simple dans cette version'
     106     &  CALL abort_gcm("mod_filtreg_p",'Pas de transformee
     107     &simple dans cette version',1)
    106108     
    107109      IF( iter.EQ. 2 )  THEN
    108110         PRINT *,' Pas d iteration du filtre dans cette version !'
    109111     &        , ' Utiliser old_filtreg et repasser !'
    110          STOP
     112         CALL abort_gcm("mod_filtreg_p","stopped",1)
    111113      ENDIF
    112114
     
    114116         PRINT *,' Cette routine ne calcule le filtre inverse que '
    115117     &        , ' sur la grille des scalaires !'
    116          STOP
     118         CALL abort_gcm("mod_filtreg_p","stopped",1)
    117119      ENDIF
    118120
     
    120122         PRINT *,' Probleme dans filtreg car ifiltre NE 2 et NE -2'
    121123     &        , ' corriger et repasser !'
    122          STOP
     124         CALL abort_gcm("mod_filtreg_p","stopped",1)
    123125      ENDIF
    124126c
     
    130132      IF( griscal )   THEN
    131133         IF( nlat. NE. jjp1 )  THEN
    132             PRINT  1111
    133             STOP
     134            CALL abort_gcm("mod_filtreg_p"," nlat. NE. jjp1",1)
    134135         ELSE
    135136c     
     
    149150      ELSE
    150151         IF( nlat.NE.jjm )  THEN
    151             PRINT  2222
    152             STOP
     152            CALL abort_gcm("mod_filtreg_p"," nlat. NE. jjm",1)
    153153         ELSE
    154154c
  • LMDZ6/trunk/libf/dyn3dmem/mod_hallo.F90

    r2620 r4469  
    154154    if (Buffer_pos(Index_pos)+Size>MaxBufferSize) then
    155155      print *,'STOP :: La taille de MaxBufferSize dans mod_hallo.F90 est trop petite !!!!'
    156       stop
     156      CALL abort_gcm("mod_hallo","stopped",1)
    157157    endif
    158158   
    159159    if (Index_pos>=ListSize) then
    160160      print *,'STOP :: La taille de ListSize dans mod_hallo.F90 est trop petite !!!!'
    161       stop
     161      CALL abort_gcm("mod_hallo","stopped",1)
    162162    endif
    163163     
     
    14161416         IF (.NOT.using_mpi) THEN
    14171417           PRINT *,'Erreur, echange MPI en mode sequentiel !!!'
    1418            STOP
     1418           CALL abort_gcm("mod_hallo","stopped",1)
    14191419         ENDIF
    14201420!         PRINT *,"-------------------------------------------------------------------"
     
    14591459             IF (.NOT.using_mpi) THEN
    14601460               PRINT *,'Erreur, echange MPI en mode sequentiel !!!'
    1461                STOP
     1461               CALL abort_gcm("mod_hallo","stopped",1)
    14621462             ENDIF
    14631463
  • LMDZ6/trunk/libf/dyn3dmem/parallel_lmdz.F90

    r3995 r4469  
    676676        else
    677677           write(lunout,*)ij 
    678         stop 'erreur dans Gather_Field'
     678        CALL abort_gcm("parallel_lmdz","erreur dans Gather_Field",1)
    679679        endif
    680680       
     
    690690              Recv_count(i)=(min(jj_end_para(i),jjm)-jj_begin_para(i)+1)*ll*iip1
    691691            else
    692               stop 'erreur dans Gather_Field'
     692              CALL abort_gcm("parallel_lmdz","erreur dans Gather_Field",1)
    693693            endif
    694694                   
  • LMDZ6/trunk/libf/dyn3dmem/qminimum_loc.F

    r4384 r4469  
    212212                   write(*,*) 'q(i,k-1,iqIsoPha(ixt,iq_vap))=',
    213213     :                   q(i,k-1,iqIsoPha(ixt,iq_vap))
    214                    stop
     214                CALL abort_gcm("qminimum_loc","stopped",1)
    215215                endif
    216216              endif
     
    237237                   write(*,*) 'q(i,k-1,iqIsoPha(ixt,iq_vap))=',
    238238     :                   q(i,k-1,iqIsoPha(ixt,iq_vap))
    239                    stop
     239                   CALL abort_gcm("qminimum_loc","stopped",1)
    240240                endif
    241241              endif
  • LMDZ6/trunk/libf/dyn3dmem/times.F90

    r1907 r4469  
    5555   
    5656      if (timer_state(no_timer)/=stopped) then
    57         stop 'start_timer :: timer is already running or suspended'
     57        CALL abort_gcm("times","start_timer :: timer is already running or suspended",1)
    5858      else
    5959        timer_state(no_timer)=running
     
    7373    if (AllTimer_IsActive) then   
    7474      if (timer_state(no_timer)/=running) then
    75         stop 'suspend_timer :: timer is not running'
     75         CALL abort_gcm("times","suspend_timer :: timer is not running",1)
    7676      else
    7777        timer_state(no_timer)=suspended
     
    9090    if (AllTimer_IsActive) then   
    9191      if (timer_state(no_timer)/=suspended) then
    92         stop 'resume_timer :: timer is not suspended'
     92        CALL abort_gcm("times","resume_timer :: timer is not suspended",1)
    9393      else
    9494        timer_state(no_timer)=running
     
    110110       
    111111      if (timer_state(no_timer)/=running) then
    112         stop 'stop_timer :: timer is not running'
     112        CALL abort_gcm("times","stop_timer :: timer is not running",1)
    113113      else
    114114        timer_state(no_timer)=stopped
  • LMDZ6/trunk/libf/dyn3dmem/vlsplt_loc.F

    r4325 r4469  
    210210c$OMP END DO NOWAIT
    211211#endif
    212 c       stop
    213212
    214213c       go to 9999
  • LMDZ6/trunk/libf/dyn3dmem/vlspltgen_loc.F

    r4143 r4469  
    1 !
     1
     2!     
    23! $Header$
    34!
     
    259260c$OMP END MASTER
    260261          CASE DEFAULT
    261           stop 'vlspltgen_p : schema non parallelise'
    262      
     262             CALL abort_gcm("vlspltgen_loc","schema non parallelise",1)
    263263        END SELECT
    264264     
     
    302302#endif   
    303303          CASE DEFAULT
    304           stop 'vlspltgen_p : schema non parallelise'
    305      
     304          CALL abort_gcm("vlspltgen_p","schema non parallelise",1)
    306305        END SELECT
    307306     
     
    346345          CASE(14); call vlyqs_loc(zq,pente_max,zm,mv,qsat,iq)
    347346          CASE DEFAULT
    348           stop 'vlspltgen_p : schema non parallelise'
     347          CALL abort_gcm("vlspltgen_p","schema non parallelise",1)
    349348        END SELECT
    350349       
     
    392391c$OMP BARRIER
    393392          CASE DEFAULT
    394           stop 'vlspltgen_p : schema non parallelise'
    395      
    396         END SELECT
     393           
     394            CALL abort_gcm("vlspltgen_p","schema non parallelise",1)
     395         END SELECT
    397396     
    398397      enddo
     
    429428c$OMP BARRIER       
    430429          CASE DEFAULT
    431           stop 'vlspltgen_p : schema non parallelise'
     430          CALL abort_gcm("vlspltgen_p","schema non parallelise",1)
    432431        END SELECT
    433432     
     
    466465          CASE(10); call   vly_loc(zq,pente_max,zm,mv,     iq)
    467466          CASE(14); call vlyqs_loc(zq,pente_max,zm,mv,qsat,iq)
    468           CASE DEFAULT; stop 'vlspltgen_p : schema non parallelise'
     467          CASE DEFAULT
     468             CALL abort_gcm("vlspltgen_p","schema non parallelise",1)
    469469        END SELECT
    470470       
     
    486486          CASE(14); call vlxqs_loc(zq,pente_max,zm,mu,
    487487     &                 qsat, ij_begin,ij_end,iq)
    488           CASE DEFAULT; stop 'vlspltgen_p : schema non parallelise'
     488          CASE DEFAULT
     489          CALL abort_gcm("vlspltgen_p","schema non parallelise",1)
    489490        END SELECT
    490491       
  • LMDZ6/trunk/libf/dyn3dmem/vlspltqs_loc.F

    r4325 r4469  
    7474            DO ij=ijb,ije-1
    7575               dxqu(ij)=q(ij+1,l,iq)-q(ij,l,iq)
    76 c              IF(u_m(ij,l).lt.0.) stop'limx n admet pas les U<0'
    77 c              sigu(ij)=u_m(ij,l)/masse(ij,l,iq)
    7876            ENDDO
    7977            DO ij=ijb+iip1-1,ije,iip1
  • LMDZ6/trunk/libf/dyn3dmem/wrgrads.F

    r1907 r4469  
    7676           print*,'nvar  ',nvar(if)
    7777           print*,'vars ',(var(iv,if),iv=1,nvar(if))
    78 
    79            stop
     78           CALL abort_gcm("wrgrads","problem",1)
    8079         endif
    8180      endif
Note: See TracChangeset for help on using the changeset viewer.