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/libf/aeronomars
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • 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
Note: See TracChangeset for help on using the changeset viewer.