source: LMDZ6/trunk/libf/phylmd/thermcell_env.F90 @ 4236

Last change on this file since 4236 was 4094, checked in by fhourdin, 2 years ago

Nettoyage thermiques (suite) et replay1d

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 2.1 KB
RevLine 
[4089]1   SUBROUTINE thermcell_env(ngrid,nlay,po,pt,pu,pv,pplay,  &
[1403]2     &           pplev,zo,zh,zl,ztv,zthl,zu,zv,zpspsk,pqsat,lev_out)
[878]3
4!--------------------------------------------------------------
5!thermcell_env: calcule les caracteristiques de l environnement
6!necessaires au calcul des proprietes dans le thermique
7!--------------------------------------------------------------
8
9
[4089]10   USE thermcell_ini_mod, ONLY : prt_level,RLvCp,RKAPPA,RETV
11   IMPLICIT NONE
[878]12
[4089]13! arguments
[878]14
[4089]15   integer,intent(in) :: ngrid,nlay,lev_out
16   real,intent(in), dimension(ngrid,nlay) :: po,pt,pu,pv,pplay
17   real,intent(in), dimension(ngrid,nlay+1) :: pplev
18   real,intent(out), dimension(ngrid,nlay) :: zo,zl,zh,ztv,zthl
19   real,intent(out), dimension(ngrid,nlay) :: zpspsk,zu,zv,pqsat
20   
21! Local
[878]22
[4089]23   integer ig,ll
24   real dqsat_dT
25   logical mask(ngrid,nlay)
[878]26
27
[1403]28!^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
29! Initialisations :
30!------------------
31
[4089]32   mask(:,:)=.true.
[1403]33
[878]34!
35! calcul des caracteristiques de l environnement
[4089]36   DO  ll=1,nlay
37     DO ig=1,ngrid
38        zo(ig,ll)=po(ig,ll)
39        zl(ig,ll)=0.
40        zh(ig,ll)=pt(ig,ll)
41     enddo
42   enddo
43
[1403]44! Condensation :
45!---------------
46! Calcul de l'humidite a saturation et de la condensation
47
[4089]48   call thermcell_qsat(ngrid*nlay,mask,pplev,pt,po,pqsat)
49   do ll=1,nlay
50      do ig=1,ngrid
51         zl(ig,ll) = max(0.,po(ig,ll)-pqsat(ig,ll))
52         zh(ig,ll) = pt(ig,ll)+RLvCp*zl(ig,ll)         !   T = Tl + Lv/Cp ql
53         zo(ig,ll) = po(ig,ll)-zl(ig,ll)
54      enddo
55   enddo
56
[878]57!-----------------------------------------------------------------------
[4089]58   if (prt_level.ge.1) print*,'0 OK convect8'
[878]59
[4089]60   do ll=1,nlay
61      do ig=1,ngrid
62          zpspsk(ig,ll)=(pplay(ig,ll)/100000.)**RKAPPA
63          zu(ig,ll)=pu(ig,ll)
64          zv(ig,ll)=pv(ig,ll)
[878]65!attention zh est maintenant le profil de T et plus le profil de theta !
[1403]66! Quelle horreur ! A eviter.
[878]67!   T-> Theta
[1403]68            ztv(ig,ll)=zh(ig,ll)/zpspsk(ig,ll)
[878]69!Theta_v
[1403]70            ztv(ig,ll)=ztv(ig,ll)*(1.+RETV*(zo(ig,ll))-zl(ig,ll))
[878]71!Thetal
[1403]72            zthl(ig,ll)=pt(ig,ll)/zpspsk(ig,ll)
[878]73!           
[4089]74      enddo
75   enddo
[878]76 
[4094]77 RETURN
[4089]78   END
Note: See TracBrowser for help on using the repository browser.