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

Contents of /trunk/libf/phylmd/CV3_routines/cv3_param.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: 2497 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 ! $Header: /home/cvsroot/LMDZ4/libf/phylmd/cv3_routines.F,v 1.5 2005/07/11 15:20:02 lmdzadmin Exp $
3 !
4 !
5 !
6 SUBROUTINE cv3_param(nd,delt)
7 use conema3_m
8 use cvparam3
9 implicit none
10
11 !------------------------------------------------------------
12 ! Set parameters for convectL for iflag_con = 3
13 !------------------------------------------------------------
14
15 !
16 ! *** PBCRIT IS THE CRITICAL CLOUD DEPTH (MB) BENEATH WHICH THE ***
17 ! *** PRECIPITATION EFFICIENCY IS ASSUMED TO BE ZERO ***
18 ! *** PTCRIT IS THE CLOUD DEPTH (MB) ABOVE WHICH THE PRECIP. ***
19 ! *** EFFICIENCY IS ASSUMED TO BE UNITY ***
20 ! *** SIGD IS THE FRACTIONAL AREA COVERED BY UNSATURATED DNDRAFT ***
21 ! *** SPFAC IS THE FRACTION OF PRECIPITATION FALLING OUTSIDE ***
22 ! *** OF CLOUD ***
23 !
24 ! [TAU: CHARACTERISTIC TIMESCALE USED TO COMPUTE ALPHA & BETA]
25 ! *** ALPHA AND BETA ARE PARAMETERS THAT CONTROL THE RATE OF ***
26 ! *** APPROACH TO QUASI-EQUILIBRIUM ***
27 ! *** (THEIR STANDARD VALUES ARE 1.0 AND 0.96, RESPECTIVELY) ***
28 ! *** (BETA MUST BE LESS THAN OR EQUAL TO 1) ***
29 !
30 ! *** DTCRIT IS THE CRITICAL BUOYANCY (K) USED TO ADJUST THE ***
31 ! *** APPROACH TO QUASI-EQUILIBRIUM ***
32 ! *** IT MUST BE LESS THAN 0 ***
33
34
35 integer nd
36 real, intent(in):: delt ! timestep (seconds)
37
38 ! noff: integer limit for convection (nd-noff)
39 ! minorig: First level of convection
40
41 ! -- limit levels for convection:
42
43 noff = 1
44 minorig = 1
45 nl=nd-noff
46 nlp=nl+1
47 nlm=nl-1
48
49 ! -- "microphysical" parameters:
50
51 sigd = 0.01
52 spfac = 0.15
53 pbcrit = 150.0
54 ptcrit = 500.0
55 !IM cf. FH epmax = 0.993
56
57 omtrain = 45.0 ! used also for snow (no disctinction rain/snow)
58
59 ! -- misc:
60
61 dtovsh = -0.2 ! dT for overshoot
62 dpbase = -40. ! definition cloud base (400m above LCL)
63 dttrig = 5. ! (loose) condition for triggering
64
65 ! -- rate of approach to quasi-equilibrium:
66
67 dtcrit = -2.0
68 tau = 8000.
69 beta = 1.0 - delt/tau
70 alpha = 1.5E-3 * delt/tau
71 ! increase alpha to compensate W decrease:
72 alpha = alpha*1.5
73
74 ! -- interface cloud parameterization:
75
76 delta=0.01 ! cld
77
78 ! -- interface with boundary-layer (gust factor): (sb)
79
80 betad=10.0 ! original value (from convect 4.3)
81
82 return
83 end

  ViewVC Help
Powered by ViewVC 1.1.21