source: LMDZ5/trunk/libf/phylmd/thermcell_env.F90 @ 3241

Last change on this file since 3241 was 2311, checked in by Ehouarn Millour, 9 years ago

Further modifications to enforce physics/dynamics separation:

  • moved iniprint.h and misc_mod back to dyn3d_common, as these should only be used by dynamics.
  • created print_control_mod in the physics to store flags prt_level, lunout, debug to be local to physics (should be used rather than iniprint.h)
  • created abort_physic.F90 , which does the same job as abort_gcm() did, but should be used instead when in physics.
  • reactivated inifis (turned it into a module, inifis_mod.F90) to initialize physical constants and print_control_mod flags.

EM

  • 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.4 KB
RevLine 
[878]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
[2311]9      USE print_control_mod, ONLY: prt_level
[878]10      IMPLICIT NONE
11
12#include "YOMCST.h"
13#include "YOETHF.h"
14#include "FCTTRE.h"     
15
16      INTEGER ngrid,nlay
17      REAL po(ngrid,nlay)
18      REAL pt(ngrid,nlay)
19      REAL pu(ngrid,nlay)
20      REAL pv(ngrid,nlay)
21      REAL pplay(ngrid,nlay)
22      REAL pplev(ngrid,nlay+1)
23      integer lev_out                           ! niveau pour les print
24
25      REAL zo(ngrid,nlay)
26      REAL zl(ngrid,nlay)
27      REAL zh(ngrid,nlay)
28      REAL ztv(ngrid,nlay)
29      REAL zthl(ngrid,nlay)
30      REAL zpspsk(ngrid,nlay)
31      REAL zu(ngrid,nlay)
32      REAL zv(ngrid,nlay)
[1403]33      REAL pqsat(ngrid,nlay)
[878]34
[1403]35      INTEGER ig,ll
[878]36
[1403]37      real dqsat_dT
38      real RLvCp
[878]39
[1403]40logical mask(ngrid,nlay)
[970]41
[1403]42
43!^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
44! Initialisations :
45!------------------
46
47mask(:,:)=.true.
48RLvCp = RLVTT/RCPD
49
[878]50!
51! calcul des caracteristiques de l environnement
52       DO  ll=1,nlay
53         DO ig=1,ngrid
54            zo(ig,ll)=po(ig,ll)
55            zl(ig,ll)=0.
56            zh(ig,ll)=pt(ig,ll)
57         EndDO
58       EndDO
59!
60!
[1403]61! Condensation :
62!---------------
63! Calcul de l'humidite a saturation et de la condensation
64
65call thermcell_qsat(ngrid*nlay,mask,pplev,pt,po,pqsat)
66DO ll=1,nlay
67   DO ig=1,ngrid
68      zl(ig,ll) = max(0.,po(ig,ll)-pqsat(ig,ll))
69      zh(ig,ll) = pt(ig,ll)+RLvCp*zl(ig,ll)         !   T = Tl + Lv/Cp ql
70      zo(ig,ll) = po(ig,ll)-zl(ig,ll)
71   ENDDO
72ENDDO
[878]73!
74!
75!-----------------------------------------------------------------------
76
[938]77      if (prt_level.ge.1) print*,'0 OK convect8'
[878]78
[1403]79      DO ll=1,nlay
80         DO ig=1,ngrid
81             zpspsk(ig,ll)=(pplay(ig,ll)/100000.)**RKAPPA
82             zu(ig,ll)=pu(ig,ll)
83             zv(ig,ll)=pv(ig,ll)
[878]84!attention zh est maintenant le profil de T et plus le profil de theta !
[1403]85! Quelle horreur ! A eviter.
[878]86!
87!   T-> Theta
[1403]88            ztv(ig,ll)=zh(ig,ll)/zpspsk(ig,ll)
[878]89!Theta_v
[1403]90            ztv(ig,ll)=ztv(ig,ll)*(1.+RETV*(zo(ig,ll))-zl(ig,ll))
[878]91!Thetal
[1403]92            zthl(ig,ll)=pt(ig,ll)/zpspsk(ig,ll)
[878]93!           
[1403]94         ENDDO
95      ENDDO
[878]96 
97      RETURN
98      END
Note: See TracBrowser for help on using the repository browser.