Changeset 2635 for trunk/LMDZ.GENERIC


Ignore:
Timestamp:
Mar 4, 2022, 6:29:05 PM (3 years ago)
Author:
aslmd
Message:

Introduction of cpp_mugaz_mode to decide what source should be used for cpp and mugaz. Force_cpp and check_cpp_match are deprecated (see issue la-communaut-des-mod-les-atmosph-riques-plan-taires/git-trunk#27).

Location:
trunk/LMDZ.GENERIC/libf/phystd
Files:
6 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.GENERIC/libf/phystd/calc_cpp_mugaz.F90

    r1397 r2635  
    44!     Purpose
    55!     -------
    6 !     Check to see if the atmospheric specific heat capacity and
     6!     Computes atmospheric specific heat capacity and
    77!     mean molar mass for the gas mixture defined in gases.def
    8 !     corresponds to what we're using. If it doesn't, abort run
    9 !     unless option 'check_cpp_match' is set to false in
    10 !     callphys.def.
     8!     with standard values.
     9!     In 1d, one can force the model to adopt these standard values
     10!     by setting cpp_mugaz_mode=2 in callfis.def.
    1111!
    1212!     Authors
     
    1414!     Robin Wordsworth (2009)
    1515!     A. Spiga: make the routine OK with latest changes in rcm1d
     16!     Jeremy Leconte (2022)
    1617!
    1718!==================================================================
     
    1920      use gases_h
    2021      use comcstfi_mod, only: cpp, mugaz
    21       use callkeys_mod, only: check_cpp_match,force_cpp
     22      use callkeys_mod, only: cpp_mugaz_mode
     23      use mod_phys_lmdz_para, only : is_master
    2224      implicit none
    2325
     
    122124      print*,'Cp in calc_cpp_mugaz is ',cpp_c,'J kg^-1 K^-1'
    123125      print*,'Mg in calc_cpp_mugaz is ',mugaz_c,'amu'
    124       print*,'Predefined Cp in physics is ',cpp,'J kg^-1 K^-1'
    125       print*,'Predefined Mg in physics is ',mugaz,'amu'
    126126
    127       if (check_cpp_match) then
    128          print*,'REQUEST TO CHECK cpp_match :'
    129          if((abs(1.-cpp/cpp_c).gt.1.e-6) .or.  &
    130               (abs(1.-mugaz/mugaz_c).gt.1.e-6)) then
    131             ! Ehouarn: tolerate a small mismatch between computed/stored values
    132             print*,'--> Values do not match!'
    133             print*,'    Either adjust cpp / mugaz via newstart to calculated values,'
    134             print*,'    or set check_cpp_match to .false. in callphys.def.'
    135             stop
    136          else
    137             print*,'--> OK. Settings match composition.'
    138          endif
     127      if(((abs(1.-cpp/cpp_c).gt.1.e-6) .or.  &
     128           (abs(1.-mugaz/mugaz_c).gt.1.e-6)).and. is_master ) then
     129         ! Ehouarn: tolerate a small mismatch between computed/stored values
     130         print*,'--> Values do not match with the predefined one ! (',cpp,',',mugaz,')'
     131         print*,'    Because cp varies with temperature and that some gases may not appear in gases.def,'
     132         print*,'    a small discrepancy might be completely normal.'
     133         print*,'    But you might want to check that!'
     134         print*,'    If you want to use the values calculated here, adjust cpp / mugaz in the dynamics via newstart (3d)'
     135         print*,'    or use cpp_mugaz_mode=2 (if you are in 1d).'
    139136      endif
    140137
    141       if (.not.force_cpp) then
    142           print*,'*** Setting cpp & mugaz to computations in calc_cpp_mugaz.'
     138      if (cpp_mugaz_mode==2) then
     139          if (is_master) print*,'*** cpp_mugaz_mode==2, so setting cpp & mugaz to computations in calc_cpp_mugaz.'
    143140          mugaz = mugaz_c
    144141          cpp = cpp_c
    145142      else
    146           print*,'*** Setting cpp & mugaz to predefined values.'
     143          if (is_master) print*,'*** Leaving cpp & mugaz equal to predefined values'
     144          if (is_master) print*,'(either from dynamics (cpp_mugaz_mode=0) or callfis (cpp_mugaz_mode=1)).'
    147145      endif
    148146
  • trunk/LMDZ.GENERIC/libf/phystd/callkeys_mod.F90

    r2633 r2635  
    2525!$OMP THREADPRIVATE(enertest,nonideal,meanOLR,kastprof,diagdtau)
    2626      logical,save :: newtonian
    27       logical,save :: check_cpp_match
    2827      logical,save :: force_cpp
     28      integer,save :: cpp_mugaz_mode
    2929      logical,save :: testradtimes
    3030      logical,save :: rayleigh
    31 !$OMP THREADPRIVATE(newtonian,check_cpp_match,force_cpp,testradtimes,rayleigh)
     31!$OMP THREADPRIVATE(newtonian,force_cpp,cpp_mugaz_mode,testradtimes,rayleigh)
    3232      logical,save :: stelbbody
    3333      logical,save :: nearco2cond
  • trunk/LMDZ.GENERIC/libf/phystd/dyn1d/kcm1d.F90

    r2470 r2635  
    88  use comsaison_h, only: mu0, fract, dist_star
    99  use planete_mod
    10   use callkeys_mod, only: check_cpp_match, pceil, tstrat, tracer, global1d
     10  use callkeys_mod, only: pceil, tstrat, tracer, global1d
    1111  use inifis_mod, only: inifis
    1212  use comcstfi_mod
     
    267267  write(*,*) " pceil = ", pceil
    268268
    269   check_cpp_match = .false.
    270   call getin("check_cpp_match",check_cpp_match)
    271   if (check_cpp_match) then
    272      print*,"In 1D modeling, check_cpp_match is supposed to be F"
    273      print*,"Please correct callphys.def"
    274      stop
    275   endif
    276 
    277 
    278269!!! GEOGRAPHICAL INITIALIZATIONS
    279270     !!! AREA. useless in 1D
  • trunk/LMDZ.GENERIC/libf/phystd/dyn1d/rcm1d.F

    r2621 r2635  
    2323      use time_phylmdz_mod, only: daysec, dtphys, day_step, ecritphy,
    2424     &                            nday, iphysiq
    25       use callkeys_mod, only: tracer,check_cpp_match,rings_shadow,
     25      use callkeys_mod, only: tracer,rings_shadow,
    2626     &                        specOLR,water,pceil,ok_slab_ocean,photochem
    2727      USE comvert_mod, ONLY: ap,bp,aps,bps,pa,preff, sig,
     
    360360      endif ! of if (tracer)
    361361
    362 !!! We have to check that check_cpp_match is F for 1D computations
    363 !!! We think this check is better than make a particular case for 1D in inifis or calc_cpp_mugaz
    364       check_cpp_match = .false.
    365       call getin("check_cpp_match",check_cpp_match)
    366       if (check_cpp_match) then
    367           print*,"In 1D modeling, check_cpp_match is supposed to be F"
    368           print*,"Please correct callphys.def"
    369           stop
    370       endif
    371 
    372362!!! GEOGRAPHICAL INITIALIZATIONS
    373363     !!! AREA. useless in 1D
  • trunk/LMDZ.GENERIC/libf/phystd/inifis_mod.F90

    r2633 r2635  
    240240     if (is_master) write(*,*) trim(rname)//": enertest = ",enertest
    241241
    242      if (is_master) write(*,*) trim(rname)//&
    243        ": Check to see if cpp values used match gases.def ?"
    244      check_cpp_match=.true. ! default value
    245      call getin_p("check_cpp_match",check_cpp_match)
    246      if (is_master) write(*,*) trim(rname)//&
    247        ": check_cpp_match = ",check_cpp_match
    248 
    249242     if (is_master) write(*,*) trim(rname)//": call radiative transfer ?"
    250243     callrad=.true. ! default value
     
    10081001     if (is_master) write(*,*)trim(rname)//": kmixmin = ",kmixmin
    10091002
    1010      if (is_master) write(*,*)trim(rname)//&
    1011        ": Does user want to force cpp and mugaz?"
     1003     if (is_master) write(*,*)'Predefined Cp from dynamics is ',cpp,'J kg^-1 K^-1'
     1004     if (is_master) write(*,*)'Predefined Mg from dynamics is ',mugaz,'amu'
     1005
    10121006     force_cpp=.false. ! default value
    10131007     call getin_p("force_cpp",force_cpp)
    1014      if (is_master) write(*,*)trim(rname)//": force_cpp = ",force_cpp
    1015 
    10161008     if (force_cpp) then
     1009      if (is_master) write(*,*)trim(rname)//": force_cpp = ",force_cpp
     1010      if (is_master) write(*,*)trim(rname)//": force_cpp is deprecated.",&
     1011      "Set cpp_mugaz_mode=1 in callfis to emulate force_cpp=.true."
     1012      call abort_physic(rname,"Anyway, you need to set force_cpp=.false. to continue.",1)
     1013     endif
     1014
     1015     if (is_master) write(*,*)trim(rname)//&
     1016     ": where do you want your cpp/mugaz value to come from?",&
     1017     "=> 0: dynamics (3d), 1: forced in callfis (1d), 2: computed from gases.def (1d)?"
     1018     cpp_mugaz_mode = 0 ! default value
     1019     call getin_p("cpp_mugaz_mode",cpp_mugaz_mode)
     1020     if (is_master) write(*,*)trim(rname)//": cpp_mugaz_mode = ",cpp_mugaz_mode
     1021
     1022     if ((cpp_mugaz_mode >= 1).and.(is_master).and.(ngrid>1)) then
     1023        write(*,*)'    !!!!! Be aware that having different values for cpp and mugaz in the dynamics and physics'
     1024        write(*,*)'    in 3D can result in very pathological behavior. You have been warned !!!!!'
     1025     endif
     1026
     1027     if (cpp_mugaz_mode == 1) then
    10171028       mugaz = -99999.
    10181029       if (is_master) write(*,*)trim(rname)//&
     
    10201031       call getin_p("mugaz",mugaz)
    10211032       IF (mugaz.eq.-99999.) THEN
    1022          call abort_physic(rname,"mugaz must be set if force_cpp = T",1)
    1023        ELSE
    1024          if (is_master) write(*,*)trim(rname)//": mugaz=",mugaz
     1033         call abort_physic(rname,"mugaz must be set if cpp_mugaz_mode = 1",1)
    10251034       ENDIF
    10261035       cpp = -99999.
     
    10291038       call getin_p("cpp",cpp)
    10301039       IF (cpp.eq.-99999.) THEN
    1031            PRINT *, "cpp must be set if force_cpp = T"
     1040           PRINT *, "cpp must be set if cpp_mugaz_mode = 1"
    10321041           STOP
    1033        ELSE
    1034            if (is_master) write(*,*)trim(rname)//": cpp=",cpp
    10351042       ENDIF
    1036      endif ! of if (force_cpp)
     1043       if (is_master) write(*,*)'New Cp from callfis is ',cpp,'J kg^-1 K^-1'
     1044       if (is_master) write(*,*)'New Mg from callfis is ',mugaz,'amu'
     1045 
     1046     endif ! of if (cpp_mugaz_mode == 1)
    10371047     call su_gases
    10381048     call calc_cpp_mugaz
  • trunk/LMDZ.GENERIC/libf/phystd/tabfi_mod.F90

    r2548 r2635  
    6161      use comcstfi_mod, only: rad, omeg, g, mugaz, rcp, cpp, r
    6262      use time_phylmdz_mod, only: dtphys, daysec
    63       use callkeys_mod, only: check_cpp_match,force_cpp
     63      use callkeys_mod, only: cpp_mugaz_mode
    6464      implicit none
    6565 
     
    494494        else if (modif(1:len_trim(modif)).eq.'calc_cpp_mugaz') then
    495495          write(*,*) 'current value rcp, mugaz:',rcp,mugaz
    496           check_cpp_match=.false.
    497           force_cpp=.false.
    498           call su_gases
    499           call calc_cpp_mugaz
     496          cpp_mugaz_mode = 2
     497          call su_gases
     498          call calc_cpp_mugaz
    500499          write(*,*)
    501500          write(*,*) ' cpp (new value):',cpp
Note: See TracChangeset for help on using the changeset viewer.