/[lmdze]/trunk/libf/phylmd/CV3_routines/cv3_trigger.f90
ViewVC logotype

Contents of /trunk/libf/phylmd/CV3_routines/cv3_trigger.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 47 - (show annotations)
Fri Jul 1 15:00:48 2011 UTC (12 years, 10 months ago) by guez
File size: 3180 byte(s)
Split "thermcell.f" and "cv3_routines.f".
Removed copies of files that are now in "L_util".
Moved "mva9" and "diagetpq" to their own files.
Unified variable names across procedures.

1
2 SUBROUTINE cv3_trigger(len,nd,icb,plcl,p,th,tv,tvp &
3 ,pbase,buoybase,iflag,sig,w0)
4 use cvparam3
5 implicit none
6
7 !-------------------------------------------------------------------
8 ! --- TRIGGERING
9 !
10 ! - computes the cloud base
11 ! - triggering (crude in this version)
12 ! - relaxation of sig and w0 when no convection
13 !
14 ! Caution1: if no convection, we set iflag=4
15 ! (it used to be 0 in convect3)
16 !
17 ! Caution2: at this stage, tvp (and thus buoy) are know up
18 ! through icb only!
19 ! -> the buoyancy below cloud base not (yet) set to the cloud base buoyancy
20 !-------------------------------------------------------------------
21
22
23 ! input:
24 integer len, nd
25 integer icb(len)
26 real plcl(len), p(len,nd)
27 real th(len,nd), tv(len,nd), tvp(len,nd)
28
29 ! output:
30 real pbase(len), buoybase(len)
31
32 ! input AND output:
33 integer iflag(len)
34 real sig(len,nd), w0(len,nd)
35
36 ! local variables:
37 integer i,k
38 real tvpbase, tvbase, tdif, ath, ath1
39
40 !
41 ! *** set cloud base buoyancy at (plcl+dpbase) level buoyancy
42 !
43 do 100 i=1,len
44 pbase(i) = plcl(i) + dpbase
45 tvpbase = tvp(i,icb(i))*(pbase(i)-p(i,icb(i)+1)) &
46 /(p(i,icb(i))-p(i,icb(i)+1)) &
47 + tvp(i,icb(i)+1)*(p(i,icb(i))-pbase(i)) &
48 /(p(i,icb(i))-p(i,icb(i)+1))
49 tvbase = tv(i,icb(i))*(pbase(i)-p(i,icb(i)+1)) &
50 /(p(i,icb(i))-p(i,icb(i)+1)) &
51 + tv(i,icb(i)+1)*(p(i,icb(i))-pbase(i)) &
52 /(p(i,icb(i))-p(i,icb(i)+1))
53 buoybase(i) = tvpbase - tvbase
54 100 continue
55
56 !
57 ! *** make sure that column is dry adiabatic between the surface ***
58 ! *** and cloud base, and that lifted air is positively buoyant ***
59 ! *** at cloud base ***
60 ! *** if not, return to calling program after resetting ***
61 ! *** sig(i) and w0(i) ***
62 !
63
64 ! oct3 do 200 i=1,len
65 ! oct3
66 ! oct3 tdif = buoybase(i)
67 ! oct3 ath1 = th(i,1)
68 ! oct3 ath = th(i,icb(i)-1) - dttrig
69 ! oct3
70 ! oct3 if (tdif.lt.dtcrit .or. ath.gt.ath1) then
71 ! oct3 do 60 k=1,nl
72 ! oct3 sig(i,k) = beta*sig(i,k) - 2.*alpha*tdif*tdif
73 ! oct3 sig(i,k) = AMAX1(sig(i,k),0.0)
74 ! oct3 w0(i,k) = beta*w0(i,k)
75 ! oct3 60 continue
76 ! oct3 iflag(i)=4 ! pour version vectorisee
77 ! oct3c convect3 iflag(i)=0
78 ! oct3cccc return
79 ! oct3 endif
80 ! oct3
81 ! oct3200 continue
82
83 ! -- oct3: on reecrit la boucle 200 (pour la vectorisation)
84
85 do 60 k=1,nl
86 do 200 i=1,len
87
88 tdif = buoybase(i)
89 ath1 = th(i,1)
90 ath = th(i,icb(i)-1) - dttrig
91
92 if (tdif.lt.dtcrit .or. ath.gt.ath1) then
93 sig(i,k) = beta*sig(i,k) - 2.*alpha*tdif*tdif
94 sig(i,k) = AMAX1(sig(i,k),0.0)
95 w0(i,k) = beta*w0(i,k)
96 iflag(i)=4 ! pour version vectorisee
97 ! convect3 iflag(i)=0
98 endif
99
100 200 continue
101 60 continue
102
103 ! fin oct3 --
104
105 return
106 end

  ViewVC Help
Powered by ViewVC 1.1.21