Changeset 2486 for trunk/LMDZ.VENUS


Ignore:
Timestamp:
Mar 26, 2021, 9:31:26 AM (4 years ago)
Author:
emillour
Message:

Venus GCM:
Cleanup radlwsw_newtoncool (make it a module in the process) and modify it so that the temperature field towards wich the relmaxation will be done is built using "presnivs" (average model level pressure) and not the GCM's actual pressure field at the first step of the simulation.
With this change, one has 1+1=2 when runing with flag "physideal".
EM

Location:
trunk/LMDZ.VENUS/libf/phyvenus
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.VENUS/libf/phyvenus/physiq_mod.F

    r2464 r2486  
    7171      USE param_v4_h
    7272      USE compo_hedin83_mod2
     73      use radlwsw_newtoncool_mod, only: radlwsw_newtoncool
    7374!      use ieee_arithmetic
    7475      use time_phylmdz_mod, only: annee_ref, day_ref, itau_phy
     
    15011502c       ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    15021503      if (physideal) then
    1503        CALL radlwsw_newtoncool
    1504      e            (dist, rmu0, fract, zzlev,
    1505      e             paprs, pplay,ftsol, t_seri)
     1504       CALL radlwsw_newtoncool(presnivs,t_seri)
    15061505      else
    15071506       CALL radlwsw
  • trunk/LMDZ.VENUS/libf/phyvenus/radlwsw_NewtonCool.F

    r2135 r2486  
    22! $Header: /home/cvsroot/LMDZ4/libf/phylmd/radlwsw.F,v 1.2 2004/10/27 10:14:46 lmdzadmin Exp $
    33!
    4       SUBROUTINE radlwsw_newtoncool(dist, rmu0, fract, zzlev,
    5      .                  paprs, pplay,tsol, pt)
     4      MODULE radlwsw_newtoncool_mod
     5     
     6      implicit none
     7     
     8      contains
     9     
     10      SUBROUTINE radlwsw_newtoncool(presnivs,pt)
    611     
    712c======================================================================
    8 c Auteur(s): Z.X. Li (LMD/CNRS) date: 19960719
    9 c Objet: interface entre le modele et les rayonnements
    10 c Arguments:
    11 c dist-----input-R- distance astronomique terre-soleil
    12 c rmu0-----input-R- cosinus de l'angle zenithal
    13 c fract----input-R- duree d'ensoleillement normalisee
    14 c paprs----input-R- pression a inter-couche (Pa)
    15 c pplay----input-R- pression au milieu de couche (Pa)
    16 c tsol-----input-R- temperature du sol (en K)
    17 c pt-------input-R- temperature (K)
    18 c
    19      
    2013c   S. Lebonnois    12/04/2007
    2114c  VERSION NEWTONIAN COOLING pour Venus (no diurnal cycle)
    2215c  update 01/2014
    23 
    2416c======================================================================
    25       use dimphy
     17      use dimphy, only: klon,klev
    2618      USE geometry_mod, ONLY: latitude ! in radians
    2719      USE phys_state_var_mod, only: heat,cool,radsol,
    2820     .  topsw,toplw,solsw,sollw,sollwdown,lwnet,swnet,zt_eq
    29       USE write_field_phy
     21
    3022      IMPLICIT none
    31 #include "YOMCST.h"
    32 #include "clesphys.h"
     23      include "YOMCST.h"
    3324
    3425c ARGUMENTS
    35       real rmu0(klon), fract(klon), dist
    3626 
    37       real zzlev(klon,klev+1),paprs(klon,klev+1), pplay(klon,klev)
    38       real tsol(klon)
    39       real pt(klon,klev)
     27      real,intent(in) :: presnivs(klev) ! approx. pressure of GCM levels (Pa)
     28      real,intent(in) :: pt(klon,klev) ! atmospheric temperature (K)
    4029 
    4130c LOCAL VARIABLES
     
    7160c
    7261
    73       logical firstcall
    74       data    firstcall/.true./
    75       save    firstcall
     62      logical,save :: firstcall=.true.
    7663     
    7764c  Initialisations
     
    7966
    8067      if (firstcall) then
    81 
     68        ! build zt_eq(), reference temperature field towards which to relax.
    8269        PRINT*,"******* ATTENTION, NEWTONIAN COOLING ********"
    8370
     
    9077            level = 1
    9178            do j=1,nlevCLee
    92               if (pressCLee(j).gt.pplay(i,k)) level = j
     79              if (pressCLee(j).gt.presnivs(k)) level = j
    9380            enddo
    9481           
    95             fact  = (log10(pplay(i,k))-log10(pressCLee(level)))
     82            fact  = (log10(presnivs(k))-log10(pressCLee(level)))
    9683     .        /(log10(pressCLee(level+1))-log10(pressCLee(level)))
    9784            ztemp = tempCLee(level)*(1-fact)+tempCLee(level+1)*fact
     
    10491        ENDDO !i
    10592
     93        firstcall = .false.
    10694      endif ! firstcall
    10795     
     
    133121c+++++++ FIN BOUCLE SUR LA GRILLE +++++++++++++++++++++++++
    134122
    135       firstcall = .false.
    136       RETURN
    137       END
     123      END SUBROUTINE radlwsw_newtoncool
    138124
     125      END MODULE radlwsw_newtoncool_mod
Note: See TracChangeset for help on using the changeset viewer.