Changeset 2311


Ignore:
Timestamp:
May 6, 2020, 1:46:00 PM (5 years ago)
Author:
emillour
Message:

Mars GCM:
Code tidying: use getin_p() instead of getin() and use "call abort_physic"
instead of "stop" or "call abort".
EM

Location:
trunk/LMDZ.MARS
Files:
17 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/README

    r2308 r2311  
    29972997(NB: this last point also implies a change in concatnc.def, but retrocompatibility
    29982998with old concatnc.def files has been ensured)
     2999
     3000== 06/05/2020 == EM
     3001More code tidying: use getin_p() instead of getin() and use "call abort_physic"
     3002instead of "stop" or "call abort"
  • trunk/LMDZ.MARS/libf/aeronomars/perosat.F

    r1266 r2311  
    55      use tracer_mod, only: igcm_h2o2, mmol
    66      use conc_mod, only: mmean
    7       USE comcstfi_h
     7      use comcstfi_h, only: g
    88      IMPLICIT NONE
    99
     
    3232      integer,intent(in) :: nlayer  ! number of atmospheric layers
    3333      integer,intent(in) :: nq      ! number of tracers
    34       INTEGER ig
    35       REAL ptimestep                ! pas de temps physique (s)
    36       REAL pplev(ngrid,nlayer+1)    ! pression aux inter-couches (Pa)
    37       REAL pplay(ngrid,nlayer)      ! pression au milieu des couches (Pa)
    38       REAL zt(nlayer)              ! temperature au centre des couches (K)
     34      INTEGER,INTENT(IN) :: ig
     35      REAL,INTENT(IN) :: ptimestep  ! pas de temps physique (s)
     36      REAL,INTENT(IN) :: pplev(ngrid,nlayer+1)! pression aux inter-couches (Pa)
     37      REAL,INTENT(IN) :: pplay(ngrid,nlayer)  ! pression au milieu des couches (Pa)
     38      REAL,INTENT(IN) :: zt(nlayer) ! temperature au centre des couches (K)
    3939                                    ! deja mise a jour dans calchim
    4040
    4141c   Traceurs :
    42       real zy(nlayer,nq)        ! traceur (fraction molaire sortie chimie)
    43       real pdqcloud(ngrid,nlayer,nq) ! tendance condensation (kg/kg.s-1)
    44       real pdqscloud(ngrid,nq)         ! flux en surface (kg.m-2.s-1)
     42      real,intent(in) :: zy(nlayer,nq) ! traceur (fraction molaire sortie chimie)
     43      real,intent(out) :: pdqcloud(ngrid,nlayer,nq) ! tendance condensation (kg/kg.s-1)
     44      real,intent(out) :: pdqscloud(ngrid,nq)       ! flux en surface (kg.m-2.s-1)
    4545     
    4646c   local:
     
    6767         if (igcm_h2o2.eq.0) then
    6868           write(*,*) "perosat: error; no h2o2 tracer !!!!"
    69            stop
     69           call abort_physic("perosat","missing h2o2 tracer",1)
    7070         endif
    7171         firstcall=.false.
  • trunk/LMDZ.MARS/libf/aeronomars/read_phototable.F90

    r1918 r2311  
    2121!***********************************************************************
    2222
    23       use ioipsl_getincom, only: getin
     23      use ioipsl_getin_p_mod, only: getin_p
    2424      use datafile_mod, only: datadir
    2525
     
    4545! look for a " phototable= ..." option in def files
    4646
    47       call getin("phototable",phototable)
     47      call getin_p("phototable",phototable)
    4848
    4949      fic = 81
     
    6161        write(*,*)'   callphys.def with:'
    6262        write(*,*)'   phototable=filename'
    63         stop
     63        call abort_physic("read_phototable","missing "//trim(phototable)//"file",1)
    6464      end if
    6565
  • trunk/LMDZ.MARS/libf/phymars/co2cloud.F

    r2261 r2311  
    1616     &                rsedcloud,rhocloud,pzlev,pdqs_sedco2,
    1717     &                pdu,pu,pcondicea)
    18       USE ioipsl_getincom, only: getin
     18      USE ioipsl_getin_p_mod, ONLY : getin_p
    1919      use dimradmars_mod, only: naerkind
    2020      USE comcstfi_h, only: pi, g, cpp
     
    201201           write(*,*) 'stop in co2cloud (nq.gt.nqmx)!'
    202202           write(*,*) 'nq=',nq,' nqmx=',nqmx
    203            stop
     203           call abort_physic("co2cloud","nq.gt.nqmx",1)
    204204        endif
    205205        write(*,*) "co2cloud.F: rho_ice_co2 = ",rho_ice_co2
     
    213213        imicroco2 = 30
    214214#endif
    215         call getin("imicroco2",imicroco2)
     215        call getin_p("imicroco2",imicroco2)
    216216        write(*,*)"imicroco2 = ",imicroco2
    217217       
     
    257257           write(*,*) 'file optprop_co2ice_1mic.dat should be in '
    258258     &          ,trim(datadir)
    259            STOP
     259           call abort_physic("co2cloud",
     260     &          "missing file optprop_co2ice_1mic.dat",1)
    260261        endif
    261262!        open(newunit=uQext,file=trim(datadir)//
  • trunk/LMDZ.MARS/libf/phymars/convadj.F

    r1779 r2311  
    88      use tracer_mod, only: noms, ! tracer names
    99     &                      igcm_h2o_vap ! index of water vapor tracer
    10       USE comcstfi_h
     10      use comcstfi_h, only: g
    1111      implicit none
    1212
     
    3232!     ------------
    3333
    34 #include "callkeys.h"
     34      include "callkeys.h"
    3535
    3636
     
    7070
    7171!     Tracers
    72       INTEGER iq,ico2
    73       save ico2
     72      INTEGER iq
     73      integer,save :: ico2
    7474      REAL zq(ngrid,nlay,nq), zq2(ngrid,nlay,nq)
    7575      REAL zqm(nq),zqco2m
    76       real m_co2, m_noco2, A , B
    77       save A, B
     76      real m_co2, m_noco2
     77      real,save :: A, B
    7878
    7979      real mtot1, mtot2 , mm1, mm2
    80        integer l1ref, l2ref
    81       LOGICAL vtest(ngrid),down,firstcall
    82       save firstcall
    83       data firstcall/.true./
     80      integer l1ref, l2ref
     81      LOGICAL vtest(ngrid),down
     82      logical,save :: firstcall=.true.
    8483
    8584!     for conservation test
     
    376375            print*,'jadrs=',jadrs
    377376
    378             call abort
     377            call abort_physic("convadj","crashed",1)
    379378         endif
    380379!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
  • trunk/LMDZ.MARS/libf/phymars/param_slope.F90

    r227 r2311  
    8989  if ((theta_s > 90.) .or. (theta_s < 0.)) then
    9090        print *, 'please set theta_s between 0 and 90', theta_s
    91         stop
     91        call abort_physic("param_slopes","invalid theta_s",1)
    9292  endif
    9393
  • trunk/LMDZ.MARS/libf/phymars/soil_settings.F

    r1130 r2311  
    135135          if (ierr.ne.0) then
    136136            write(*,*) 'soil_settings: failed allocation of oldmlayer!'
    137             stop
     137            call abort_physic("soil_settings",
     138     &           "failed oldmlayer allocation",1)
    138139          endif
    139140        endif
     
    255256       if (.not.found) then
    256257         write(*,*) "soil_settings: Failed loading <inertiedat>"
    257          call abort
     258         call abort_physic("soil_settings",
     259     &        "failed loading <inertiedat>",1)
    258260       endif
    259261       
     
    272274            write(*,*) 'soil_settings: failed allocation of ',
    273275     &                 'oldinertiedat!'
    274             stop
     276            call abort_physic("soil_settings",
     277     &        "failed allocation of oldinertiedat",1)
    275278           endif
    276279         endif ! of if (.not.allocated(oldinertiedat))
     
    284287        if (.not.found) then
    285288          write(*,*) "soil_settings: Failed loading <inertiedat>"
    286           call abort
     289         call abort_physic("soil_settings",
     290     &        "failed loading <inertiedat>",1)
    287291        endif
    288292       else ! put values in therm_i
     
    295299         if (.not.found) then
    296300           write(*,*) "soil_settings: Failed loading <inertiedat>"
    297            call abort
     301           call abort_physic("soil_settings",
     302     &        "failed loading <inertiedat>",1)
    298303         endif
    299304!        endif
     
    320325             write(*,*) 'soil_settings: failed allocation of ',
    321326     &                  'oldtsoil!'
    322              stop
     327             call abort_physic("soil_settings",
     328     &        "failed allocation of oldtsoil",1)
    323329           endif
    324330         endif
     
    332338         if (.not.found) then
    333339           write(*,*) "soil_settings: Failed loading <tsoil>"
    334            call abort
     340           call abort_physic("soil_settings",
     341     &          "failed loading <tsoil>",1)
    335342         endif
    336343       else ! put values in tsoil
     
    351358         if (.not.found) then
    352359           write(*,*) "soil_settings: Failed loading <tsoil>"
    353            call abort
     360           call abort_physic("soil_settings",
     361     &          "failed loading <tsoil>",1)
    354362         endif
    355363       endif ! of if (interpol)
  • trunk/LMDZ.MARS/libf/phymars/suaer.F90

    r2199 r2311  
    232232  write(*,*)' change it in file phymars/suaer.F90. Just'
    233233  write(*,*)' modify the variable called file_id.'
    234   CALL ABORT
     234  CALL abort_physic("suaer","missing file "//trim(file_id(iaer,idomain)),1)
    235235ENDIF
    236236OPEN(UNIT=file_unit,&
     
    249249    TRIM(datadir)//&
    250250    '/'//TRIM(file_id(iaer,idomain))
    251     call abort
     251    call abort_physic("suaer","problem reading "//trim(file_id(iaer,idomain)),1)
    252252  endif
    253253  IF ((scanline(1:1) .ne. '#').and.&
     
    263263          TRIM(datadir)//&
    264264          '/'//TRIM(file_id(iaer,idomain))
    265           call abort
     265          call abort_physic("suaer",&
     266               "problem reading "//trim(file_id(iaer,idomain)),1)
    266267        endif
    267268        jfile = jfile+1
     
    274275          TRIM(datadir)//&
    275276          '/'//TRIM(file_id(iaer,idomain))
    276           call abort
     277          call abort_physic("suaer",&
     278               "problem reading "//trim(file_id(iaer,idomain)),1)
    277279        endif
    278280        endwhile = .true.
     
    280282        WRITE(*,*) 'readoptprop: ',&
    281283          'Error while loading optical properties.'
    282         CALL ABORT
     284        call abort_physic("suaer",&
     285               "problem loading optical properties",1)
    283286    END SELECT reading1_seq ! ==============================
    284287  ENDIF
     
    346349        WRITE(*,*) 'suaer.F90: ',&
    347350          'Error while loading optical properties.'
    348         CALL ABORT
     351        call abort_physic("suaer",&
     352               "problem loading optical properties",1)
    349353    END SELECT reading2_seq ! ==============================
    350354  ENDIF
     
    378382   write(*,*) "       you must increase the value of nsizemax"
    379383   write(*,*) "       in dimradmars_mod !"
    380    stop
     384   call abort_physic("suaer","nsizemax too small",1)
    381385 endif
    382386! ------------------------------------------------
  • trunk/LMDZ.MARS/libf/phymars/surfini.F

    r2182 r2311  
    11      SUBROUTINE surfini(ngrid,piceco2,qsurf)
    22
    3       USE ioipsl_getincom, only: getin
     3      USE ioipsl_getin_p_mod, ONLY : getin_p
    44      use netcdf
    55      use tracer_mod, only: nqmx, noms
     
    141141         write(*,*) "surfini: Ice dryness ?"
    142142         icedryness=1. ! default value
    143          call getin("icedryness",icedryness)
     143         call getin_p("icedryness",icedryness)
    144144         write(*,*) "surfini: icedryness = ",icedryness
    145145         dryness (:) = icedryness
     
    187187       write(*,*)'   can be obtained online on:'
    188188       write(*,*)' http://www.lmd.jussieu.fr/~lmdz/planets/mars/datadir'
    189        CALL ABORT
     189       call abort_physic("surfini","missing surface.nc file",1)
    190190         ENDIF
    191191     
     
    196196          write(*,*) ' in file ',trim(zedatafile),'/surface.nc'
    197197          write(*,*)trim(nf90_strerror(ierr))
    198           stop
     198          call abort_physic("surfini","missing "//trim(string),1)
    199199         endif
    200200
     
    204204          write(*,*) 'surfini: error failed loading ',trim(string)
    205205          write(*,*)trim(nf90_strerror(ierr))
    206           stop
     206          call abort_physic("surfini","failed loading "//trim(string),1)
    207207         endif
    208208 
     
    359359          print*,'Please change icelocationmode in surfini.F'
    360360          print*,'Or add some new definitions ...'
    361           call abort
     361          call abort_physic("surfini",
     362     &         "no pre-definitions for this resolution",1)
    362363         
    363364         endif
     
    434435         print*, 'In surfini.F, icelocationmode is ', icelocationmode
    435436         print*, 'It should be 1, 2 or 3.'
    436          call abort 
     437         call abort_physic("surfini","wrong icelocationmode",1)
    437438
    438439        ENDIF ! of if (icelocation)
  • trunk/LMDZ.MARS/libf/phymars/swmain_mod.F

    r1983 r2311  
    160160          else
    161161            write(*,*) "swmain: invalid swrtype value !!"
    162             stop
     162            call abort_physic("swmain","invalid swrtype",1)
    163163          endif ! of if (swrtype.eq.2)
    164164        endif ! of if (swrtype.eq.1)
  • trunk/LMDZ.MARS/libf/phymars/tabfi.F

    r2281 r2311  
    267267        write(*,*) "tabfi: Error modifying tab_control should",
    268268     &             " only happen in serial mode (eg: by newstart)"
    269         stop
     269        call abort_physic(modname,
     270     &       "tab_control modification not possible in parallel",1)
    270271      endif
    271272c-----------------------------------------------------------------------
  • trunk/LMDZ.MARS/libf/phymars/vlz_fi.F

    r2120 r2311  
    168168c               wq(ij,l+1)= (MQtot + (-w(ij,l+1)-Mtot)*qm(ij,1))
    169169                write(*,*) 'a rather weird situation in vlz_fi !'
    170                 stop
     170                call abort_physic("vlz_fi","weird situation",1)
    171171             end if
    172172
  • trunk/LMDZ.MARS/libf/phymars/watercloud_mod.F

    r2162 r2311  
    1313     &                nq,tau,tauscaling,rdust,rice,nuice,
    1414     &                rsedcloud,rhocloud,totcloudfrac)
    15       USE ioipsl_getincom, ONLY: getin
     15      USE ioipsl_getin_p_mod, ONLY : getin_p
    1616      USE updaterad, ONLY: updaterdust, updaterice_micro,
    1717     &                     updaterice_typ
     
    132132           write(*,*) 'stop in watercloud (nq.gt.nqmx)!'
    133133           write(*,*) 'nq=',nq,' nqmx=',nqmx
    134            stop
     134           call abort_physic("watercloud","nq.gt.nqmx",1)
    135135        endif
    136136         
     
    144144        imicro = 30
    145145#endif
    146         call getin("imicro",imicro)
     146        call getin_p("imicro",imicro)
    147147        write(*,*)"watercloud: imicro = ",imicro
    148148       
  • trunk/LMDZ.MARS/libf/phymars/writediagfi.F

    r2141 r2311  
    144144            if (n.ge.n_nom_def_max) then
    145145               write(*,*)"n_nom_def_max too small in writediagfi.F:",n
    146                stop
     146               call abort_physic("writediagfi",
     147     &             "n_nom_def_max too small",1)
    147148            end if
    148149            n_nom_def=n-1
     
    177178           write(*,*) "   firstnom string not long enough!!"
    178179           write(*,*) "   increase its size to at least ",len_trim(nom)
    179            stop
     180           call abort_physic("writediagfi","firstnom too short",1)
    180181         endif
    181182         
     
    363364     &                   trim(nom)
    364365              write(*,*) "it seems it already exists!"
    365               stop
     366              call abort_physic("writediagfi",
     367     &             trim(nom)//" already exists",1)
    366368             endif
    367369           endif
     
    398400              write(*,*) "***** with dx3: ",trim(nom)
    399401              write(*,*) 'ierr=', ierr,": ",NF_STRERROR(ierr)
    400               stop
     402              call abort_physic("writediagfi",
     403     &             "failed writing "//trim(nom),1)
    401404           endif
    402405
     
    465468     &                   trim(nom)
    466469              write(*,*) "it seems it already exists!"
    467               stop
     470              call abort_physic("writediagfi",
     471     &             trim(nom)//" already exists",1)
    468472             endif
    469473           endif
     
    495499              write(*,*) "***** with dx2: ",trim(nom)
    496500              write(*,*) 'ierr=', ierr,": ",NF_STRERROR(ierr)
    497               stop
     501              call abort_physic("writediagfi",
     502     &             "failed writing "//trim(nom),1)
    498503           endif
    499504
     
    507512           write(*,*) "writediagfi error: dim=1 not implemented ",
    508513     &                 "in parallel mode. Problem for ",trim(nom)
    509            stop
     514              call abort_physic("writediagfi",
     515     &             "failed writing "//trim(nom),1)
    510516         endif
    511517!         Passage variable physique -->  physique dynamique
     
    533539     &                   trim(nom)
    534540              write(*,*) "it seems it already exists!"
    535               stop
     541              call abort_physic("writediagfi",
     542     &             trim(nom)//" already exists",1)
    536543             endif
    537544           endif
     
    552559              write(*,*) "***** with dx1: ",trim(nom)
    553560              write(*,*) 'ierr=', ierr,": ",NF_STRERROR(ierr)
    554               stop
     561              call abort_physic("writediagfi",
     562     &             "failed writing "//trim(nom),1)
    555563           endif
    556564
     
    581589     &                   trim(nom)
    582590              write(*,*) "it seems it already exists!"
    583               stop
     591              call abort_physic("writediagfi",
     592     &             trim(nom)//" already exists",1)
    584593             endif
    585594           endif
     
    597606              write(*,*) "***** with dx0: ",trim(nom)
    598607              write(*,*) 'ierr=', ierr,": ",NF_STRERROR(ierr)
    599               stop
     608              call abort_physic("writediagfi",
     609     &             "failed writing "//trim(nom),1)
    600610           endif
    601611
  • trunk/LMDZ.MARS/libf/phymars/writediagsoil.F90

    r2023 r2311  
    8484    write(*,*) "   firstname string not long enough!!"
    8585    write(*,*) "   increase its size to at least ",len_trim(name)
    86     stop
     86    call abort_physic("writediagsoil","firstname too short",1)
    8787  endif
    8888 
     
    9696   if (ierr.ne.NF_NOERR) then
    9797    write(*,*)'writediagsoil: Error, failed creating file '//trim(filename)
    98     stop
     98    call abort_physic("writediagsoil","failed creating"//trim(filename),1)
    9999   endif
    100100  endif
     
    178178     if (ierr.ne.NF_NOERR) then
    179179      write(*,*)"writediagsoil: Failed writing date to time variable"
    180       stop
     180      call abort_physic("writediagsoil","failed writing time",1)
    181181     endif
    182182    endif ! of if (is_master)
     
    354354#ifdef CPP_PARA
    355355  write(*,*) "writediagsoil: dimps==0 case not implemented in // mode!!"
    356   stop
     356  call abort_physic("writediagsoil","dimps==0 not implemented",1)
    357357#endif
    358358  ! A. Copy data value
  • trunk/LMDZ.MARS/libf/phymars/wstats.F90

    r1689 r2311  
    171171
    172172   write (*,*) "====================="
    173    write (*,*) "STATS: creation de ",nom
     173   write (*,*) "STATS: creating ",nom
    174174   namebis=trim(nom)
    175175   call def_var_stats(nid,namebis,titre,unite,nbdim,id,meanid,ierr)
     
    245245         write (*,*) "wstats error reading :",trim(nom)
    246246         write (*,*) NF_STRERROR(ierr)
    247          stop ""
     247         call abort_physic("wstats","Failed reading "//trim(nom),1)
    248248      endif
    249249
     
    265265         write (*,*) "wstats error reading :",trim(nom)
    266266         write (*,*) NF_STRERROR(ierr)
    267          stop ""
     267         call abort_physic("wstats","Failed reading "//trim(nom),1)
    268268      endif
    269269   endif
     
    303303     write (*,*) "wstats error writing :",trim(nom)
    304304     write (*,*) NF_STRERROR(ierr)
    305      stop ""
     305     call abort_physic("wstats","Failed writing "//trim(nom),1)
    306306  endif
    307307
     
    325325     write(*,*) "sd2d:",sd2d
    326326     write (*,*) NF_STRERROR(ierr)
    327      stop ""
     327     call abort_physic("wstats","Failed writing "//trim(nom),1)
    328328  endif
    329329
     
    399399     write (*,*) "inivar error writing variable"
    400400     write (*,*) NF_STRERROR(ierr)
    401      stop ""
     401     call abort_physic("inivar","error writing variable",1)
    402402  endif
    403403
     
    445445     write (*,*) "inivar error writing variable"
    446446     write (*,*) NF_STRERROR(ierr)
    447      stop ""
     447     call abort_physic("inivar","error writing variable",1)
    448448  endif
    449449
     
    491491   write(*,*) "def_var_stats: Failed defining variable "//trim(name)
    492492   write(*,*) NF_STRERROR(ierr)
    493    stop ""
     493   call abort_physic("def_var_stats","Failed defining "//trim(name),1)
    494494endif
    495495
     
    500500   write(*,*) "def_var_stats: Failed writing title attribute for "//trim(name)
    501501   write(*,*) NF_STRERROR(ierr)
    502    stop ""
     502   call abort_physic("def_var_stats","Failed writing title for "//trim(name),1)
    503503endif
    504504
     
    508508   write(*,*) "def_var_stats: Failed writing units attribute for "//trim(name)
    509509   write(*,*) NF_STRERROR(ierr)
    510    stop ""
     510   call abort_physic("def_var_stats","Failed writing units for "//trim(name),1)
    511511endif
    512512
  • trunk/LMDZ.MARS/libf/phymars/yamada4.F

    r1774 r2311  
    1616!.......................................................................
    1717! MARS
    18 #include "callkeys.h"
     18      include "callkeys.h"
    1919!.......................................................................
    2020!
     
    171171     
    172172      if (.not.(iflag_pbl.ge.6.and.iflag_pbl.le.10)) then
    173            stop'probleme de coherence dans appel a MY'
     173        call abort_physic("yamada4",
     174     &       'probleme de coherence dans appel a MY',1)
    174175      endif
    175176
     
    608609!.......................................................................
    609610! MARS
    610 #include "callkeys.h"
     611      include "callkeys.h"
    611612!.......................................................................
    612613!
     
    686687!.......................................................................
    687688! MARS
    688 #include "callkeys.h"
     689      include "callkeys.h"
    689690!.......................................................................
    690691!
Note: See TracChangeset for help on using the changeset viewer.