/[lmdze]/trunk/libf/dyn3d/conf_guide.f90
ViewVC logotype

Annotation of /trunk/libf/dyn3d/conf_guide.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 44 - (hide annotations)
Wed Apr 13 12:29:18 2011 UTC (13 years, 1 month ago) by guez
File size: 2326 byte(s)
Removed argument "pdteta" of "calfis", because it was not used.

Created module "conf_guide_m", containing procedure
"conf_guide". Moved module variables from "guide_m" to "conf_guide_m".

In module "getparam", removed "ini_getparam" and "fin_getparam" from
generic interface "getpar".

Created module variables in "tau2alpha_m" to replace common "comdxdy".

1 guez 44 module conf_guide_m
2 guez 37
3 guez 44 IMPLICIT NONE
4 guez 3
5 guez 44 REAL tau_min_u, tau_max_u
6     REAL tau_min_v, tau_max_v
7     REAL tau_min_t, tau_max_t
8     REAL tau_min_q, tau_max_q
9     REAL tau_min_p, tau_max_p
10     LOGICAL ncep, ini_anal
11     LOGICAL guide_u, guide_v, guide_t, guide_q, guide_p
12     INTEGER online
13 guez 3
14 guez 44 contains
15 guez 3
16 guez 44 SUBROUTINE conf_guide
17 guez 3
18 guez 44 ! From LMDZ4/libf/dyn3d/conf_guide.F, version 1.1.1.1 2004/05/19 12:53:07
19     ! Parametres de controle du run:
20 guez 3
21 guez 44 use getparam, only: ini_getparam, getpar, fin_getparam
22     use tau2alpha_m, only: lat_max_guide, lat_min_guide
23 guez 3
24 guez 44 !-----------------------------------------------------------------------
25 guez 3
26 guez 44 print *, "Call sequence information: conf_guide"
27     call ini_getparam('guide.eff')
28 guez 3
29 guez 44 call getpar('online',1,online,'Index de controle du guide')
30     CALL getpar('ncep',.false.,ncep,'Coordonnee vert NCEP ou ECMWF')
31     CALL getpar('ini_anal',.false.,ini_anal,'Initial = analyse')
32 guez 3
33 guez 44 CALL getpar('guide_u',.true.,guide_u,'guidage de u')
34     CALL getpar('guide_v',.true.,guide_v,'guidage de v')
35     CALL getpar('guide_T',.true.,guide_T,'guidage de T')
36     CALL getpar('guide_P',.true.,guide_P,'guidage de P')
37     CALL getpar('guide_Q',.true.,guide_Q,'guidage de Q')
38    
39     ! Constantes de rappel. Unite : fraction de jour
40     CALL getpar('tau_min_u',0.02,tau_min_u,'Cste de rappel min, u')
41     CALL getpar('tau_max_u', 10.,tau_max_u,'Cste de rappel max, u')
42     CALL getpar('tau_min_v',0.02,tau_min_v,'Cste de rappel min, v')
43     CALL getpar('tau_max_v', 10.,tau_max_v,'Cste de rappel max, v')
44     CALL getpar('tau_min_T',0.02,tau_min_T,'Cste de rappel min, T')
45     CALL getpar('tau_max_T', 10.,tau_max_T,'Cste de rappel max, T')
46     CALL getpar('tau_min_Q',0.02,tau_min_Q,'Cste de rappel min, Q')
47     CALL getpar('tau_max_Q', 10.,tau_max_Q,'Cste de rappel max, Q')
48     CALL getpar('tau_min_P',0.02,tau_min_P,'Cste de rappel min, P')
49     CALL getpar('tau_max_P', 10.,tau_max_P,'Cste de rappel max, P')
50    
51     ! Latitude min et max pour le rappel.
52     ! dans le cas ou on 'a les analyses que sur une bande de latitudes.
53     CALL getpar('lat_min_guide',-90.,lat_min_guide &
54     ,'Latitude minimum pour le guidage ')
55     CALL getpar('lat_max_guide', 90.,lat_max_guide &
56     ,'Latitude maximum pour le guidage ')
57    
58     CALL fin_getparam
59    
60     end SUBROUTINE conf_guide
61    
62     end module conf_guide_m

  ViewVC Help
Powered by ViewVC 1.1.21