/[lmdze]/trunk/libf/phylmd/CV_routines/cv_prelim.f90
ViewVC logotype

Contents of /trunk/libf/phylmd/CV_routines/cv_prelim.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 52 - (show annotations)
Fri Sep 23 12:28:01 2011 UTC (12 years, 7 months ago) by guez
File size: 1476 byte(s)
Split "conflx.f" into single-procedure files in directory "Conflx".

Split "cv_routines.f" into single-procedure files in directory
"CV_routines". Made module "cvparam" from included file
"cvparam.h". No included file other than "netcdf.inc" left in LMDZE.

1
2 SUBROUTINE cv_prelim(len,nd,ndp1,t,q,p,ph &
3 ,lv,cpn,tv,gz,h,hm)
4 use cvthermo
5 use cvparam
6 implicit none
7
8 !=====================================================================
9 ! --- CALCULATE ARRAYS OF GEOPOTENTIAL, HEAT CAPACITY & STATIC ENERGY
10 !=====================================================================
11
12 ! inputs:
13 integer len, nd, ndp1
14 real, intent(in):: t(len,nd)
15 real q(len,nd), p(len,nd), ph(len,ndp1)
16
17 ! outputs:
18 real lv(len,nd), cpn(len,nd), tv(len,nd)
19 real gz(len,nd), h(len,nd), hm(len,nd)
20
21 ! local variables:
22 integer k, i
23 real cpx(len,nd)
24
25
26
27 do 110 k=1,nlp
28 do 100 i=1,len
29 lv(i,k)= lv0-clmcpv*(t(i,k)-t0)
30 cpn(i,k)=cpd*(1.0-q(i,k))+cpv*q(i,k)
31 cpx(i,k)=cpd*(1.0-q(i,k))+cl*q(i,k)
32 tv(i,k)=t(i,k)*(1.0+q(i,k)*epsim1)
33 100 continue
34 110 continue
35 !
36 ! gz = phi at the full levels (same as p).
37 !
38 do 120 i=1,len
39 gz(i,1)=0.0
40 120 continue
41 do 140 k=2,nlp
42 do 130 i=1,len
43 gz(i,k)=gz(i,k-1)+hrd*(tv(i,k-1)+tv(i,k)) &
44 *(p(i,k-1)-p(i,k))/ph(i,k)
45 130 continue
46 140 continue
47 !
48 ! h = phi + cpT (dry static energy).
49 ! hm = phi + cp(T-Tbase)+Lq
50 !
51 do 170 k=1,nlp
52 do 160 i=1,len
53 h(i,k)=gz(i,k)+cpn(i,k)*t(i,k)
54 hm(i,k)=gz(i,k)+cpx(i,k)*(t(i,k)-t(i,1))+lv(i,k)*q(i,k)
55 160 continue
56 170 continue
57
58 return
59 end

  ViewVC Help
Powered by ViewVC 1.1.21