Changeset 2304


Ignore:
Timestamp:
Apr 28, 2020, 3:32:34 PM (5 years ago)
Author:
emillour
Message:

Mars GCM:
Some 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:
6 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/README

    r2303 r2304  
    29822982Example : concat[diagfi2 (66sols from sol 61); diagfi4 (65sols from sol 193)]
    29832983Old output Time: [61.08,..127,|127.08,..192]; New output Time: [61.08,..127,|193.08,..258]
     2984
     2985== 28/04/2020 == EM
     2986Some code tidying: use getin_p() instead of getin() and use "call abort_physic"
     2987instead of "stop" or "call abort"
  • trunk/LMDZ.MARS/libf/phymars/aeropacity_mod.F

    r2252 r2304  
    1212     &    clearsky,totcloudfrac)
    1313                                                         
    14 ! to use  'getin'
    15       USE ioipsl_getincom, only: getin
     14      use ioipsl_getin_p_mod, only: getin_p
    1615      use tracer_mod, only: noms, igcm_h2o_ice, igcm_dust_mass,
    1716     &                      igcm_dust_submicron, rho_dust, rho_ice,
     
    2423      use tracer_mod, only: r3n_q, ref_r0, igcm_dust_number
    2524#endif
    26       use planete_h
    27       USE comcstfi_h
     25      use comcstfi_h, only: g, pi
    2826      use dimradmars_mod, only: naerkind, name_iaer,
    2927     &            iaerdust,tauvis,
     
    3230     &            iaer_stormdust_doubleq,
    3331     &            iaer_topdust_doubleq
    34       USE calcstormfract_mod
     32
    3533       IMPLICIT NONE
    3634c=======================================================================
     
    227225!       load value of tauvis from callphys.def (if given there,
    228226!       otherwise default value read from starfi.nc file will be used)
    229         call getin("tauvis",tauvis)
     227        call getin_p("tauvis",tauvis)
    230228
    231229        IF (freedust.or.rdstorm) THEN ! if rdstorm no need to held opacity constant at the first levels
     
    303301        call read_dust_scenario(ngrid,nlayer,zday,pplev,tauref)
    304302      ELSE
    305         stop 'problem with iaervar in aeropacity.F'
     303        call abort_physic("aeropacity","wrong value for iaervar",1)
    306304      ENDIF
    307305
     
    635633        write(*,*) "Add a local storm ?"
    636634        localstorm=.true. ! default value
    637         call getin("localstorm",localstorm)
     635        call getin_p("localstorm",localstorm)
    638636        write(*,*) " localstorm = ",localstorm
    639637
     
    645643          write(*,*) "ref opacity of local dust storm"
    646644              taulocref = 4.25 ! default value
    647               call getin("taulocref",taulocref)
     645              call getin_p("taulocref",taulocref)
    648646              write(*,*) " taulocref = ",taulocref
    649647
    650648          write(*,*) "target altitude of local storm (km)"
    651649              ztoploc = 10.0 ! default value
    652               call getin("ztoploc",ztoploc)
     650              call getin_p("ztoploc",ztoploc)
    653651              write(*,*) " ztoploc = ",ztoploc
    654652
    655653          write(*,*) "radius of dust storm (degree)"
    656654              radloc = 0.5 ! default value
    657               call getin("radloc",radloc)
     655              call getin_p("radloc",radloc)
    658656              write(*,*) " radloc = ",radloc
    659657
    660658          write(*,*) "center longitude of storm (deg)"
    661659              lonloc = 25.0 ! default value
    662               call getin("lonloc",lonloc)
     660              call getin_p("lonloc",lonloc)
    663661              write(*,*) " lonloc = ",lonloc
    664662
    665663          write(*,*) "center latitude of storm (deg)"
    666664              latloc = -2.5 ! default value
    667               call getin("latloc",latloc)
     665              call getin_p("latloc",latloc)
    668666              write(*,*) " latloc = ",latloc
    669667       
    670668          write(*,*) "reff storm (mic) 0. for background"
    671669              reffstorm = 0.0 ! default value
    672               call getin("reffstorm",reffstorm)
     670              call getin_p("reffstorm",reffstorm)
    673671              write(*,*) " reffstorm = ",reffstorm
    674672
  • trunk/LMDZ.MARS/libf/phymars/albedocaps.F90

    r1918 r2304  
    44! depending on the presence of CO2 ice on the surface
    55
    6 ! to use the 'getin' routine
    7 use ioipsl_getincom, only: getin
     6use ioipsl_getin_p_mod, only: getin_p
    87use geometry_mod, only: latitude ! grid point latitudes (rad)
    98use surfdat_h, only: TESicealbedo, TESice_Ncoef, TESice_Scoef, &
     
    3231  TESicealbedo=.false. ! default value
    3332  write(*,*)" albedocaps: Use TES Cap albedoes ?"
    34   call getin("TESicealbedo",TESicealbedo)
     33  call getin_p("TESicealbedo",TESicealbedo)
    3534  write(*,*)" albedocaps: TESicealbedo = ",TESicealbedo
    3635 
     
    3938    write(*,*)" albedocaps: Coefficient for Northern Cap ?"
    4039    TESice_Ncoef=1.0 ! default value
    41     call getin("TESice_Ncoef",TESice_Ncoef)
     40    call getin_p("TESice_Ncoef",TESice_Ncoef)
    4241    write(*,*)" albedocaps: TESice_Ncoef = ",TESice_Ncoef
    4342   
    4443    write(*,*)" albedocaps: Coefficient for Southern Cap ?"
    4544    TESice_Scoef=1.0 ! default value
    46     call getin("TESice_Scoef",TESice_Scoef)
     45    call getin_p("TESice_Scoef",TESice_Scoef)
    4746    write(*,*)" albedocaps: TESice_Scoef = ",TESice_Scoef
    4847  endif
     
    116115real :: lond ! longitude, in degrees
    117116integer :: i
     117character(len=20),parameter :: modname="TES_icecap_albedo"
    118118
    119119! TES datasets: (hard coded fixed length/sizes; for now)
     
    160160    write(*,*)'   can be obtained online on:'
    161161    write(*,*)'   http://www.lmd.jussieu.fr/~lmdz/planets/mars/datadir'
    162     CALL ABORT
     162    CALL abort_physic(modname,"missing input file",1)
    163163  ELSE
    164164    write(*,*) "albedocaps: using file ",trim(datadir)//"/npsc_albedo.nc"
     
    169169    write(*,*) "Failed to find longitude in file!"
    170170    write(*,*)trim(nf90_strerror(ierr))
    171     stop
     171    call abort_physic(modname,"failed finding longitude",1)
    172172  else
    173173    ierr=nf90_get_var(nid,nvarid,TESlon)
     
    175175      write(*,*) "Failed loading longitude data from file!"
    176176      write(*,*)trim(nf90_strerror(ierr))
    177       stop
     177      call abort_physic(modname,"failed loading longitude",1)
    178178    endif
    179179  endif
     
    183183    write(*,*) "Failed to find latitude in file!"
    184184    write(*,*)trim(nf90_strerror(ierr))
    185     stop
     185    call abort_physic(modname,"failed finding latitude",1)
    186186  else
    187187    ierr=nf90_get_var(nid,nvarid,TESlatn)
     
    189189      write(*,*) "Failed loading latitude data from file!"
    190190      write(*,*)trim(nf90_strerror(ierr))
    191       stop
     191      call abort_physic(modname,"failed loading latitude",1)
    192192    endif
    193193  endif
     
    197197    write(*,*) "Failed to find time in file!"
    198198    write(*,*)trim(nf90_strerror(ierr))
    199     stop
     199    call abort_physic(modname,"failed finding time",1)
    200200  else
    201201    ierr=nf90_get_var(nid,nvarid,TESls)
     
    203203      write(*,*) "Failed loading time data from file!"
    204204      write(*,*)trim(nf90_strerror(ierr))
    205       stop
     205      call abort_physic(modname,"failed loading time",1)
    206206    endif
    207207  endif
     
    211211    write(*,*) "Failed to find albedo in file!"
    212212    write(*,*)trim(nf90_strerror(ierr))
    213     stop
     213    call abort_physic(modname,"failed finding albedo",1)
    214214  else
    215215    ierr=nf90_get_var(nid,nvarid,TESalbn)
     
    217217      write(*,*) "Failed loading albedo data from file!"
    218218      write(*,*)trim(nf90_strerror(ierr))
    219       stop
     219      call abort_physic(modname,"failed loading albedo",1)
    220220    endif
    221221  endif
     
    233233    write(*,*)'   can be obtained online on:'
    234234    write(*,*)'   http://www.lmd.jussieu.fr/~lmdz/planets/mars/datadir'
    235     CALL ABORT
     235    CALL abort_physic(modname,"missing input file",1)
    236236  ELSE
    237237    write(*,*) "albedocaps: using file ",trim(datadir)//"/spsc_albedo.nc"
     
    242242    write(*,*) "Failed to find latitude in file!"
    243243    write(*,*)trim(nf90_strerror(ierr))
    244     stop
     244    call abort_physic(modname,"failed finding latitude",1)
    245245  else
    246246    ierr=nf90_get_var(nid,nvarid,TESlats)
     
    248248      write(*,*) "Failed loading latitude data from file!"
    249249      write(*,*)trim(nf90_strerror(ierr))
    250       stop
     250      call abort_physic(modname,"failed loading latitude",1)
    251251    endif
    252252  endif
     
    256256    write(*,*) "Failed to find albedo in file!"
    257257    write(*,*)trim(nf90_strerror(ierr))
    258     stop
     258    call abort_physic(modname,"failed finding albedo",1)
    259259  else
    260260    ierr=nf90_get_var(nid,nvarid,TESalbs)
     
    262262      write(*,*) "Failed loading albedo data from file!"
    263263      write(*,*)trim(nf90_strerror(ierr))
    264       stop
     264      call abort_physic(modname,"failed loading albedo",1)
    265265    endif
    266266  endif
  • trunk/LMDZ.MARS/libf/phymars/callsedim_mod.F

    r2199 r2304  
    1212     &                tau,tauscaling)
    1313
    14       USE ioipsl_getincom, only: getin
     14      USE ioipsl_getin_p_mod, only: getin_p
    1515      USE updaterad, only: updaterdust,updaterice_micro,updaterice_typ
    1616      USE tracer_mod, only: noms, igcm_dust_mass, igcm_dust_number,
     
    103103      REAL Mo,No
    104104      REAl ccntyp
    105 
     105      character(len=20),parameter :: modname="callsedim"
    106106
    107107
     
    203203          write(*,*) ' tracers for dust mass and number mixing'
    204204          write(*,*) ' ratio and doubleq is activated!'
    205           stop
     205          call abort_physic(modname,"missing dust tracers",1)
    206206        endif
    207207        ENDIF !of if (doubleq)
     
    225225            write(*,*) ' tracers for ccn mass and number mixing'
    226226            write(*,*) ' ratio and microphys is activated!'
    227             stop
     227            call abort_physic(modname,"missing ccn tracers",1)
    228228          endif
    229229        ENDIF !of if (microphys)
     
    252252            write(*,*) ' tracers for ccn co2 mass and number mixing'
    253253            write(*,*) ' ratio and co2clouds are activated!'
    254             stop
     254            call abort_physic(modname,"missing co2 ccn tracers",1)
    255255          endif
    256256       ENDIF                    !of if (co2clouds)
     
    259259         write(*,*) "correction for the shape of the ice particles ?"
    260260         beta=0.75 ! default value
    261          call getin("ice_shape",beta)
     261         call getin_p("ice_shape",beta)
    262262         write(*,*) " ice_shape = ",beta
    263263
     
    289289             write(*,*) ' tracers for stormdust mass and number mixing'
    290290             write(*,*) ' ratio and rdstorm is activated!'
    291              stop
     291             call abort_physic(modname,"missing stormdust tracers",1)
    292292           endif
    293293       ENDIF !of if (rdstorm)
     
    314314             write(*,*) ' tracers for topdust mass and number mixing'
    315315             write(*,*) ' ratio and slpwind is activated!'
    316              stop
     316             call abort_physic(modname,"missing topdust tracers",1)
    317317           endif
    318318       ENDIF !of if (slpwind)
  • trunk/LMDZ.MARS/libf/phymars/conf_phys.F

    r2281 r2304  
    3333!   declarations:
    3434!   -------------
    35 ! to use  'getin'
    36       USE ioipsl_getincom, only : getin
    3735      USE ioipsl_getin_p_mod, ONLY : getin_p
    3836      use tracer_mod, only : nuice_sed, ccn_factor, nuiceco2_sed,
     
    5452      INTEGER,INTENT(IN) :: ngrid,nlayer,nq
    5553      INTEGER ierr,j
     54      character(len=20),parameter :: modname="conf_phys"
    5655 
    5756      CHARACTER ch1*12
     
    6059      ! or shared between dynamics and physics.
    6160      ecritphy=240 ! default value
    62       call getin("ecritphy",ecritphy) ! frequency of outputs in physics,
     61      call getin_p("ecritphy",ecritphy) ! frequency of outputs in physics,
    6362                                      ! in dynamical steps
    6463      day_step=960 ! default value
    65       call getin("day_step",day_step) ! number of dynamical steps per day
     64      call getin_p("day_step",day_step) ! number of dynamical steps per day
    6665      iphysiq=20 ! default value
    67       call getin("iphysiq",iphysiq) ! call physics every iphysiq dyn step
     66      call getin_p("iphysiq",iphysiq) ! call physics every iphysiq dyn step
    6867      ecritstart=0 ! default value
    69       call getin("ecritstart",ecritstart) ! write a restart every ecristart steps
     68      call getin_p("ecritstart",ecritstart) ! write a restart every ecristart steps
    7069#endif
    7170
     
    8887         write(*,*) "Directory where external input files are:"
    8988         ! default path is set in datafile_mod
    90          call getin("datadir",datadir)
     89         call getin_p("datadir",datadir)
    9190         write(*,*) " datadir = ",trim(datadir)
    9291
     
    9897         write(*,*) "Run with or without tracer transport ?"
    9998         tracer=.false. ! default value
    100          call getin("tracer",tracer)
     99         call getin_p("tracer",tracer)
    101100         write(*,*) " tracer = ",tracer
    102101
     
    104103         write(*,*) "(if diurnal=False, diurnal averaged solar heating)"
    105104         diurnal=.true. ! default value
    106          call getin("diurnal",diurnal)
     105         call getin_p("diurnal",diurnal)
    107106         write(*,*) " diurnal = ",diurnal
    108107
     
    111110     &   "set in 'start'"
    112111         season=.true. ! default value
    113          call getin("season",season)
     112         call getin_p("season",season)
    114113         write(*,*) " season = ",season
    115114
    116115         write(*,*) "Write some extra output to the screen ?"
    117116         lwrite=.false. ! default value
    118          call getin("lwrite",lwrite)
     117         call getin_p("lwrite",lwrite)
    119118         write(*,*) " lwrite = ",lwrite
    120119
     
    125124         callstats=.true. ! default value
    126125#endif
    127          call getin("callstats",callstats)
     126         call getin_p("callstats",callstats)
    128127         write(*,*) " callstats = ",callstats
    129128
     
    131130     &              "Climate Database?"
    132131         calleofdump=.false. ! default value
    133          call getin("calleofdump",calleofdump)
     132         call getin_p("calleofdump",calleofdump)
    134133         write(*,*) " calleofdump = ",calleofdump
    135134
     
    139138     &   "=24,25 ... 30 :Mars Year 24, ... or 30 from TES assimilation"
    140139         iaervar=3 ! default value
    141          call getin("iaervar",iaervar)
     140         call getin_p("iaervar",iaervar)
    142141         write(*,*) " iaervar = ",iaervar
    143142
     
    145144     &   "(matters only if iaervar=1)"
    146145         ! NB: default value of tauvis is set/read in startfi.nc file
    147          call getin("tauvis",tauvis)
     146         call getin_p("tauvis",tauvis)
    148147         write(*,*) " tauvis = ",tauvis
    149148
     
    152151     & " =2 Viking scenario; =3 MGS scenario)"
    153152         iddist=3 ! default value
    154          call getin("iddist",iddist)
     153         call getin_p("iddist",iddist)
    155154         write(*,*) " iddist = ",iddist
    156155
    157156         write(*,*) "Dust top altitude (km). (Matters only if iddist=1)"
    158157         topdustref= 90.0 ! default value
    159          call getin("topdustref",topdustref)
     158         call getin_p("topdustref",topdustref)
    160159         write(*,*) " topdustref = ",topdustref
    161160
    162161         write(*,*) "Prescribed surface thermal flux (H/(rho*cp),K m/s)"
    163162         tke_heat_flux=0. ! default value
    164          call getin("tke_heat_flux",tke_heat_flux)
     163         call getin_p("tke_heat_flux",tke_heat_flux)
    165164         write(*,*) " tke_heat_flux = ",tke_heat_flux
    166165         write(*,*) " 0 means the usual schemes are computing"
     
    168167         write(*,*) "call radiative transfer ?"
    169168         callrad=.true. ! default value
    170          call getin("callrad",callrad)
     169         call getin_p("callrad",callrad)
    171170         write(*,*) " callrad = ",callrad
    172171
     
    178177         callslope=.false. ! default value (not supported yet)
    179178#endif
    180          call getin("callslope",callslope)
     179         call getin_p("callslope",callslope)
    181180         write(*,*) " callslope = ",callslope
    182181
     
    184183     &              "(matters only if callrad=T)"
    185184         callnlte=.false. ! default value
    186          call getin("callnlte",callnlte)
     185         call getin_p("callnlte",callnlte)
    187186         write(*,*) " callnlte = ",callnlte
    188187         
     
    193192         write(*,*) "2 -> new model"
    194193         write(*,*) "(matters only if callnlte=T)"
    195          call getin("nltemodel",nltemodel)
     194         call getin_p("nltemodel",nltemodel)
    196195         write(*,*) " nltemodel = ",nltemodel
    197196
     
    199198     &              "(matters only if callrad=T)"
    200199         callnirco2=.false. ! default value
    201          call getin("callnirco2",callnirco2)
     200         call getin_p("callnirco2",callnirco2)
    202201         write(*,*) " callnirco2 = ",callnirco2
    203202
     
    211210         nircorr=0      !default value
    212211#endif
    213          call getin("nircorr",nircorr)
     212         call getin_p("nircorr",nircorr)
    214213         write(*,*) " nircorr = ",nircorr
    215214
    216215         write(*,*) "call turbulent vertical diffusion ?"
    217216         calldifv=.true. ! default value
    218          call getin("calldifv",calldifv)
     217         call getin_p("calldifv",calldifv)
    219218         write(*,*) " calldifv = ",calldifv
    220219
    221220         write(*,*) "call thermals ?"
    222221         calltherm=.false. ! default value
    223          call getin("calltherm",calltherm)
     222         call getin_p("calltherm",calltherm)
    224223         write(*,*) " calltherm = ",calltherm
    225224
    226225         write(*,*) "call convective adjustment ?"
    227226         calladj=.true. ! default value
    228          call getin("calladj",calladj)
     227         call getin_p("calladj",calladj)
    229228         write(*,*) " calladj = ",calladj
    230229
     
    238237         write(*,*) "used latest version of yamada scheme?"
    239238         callyamada4=.true. ! default value
    240          call getin("callyamada4",callyamada4)
     239         call getin_p("callyamada4",callyamada4)
    241240         write(*,*) " callyamada4 = ",callyamada4
    242241
     
    250249         write(*,*) "call Richardson-based surface layer ?"
    251250         callrichsl=.false. ! default value
    252          call getin("callrichsl",callrichsl)
     251         call getin_p("callrichsl",callrichsl)
    253252         write(*,*) " callrichsl = ",callrichsl
    254253
     
    268267          print*,'If you want to use the Ri. surface-layer, either
    269268     & activate thermals OR de-activate the convective adjustment.'
    270           stop
     269          call abort_physic(modname,
     270     &     "Richardson layer must be used with thermals",1)
    271271         endif
    272272
    273273         write(*,*) "call CO2 condensation ?"
    274274         callcond=.true. ! default value
    275          call getin("callcond",callcond)
     275         call getin_p("callcond",callcond)
    276276         write(*,*) " callcond = ",callcond
    277277
    278278         write(*,*)"call thermal conduction in the soil ?"
    279279         callsoil=.true. ! default value
    280          call getin("callsoil",callsoil)
     280         call getin_p("callsoil",callsoil)
    281281         write(*,*) " callsoil = ",callsoil
    282282         
     
    285285     &             "scheme ?"
    286286         calllott=.true. ! default value
    287          call getin("calllott",calllott)
     287         call getin_p("calllott",calllott)
    288288         write(*,*)" calllott = ",calllott
    289289
     
    291291     &             "scheme ?"
    292292         calllott_nonoro=.false. ! default value
    293          call getin("calllott_nonoro",calllott_nonoro)
     293         call getin_p("calllott_nonoro",calllott_nonoro)
    294294         write(*,*)" calllott_nonoro = ",calllott_nonoro
    295295
     
    297297         write(*,*)"call rocket dust storm parametrization"
    298298         rdstorm=.false. ! default value
    299          call getin("rdstorm",rdstorm)
     299         call getin_p("rdstorm",rdstorm)
    300300         write(*,*)" rdstorm = ",rdstorm
    301301! rocket dust storm detrainment coefficient       
    302302        coeff_detrainment=0. ! default value
    303         call getin("coeff_detrainment",coeff_detrainment)
     303        call getin_p("coeff_detrainment",coeff_detrainment)
    304304        write(*,*)" coeff_detrainment = ",coeff_detrainment
    305305
     
    307307         write(*,*)"call slope wind lifting parametrization"
    308308         slpwind=.false. ! default value
    309          call getin("slpwind",slpwind)
     309         call getin_p("slpwind",slpwind)
    310310         write(*,*)" slpwind = ",slpwind
    311311
     
    314314     &              " /condensation of ground water ice"
    315315         latentheat_surfwater=.true. ! default value
    316          call getin("latentheat_surfwater",latentheat_surfwater)
     316         call getin_p("latentheat_surfwater",latentheat_surfwater)
    317317         write(*,*)" latentheat_surfwater = ",latentheat_surfwater
    318318
     
    320320     &             " physical timestep"
    321321         iradia=1 ! default value
    322          call getin("iradia",iradia)
     322         call getin_p("iradia",iradia)
    323323         write(*,*)" iradia = ",iradia
    324324         
     
    327327     &             "(for diagnostics only)"
    328328         callg2d=.false. ! default value
    329          call getin("callg2d",callg2d)
     329         call getin_p("callg2d",callg2d)
    330330         write(*,*)" callg2d = ",callg2d
    331331
    332332         write(*,*)"Rayleigh scattering : (should be .false. for now)"
    333333         rayleigh=.false.
    334          call getin("rayleigh",rayleigh)
     334         call getin_p("rayleigh",rayleigh)
    335335         write(*,*)" rayleigh = ",rayleigh
    336336
     
    341341         write(*,*)"Transported dust ? (if >0, use 'dustbin' dust bins)"
    342342         dustbin=0 ! default value
    343          call getin("dustbin",dustbin)
     343         call getin_p("dustbin",dustbin)
    344344         write(*,*)" dustbin = ",dustbin
    345345! active
    346346         write(*,*)"Radiatively active dust ? (matters if dustbin>0)"
    347347         active=.false. ! default value
    348          call getin("active",active)
     348         call getin_p("active",active)
    349349         write(*,*)" active = ",active
    350350
     
    354354         if (active.and.(dustbin.lt.1)) then
    355355           print*,'if active is used, then dustbin should > 0'
    356            stop
     356           call abort_physic(modname,
     357     &          "active option requires dustbin < 0",1)
    357358         endif
    358359! doubleq
     
    360361     &             " dust size ?"
    361362         doubleq=.false. ! default value
    362          call getin("doubleq",doubleq)
     363         call getin_p("doubleq",doubleq)
    363364         write(*,*)" doubleq = ",doubleq
    364365! submicron
    365366         submicron=.false. ! default value
    366          call getin("submicron",submicron)
     367         call getin_p("submicron",submicron)
    367368         write(*,*)" submicron = ",submicron
    368369
     
    372373         if (doubleq.and.(dustbin.ne.2)) then
    373374           print*,'if doubleq is used, then dustbin should be 2'
    374            stop
     375           call abort_physic(modname,
     376     &          "doubleq option requires dustbin = 2",1)
    375377         endif
    376378         if (doubleq.and.submicron.and.(nq.LT.3)) then
     
    378380           print*,' then the number of tracers has to be'
    379381           print*,' larger than 3.'
    380            stop
     382           call abort_physic(modname,
     383     &          "submicron option requires dustbin > 2",1)
    381384         endif
    382385
     
    384387         write(*,*)"dust lifted by GCM surface winds ?"
    385388         lifting=.false. ! default value
    386          call getin("lifting",lifting)
     389         call getin_p("lifting",lifting)
    387390         write(*,*)" lifting = ",lifting
    388391
     
    392395         if (lifting.and.(dustbin.lt.1)) then
    393396           print*,'if lifting is used, then dustbin should > 0'
    394            stop
     397           call abort_physic(modname,
     398     &          "lifting option requires dustbin > 0",1)
    395399         endif
    396400
    397401! dust injection scheme
    398402        dustinjection=0 ! default: no injection scheme
    399         call getin("dustinjection",dustinjection)
     403        call getin_p("dustinjection",dustinjection)
    400404        write(*,*)" dustinjection = ",dustinjection
    401405! dust injection scheme coefficient       
    402406        coeff_injection=1. ! default value
    403         call getin("coeff_injection",coeff_injection)
     407        call getin_p("coeff_injection",coeff_injection)
    404408        write(*,*)" coeff_in,jection = ",coeff_injection
    405409! timing for dust injection       
    406410        ti_injection=10. ! default value
    407411        tf_injection=12. ! default value
    408         call getin("ti_injection",ti_injection)
     412        call getin_p("ti_injection",ti_injection)
    409413        write(*,*)" ti_injection = ",ti_injection
    410         call getin("tf_injection",tf_injection)
     414        call getin_p("tf_injection",tf_injection)
    411415        write(*,*)" tf_injection = ",tf_injection
    412416
     
    415419         write(*,*)"dust lifted by GCM surface winds ?"
    416420         freedust=.false. ! default value
    417          call getin("freedust",freedust)
     421         call getin_p("freedust",freedust)
    418422         write(*,*)" freedust = ",freedust
    419423         if (freedust.and..not.doubleq) then
    420424           print*,'freedust should be used with doubleq !'
    421            stop
     425           call abort_physic(modname,
     426     &          "freedust option requires doubleq",1)
    422427         endif
    423428#ifndef MESOSCALE
     
    428433             print*,'if freedust is used and dustinjection = 0,
    429434     &      then lifting should not be used'
    430              stop
     435             call abort_physic(modname,
     436     &          "freedust option with dustinjection = 0"//
     437     &          " requires lifting",1)
    431438           endif
    432439         endif
     
    435442           if(.not.lifting) then
    436443             print*,"if dustinjection=1, then lifting should be true"
    437              stop
     444             call abort_physic(modname,
     445     &          "dustinjection=1 requires lifting",1)
    438446           endif
    439447           if(.not.freedust) then
    440448             print*,"if dustinjection=1, then freedust should be true"
    441              stop
     449             call abort_physic(modname,
     450     &          "dustinjection=1 requires freedust",1)
    442451           endif
    443452         endif
     
    448457           print*,'if rdstorm or slpwind is used, then doubleq
    449458     &            should be used !'
    450            stop
     459           call abort_physic(modname,
     460     &          "rdstorm or slpwind requires doubleq",1)
    451461         endif
    452462         if ((rdstorm.or.slpwind).and..not.active) then
    453463           print*,'if rdstorm or slpwind is used, then active
    454464     &            should be used !'
    455            stop
     465           call abort_physic(modname,
     466     &          "rdstorm or slpwind requires activ",1)
    456467         endif
    457468         if (rdstorm.and..not.lifting) then
    458469           print*,'if rdstorm is used, then lifting
    459470     &            should be used !'
    460            stop
     471           call abort_physic(modname,
     472     &          "rdstorm requires lifting",1)
    461473         endif
    462474         if ((rdstorm.or.slpwind).and..not.freedust) then
    463475           print*,'if rdstorm or slpwind is used, then freedust
    464476     &            should be used !'
    465            stop
     477           call abort_physic(modname,
     478     &          "rdstorm or slpwind requires freedust",1)
    466479         endif
    467480         if (rdstorm.and.(dustinjection.eq.0)) then
    468481           print*,'if rdstorm is used, then dustinjection
    469482     &            should be used !'
    470            stop
     483           call abort_physic(modname,
     484     &          "rdstorm requires dustinjection",1)
    471485         endif
    472486! Dust IR opacity
     
    483497         !
    484498         dustiropacity="tes" !default value - is expected to shift to mcs one day
    485          call getin("dustiropacity",dustiropacity)
     499         call getin_p("dustiropacity",dustiropacity)
    486500         write(*,*)" dustiropacity = ",trim(dustiropacity)
    487501         select case (trim(dustiropacity))
     
    493507              write(*,*) trim(dustiropacity),
    494508     &                  " is not a valid option for dustiropacity"
    495              stop
     509             call abort_physic(modname,
     510     &          "invalid dustiropacity option value",1)
    496511         end select
    497512
     
    499514         write(*,*)" dust lifted by dust devils ?"
    500515         callddevil=.false. !default value
    501          call getin("callddevil",callddevil)
     516         call getin_p("callddevil",callddevil)
    502517         write(*,*)" callddevil = ",callddevil
    503518
     
    507522         if (callddevil.and.(dustbin.lt.1)) then
    508523           print*,'if dustdevil is used, then dustbin should > 0'
    509            stop
     524           call abort_physic(modname,
     525     &          "callddevil requires dustbin > 0",1)
    510526         endif
    511527! sedimentation
    512528         write(*,*) "Gravitationnal sedimentation ?"
    513529         sedimentation=.true. ! default value
    514          call getin("sedimentation",sedimentation)
     530         call getin_p("sedimentation",sedimentation)
    515531         write(*,*) " sedimentation = ",sedimentation
    516532! activice
     
    518534     &              "water ice ?"
    519535         activice=.false. ! default value
    520          call getin("activice",activice)
     536         call getin_p("activice",activice)
    521537         write(*,*) " activice = ",activice
    522538! water
    523539         write(*,*) "Compute water cycle ?"
    524540         water=.false. ! default value
    525          call getin("water",water)
     541         call getin_p("water",water)
    526542         write(*,*) " water = ",water
    527543
     
    529545         write(*,*) "Fixed cloud fraction?"
    530546         CLFfixval=1.0 ! default value
    531          call getin("CLFfixval",CLFfixval)
     547         call getin_p("CLFfixval",CLFfixval)
    532548         write(*,*) "CLFfixval=",CLFfixval
    533549! sub-grid cloud fraction: varying
    534550         write(*,*) "Use partial nebulosity?"
    535551         CLFvarying=.false. ! default value
    536          call getin("CLFvarying",CLFvarying)
     552         call getin_p("CLFvarying",CLFvarying)
    537553         write(*,*)"CLFvarying=",CLFvarying
    538554
     
    540556         write(*,*) "Compute CO2 clouds (implies microphysical scheme)?"
    541557         co2clouds=.false. ! default value
    542          call getin("co2clouds",co2clouds)
     558         call getin_p("co2clouds",co2clouds)
    543559         write(*,*) " co2clouds = ",co2clouds
    544560!Can water ice particles serve as CCN for CO2clouds
    545561         write(*,*) "Use water ice as CO2 clouds CCN ?"
    546562         co2useh2o=.false. ! default value
    547          call getin("co2useh2o",co2useh2o)
     563         call getin_p("co2useh2o",co2useh2o)
    548564         write(*,*) " co2useh2o = ",co2useh2o
    549565!Do we allow a supply of meteoritic paricles to serve as CO2 ice CCN?
    550566         write(*,*) "Supply meteoritic particle for CO2 clouds ?"
    551567         meteo_flux=.false. !Default value
    552          call getin("meteo_flux",meteo_flux)
     568         call getin_p("meteo_flux",meteo_flux)
    553569         write(*,*)  " meteo_flux = ",meteo_flux
    554570!Do we allow a sub-grid temperature distribution for the CO2 microphysics
    555571         write(*,*) "sub-grid temperature distribution for CO2 clouds?"
    556572         CLFvaryingCO2=.false. !Default value
    557          call getin("CLFvaryingCO2",CLFvaryingCO2)
     573         call getin_p("CLFvaryingCO2",CLFvaryingCO2)
    558574         write(*,*)  " CLFvaryingCO2 = ",CLFvaryingCO2
    559575!Amplitude of the sub-grid temperature distribution for the CO2 microphysics
    560576         write(*,*) "sub-grid temperature amplitude for CO2 clouds?"
    561577         spantCO2=0 !Default value
    562          call getin("spantCO2",spantCO2)
     578         call getin_p("spantCO2",spantCO2)
    563579         write(*,*)  " spantCO2 = ",spantCO2
    564580!Do you want to filter the sub-grid T distribution by a Saturation index?
    565581         write(*,*) "filter sub-grid temperature by Saturation index?"
    566582         satindexco2=.true.
    567          call getin("satindexco2",satindexco2)
     583         call getin_p("satindexco2",satindexco2)
    568584         write(*,*)  " satindexco2 = ",satindexco2
    569585
     
    572588         write(*,*) "Activate the thermal inertia feedback ?"
    573589         tifeedback=.false. ! default value
    574          call getin("tifeedback",tifeedback)
     590         call getin_p("tifeedback",tifeedback)
    575591         write(*,*) " tifeedback = ",tifeedback
    576592
     
    580596           print*,'if tifeedback is used,'
    581597           print*,'water should be used too'
    582            stop
     598           call abort_physic(modname,
     599     &          "tifeedback requires water",1)
    583600         endif
    584601
     
    586603           print*,'if tifeedback is used,'
    587604           print*,'callsoil should be used too'
    588            stop
     605           call abort_physic(modname,
     606     &          "tifeedback requires callsoil",1)
    589607         endif
    590608
    591609         if (activice.and..not.water) then
    592610           print*,'if activice is used, water should be used too'
    593            stop
     611           call abort_physic(modname,
     612     &          "activeice requires water",1)
    594613         endif
    595614
    596615         if (water.and..not.tracer) then
    597616           print*,'if water is used, tracer should be used too'
    598            stop
     617           call abort_physic(modname,
     618     &          "water requires tracer",1)
    599619         endif
    600620         
     
    602622        write(*,*) "Sed effective variance for water ice clouds ?"
    603623        nuice_sed=0.45
    604         call getin("nuice_sed",nuice_sed)
     624        call getin_p("nuice_sed",nuice_sed)
    605625        write(*,*) "water_param nueff Sedimentation:", nuice_sed
    606626             
    607627        write(*,*) "Sed effective variance for CO2 clouds ?"
    608628        nuiceco2_sed=0.45
    609         call getin("nuiceco2_sed",nuiceco2_sed)
     629        call getin_p("nuiceco2_sed",nuiceco2_sed)
    610630        write(*,*) "CO2 nueff Sedimentation:", nuiceco2_sed
    611631 
    612632        write(*,*) "REF effective variance for CO2 clouds ?"
    613633        nuiceco2_ref=0.45
    614         call getin("nuiceco2_ref",nuiceco2_ref)
     634        call getin_p("nuiceco2_ref",nuiceco2_ref)
    615635        write(*,*) "CO2 nueff Sedimentation:", nuiceco2_ref
    616636
    617637        write(*,*) "REF effective variance for water clouds ?"
    618638        nuice_ref=0.45
    619         call getin("nuice_ref",nuice_ref)
     639        call getin_p("nuice_ref",nuice_ref)
    620640        write(*,*) "CO2 nueff Sedimentation:", nuice_ref
    621641
     
    624644        write(*,*) "water param CCN reduc. factor ?"
    625645        ccn_factor = 4.5
    626         call getin("ccn_factor",ccn_factor)
     646        call getin_p("ccn_factor",ccn_factor)
    627647        write(*,*)" ccn_factor = ",ccn_factor
    628648        write(*,*)"Careful: only used when microphys=F, otherwise"
     
    632652        write(*,*)"Microphysical scheme for water-ice clouds?"
    633653        microphys=.false.       ! default value
    634         call getin("microphys",microphys)
     654        call getin_p("microphys",microphys)
    635655        write(*,*)" microphys = ",microphys
    636656
     
    638658        write(*,*)"Allow super-saturation of water vapor?"
    639659        supersat=.true.         ! default value
    640         call getin("supersat",supersat)
     660        call getin_p("supersat",supersat)
    641661        write(*,*)"supersat = ",supersat
    642662
     
    644664        write(*,*) "water contact parameter ?"
    645665        mteta  = 0.95
    646         call getin("mteta",mteta)
     666        call getin_p("mteta",mteta)
    647667        write(*,*) "mteta = ", mteta
    648668       
     
    650670        write(*,*)"Dust scavenging by H2O/CO2 snowfall ?"
    651671        scavenging=.false.      ! default value
    652         call getin("scavenging",scavenging)
     672        call getin_p("scavenging",scavenging)
    653673        write(*,*)" scavenging = ",scavenging
    654674         
     
    661681           print*,'if microphys is used, then doubleq,'
    662682           print*,'and water must be used!'
    663            stop
     683           call abort_physic(modname,
     684     &          "microphys requires water and doubleq",1)
    664685        endif
    665686        if (microphys.and..not.scavenging) then
     
    675696           print*,'if scavenging is used, then microphys'
    676697           print*,'must be used!'
    677            stop
     698           call abort_physic(modname,
     699     &          "scavenging requires microphys",1)
    678700        endif
    679701
     
    682704        write(*,*)"Dust scavenging by instantaneous CO2 snowfall ?"
    683705        scavco2cond=.false.      ! default value
    684         call getin("scavco2cond",scavco2cond)
     706        call getin_p("scavco2cond",scavco2cond)
    685707        write(*,*)" scavco2cond = ",scavco2cond
    686708! Test of incompatibility:
     
    688710        if (scavco2cond.and.(dustbin.lt.1))then
    689711           print*,'if scavco2cond is used, then dustbin should be > 0'
    690            stop
     712           call abort_physic(modname,
     713     &          "scavco2cond requires dustbin > 0",1)
    691714        endif
    692715! if co2clouds is used, then there is no need for scavco2cond
     
    698721           print*,'----------------WARNING-----------------'
    699722           print*,''
    700            stop
     723           call abort_physic(modname,
     724     &          "incompatible co2cloud and scavco2cond options",1)
    701725        endif
    702726       
     
    708732     &   "and South pole is a cold trap)"
    709733         caps=.true. ! default value
    710          call getin("caps",caps)
     734         call getin_p("caps",caps)
    711735         write(*,*) " caps = ",caps
    712736
     
    714738         write(*,*) "water ice albedo ?"
    715739         albedo_h2o_ice=0.45
    716          call getin("albedo_h2o_ice",albedo_h2o_ice)
     740         call getin_p("albedo_h2o_ice",albedo_h2o_ice)
    717741         write(*,*) " albedo_h2o_ice = ",albedo_h2o_ice
    718742! inert_h2o_ice
    719743         write(*,*) "water ice thermal inertia ?"
    720744         inert_h2o_ice=2400 ! (J.m^-2.K^-1.s^-1/2)
    721          call getin("inert_h2o_ice",inert_h2o_ice)
     745         call getin_p("inert_h2o_ice",inert_h2o_ice)
    722746         write(*,*) " inert_h2o_ice = ",inert_h2o_ice
    723747! frost_albedo_threshold
    724748         write(*,*) "frost thickness threshold for albedo ?"
    725749         frost_albedo_threshold=0.005 ! 5.4 mic (i.e 0.005 kg.m-2)
    726          call getin("frost_albedo_threshold",
     750         call getin_p("frost_albedo_threshold",
    727751     &    frost_albedo_threshold)
    728752         write(*,*) " frost_albedo_threshold = ",
     
    732756         write(*,*) "Titus crocus line ?"
    733757         tituscap=.false.  ! default value
    734          call getin("tituscap",tituscap)
     758         call getin_p("tituscap",tituscap)
    735759         write(*,*) "tituscap",tituscap
    736760                     
     
    738762         write(*,*) "photochemistry: include chemical species"
    739763         photochem=.false. ! default value
    740          call getin("photochem",photochem)
     764         call getin_p("photochem",photochem)
    741765         write(*,*) " photochem = ",photochem
    742766         
     
    744768     &   "every ichemistry physics step (default: ichemistry=1)"
    745769         ichemistry=1
    746          call getin("ichemistry",ichemistry)
     770         call getin_p("ichemistry",ichemistry)
    747771         write(*,*) " ichemistry = ",ichemistry
    748772
     
    751775         write(*,*) "how many scatterers?"
    752776         naerkind=1 ! default value
    753          call getin("naerkind",naerkind)
     777         call getin_p("naerkind",naerkind)
    754778         write(*,*)" naerkind = ",naerkind
    755779
     
    761785           WRITE(*,*) 'to TRUE, and "naerkind" must be at least'
    762786           WRITE(*,*) 'equal to 2.'
    763            CALL ABORT
     787           call abort_physic(modname,
     788     &          "radiatively active dust and water"//
     789     &          " require naerkind > 1",1)
    764790         ENDIF
    765791
     
    807833         write(*,*) "call thermosphere ?"
    808834         callthermos=.false. ! default value
    809          call getin("callthermos",callthermos)
     835         call getin_p("callthermos",callthermos)
    810836         write(*,*) " callthermos = ",callthermos
    811837         
     
    814840     &              "(only if water=.false.)"
    815841         thermoswater=.false. ! default value
    816          call getin("thermoswater",thermoswater)
     842         call getin_p("thermoswater",thermoswater)
    817843         write(*,*) " thermoswater = ",thermoswater
    818844
     
    820846     &    " (only if callthermos=.true.)"
    821847         callconduct=.false. ! default value
    822          call getin("callconduct",callconduct)
     848         call getin_p("callconduct",callconduct)
    823849         write(*,*) " callconduct = ",callconduct
    824850
     
    826852     &   " (only if callthermos=.true.)"
    827853         calleuv=.false.  ! default value
    828          call getin("calleuv",calleuv)
     854         call getin_p("calleuv",calleuv)
    829855         write(*,*) " calleuv = ",calleuv
    830856
     
    832858     &   " (only if callthermos=.true.)"
    833859         callmolvis=.false. ! default value
    834          call getin("callmolvis",callmolvis)
     860         call getin_p("callmolvis",callmolvis)
    835861         write(*,*) " callmolvis = ",callmolvis
    836862
     
    838864     &   " (only if callthermos=.true.)"
    839865         callmoldiff=.false. ! default value
    840          call getin("callmoldiff",callmoldiff)
     866         call getin_p("callmoldiff",callmoldiff)
    841867         write(*,*) " callmoldiff = ",callmoldiff
    842868         
     
    845871     &   " (only if callthermos=.true.)"
    846872         thermochem=.false. ! default value
    847          call getin("thermochem",thermochem)
     873         call getin_p("thermochem",thermochem)
    848874         write(*,*) " thermochem = ",thermochem
    849875
     
    852878     &          "1-> daily evolution of E10.7 (for given solvaryear)"
    853879         solvarmod=1
    854          call getin("solvarmod",solvarmod)
     880         call getin_p("solvarmod",solvarmod)
    855881         write(*,*) " solvarmod = ",solvarmod
    856882
     
    858884         write(*,*) " (min=80 , ave=140, max=320)"
    859885         fixed_euv_value=140 ! default value
    860          call getin("fixed_euv_value",fixed_euv_value)
     886         call getin_p("fixed_euv_value",fixed_euv_value)
    861887         write(*,*) " fixed_euv_value = ",fixed_euv_value
    862888         
     
    864890         write(*,*) "Only if solvarmod=1"
    865891         solvaryear=24
    866          call getin("solvaryear",solvaryear)
     892         call getin_p("solvaryear",solvaryear)
    867893         write(*,*) " solvaryear = ",solvaryear
    868894
     
    871897     &   "lower values may be used to compensate low 15 um cooling"
    872898         euveff=0.21 !default value
    873          call getin("euveff",euveff)
     899         call getin_p("euveff",euveff)
    874900         write(*,*) " euveff = ", euveff
    875901
     
    878904           if (thermoswater) then
    879905             print*,'if thermoswater is set, callthermos must be true'
    880              stop
     906             call abort_physic(modname,
     907     &          "thermoswater requires callthermos",1)
    881908           endif         
    882909           if (callconduct) then
    883910             print*,'if callconduct is set, callthermos must be true'
    884              stop
     911             call abort_physic(modname,
     912     &          "callconduct requires callthermos",1)
    885913           endif       
    886914           if (calleuv) then
    887915             print*,'if calleuv is set, callthermos must be true'
    888              stop
     916             call abort_physic(modname,
     917     &          "calleuv requires callthermos",1)
    889918           endif         
    890919           if (callmolvis) then
    891920             print*,'if callmolvis is set, callthermos must be true'
    892              stop
     921             call abort_physic(modname,
     922     &          "callmolvis requires callthermos",1)
    893923           endif       
    894924           if (callmoldiff) then
    895925             print*,'if callmoldiff is set, callthermos must be true'
    896              stop
     926             call abort_physic(modname,
     927     &          "callmoldiff requires callthermos",1)
    897928           endif         
    898929           if (thermochem) then
    899930             print*,'if thermochem is set, callthermos must be true'
    900              stop
     931             call abort_physic(modname,
     932     &          "thermochem requires callthermos",1)
    901933           endif         
    902934        endif
     
    907939         if (photochem.and..not.water) then
    908940           print*,'if photochem is used, water should be used too'
    909            stop
     941           call abort_physic(modname,
     942     &          "photochem requires water",1)
    910943         endif
    911944
     
    917950             print*,'if callthermos is used, water or thermoswater
    918951     &               should be used too'
    919              stop
     952             call abort_physic(modname,
     953     &          "callthermos requires water or thermoswater",1)
    920954           endif
    921955         endif
     
    927961         write(*,*)
    928962         write(*,*) 'Cannot read file callphys.def. Is it here ?'
    929          stop
     963         call abort_physic(modname,
     964     &          "missing callphys.def file",1)
    930965      ENDIF
    931966
  • trunk/LMDZ.MARS/libf/phymars/improvedclouds_mod.F

    r2151 r2304  
    99     &             pqeff,sum_subpdq,subpdqcloud,subpdtcloud,
    1010     &             nq,tauscaling)
    11 ! to use  'getin'
    12       USE ioipsl_getincom
    13       USE updaterad
     11      USE updaterad, ONLY: updaterice_micro, updaterccn
    1412      USE watersat_mod, ONLY: watersat
    1513      use tracer_mod, only: rho_ice, nuice_sed, igcm_h2o_vap,
     
    1816     &                      igcm_ccn_number
    1917      use conc_mod, only: mmean
    20       USE comcstfi_h
     18      use comcstfi_h, only: pi, cpp
    2119      implicit none
    2220     
Note: See TracChangeset for help on using the changeset viewer.