/[lmdze]/trunk/Sources/dyn3d/Guide/conf_guide.f
ViewVC logotype

Contents of /trunk/Sources/dyn3d/Guide/conf_guide.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 140 - (show annotations)
Fri Jun 5 18:58:06 2015 UTC (8 years, 11 months ago) by guez
File size: 3034 byte(s)
Changed unit of variables lat_min_guide and lat_max_guide from module
conf_guide_m from degrees to rad. Then we do not have to convert the
whole array rlat from rad to degrees in SUBROUTINE tau2alpha.

Removed some useless computations in inigeom.

Removed module coefils. Moved variables sddv, unsddv, sddu, unsddu,
eignfnu, eignfnv of module coefils to module inifgn_m. Downgraded
variables coefilu, coefilu2, coefilv, coefilv2, modfrstu, modfrstv of
module coefils to local variables of SUBROUTINE inifilr.

Write and read a 3-dimensional variable Tsoil in restartphy.nc and
startphy.nc instead of multiple variables for the different
subs-urfaces and soil layers. This does not allow any longer to
provide only the surface value in startphy.nc and spread it to other
layers. Instead, if necessary, pre-process the file startphy.nc to
spread the surface value.

1 module conf_guide_m
2
3 IMPLICIT NONE
4
5 ! Constantes de rappel, en jours :
6 REAL:: tau_min_u = 0.03
7 REAL:: tau_max_u = 10.
8 REAL:: tau_min_v = 0.03
9 REAL:: tau_max_v = 10.
10 REAL:: tau_min_t = 0.03
11 REAL:: tau_max_t = 10.
12 REAL:: tau_min_q = 0.03
13 REAL:: tau_max_q = 10.
14 REAL:: tau_min_p = 0.03
15 REAL:: tau_max_p = 10.
16
17 LOGICAL:: ncep = .false. ! Coordonnee vert NCEP ou ECMWF
18 LOGICAL:: ini_anal = .false. ! Initial = analyse
19 LOGICAL:: guide_u = .false. ! guidage de u
20 LOGICAL:: guide_v = .false. ! gvidage de v
21 LOGICAL:: guide_t = .false. ! guidage de T
22 LOGICAL:: guide_q = .false. ! guidage de q
23
24 logical:: online = .true. ! controle du guide
25 ! hors-ligne: x=x_rea
26
27 ! Dans le cas où on n'a les analyses que sur une bande de latitudes :
28 REAL, save:: lat_min_guide ! minimum latitude for nudging, in rad
29 real, save:: lat_max_guide ! maximum latitude for nudging, in rad
30
31 logical, save:: ok_guide ! guidage
32 REAL, save:: factt ! pas de temps entre deux appels au guidage, en jours
33
34 contains
35
36 SUBROUTINE conf_guide
37
38 ! From LMDZ4/libf/dyn3d/conf_guide.F, version 1.1.1.1 2004/05/19 12:53:07
39 ! Parametres de controle du run:
40
41 use abort_gcm_m, only: abort_gcm
42 use comconst, only: daysec, dtvr
43 use conf_gcm_m, only: day_step, iperiod
44 use dynetat0_m, only: grossismx, grossismy
45 use nr_util, only: assert, pi
46 use unit_nml_m, only: unit_nml
47
48 ! Local:
49
50 REAL:: lat_min_guide_deg = -90. ! in degrees
51 real:: lat_max_guide_deg = 90. ! in degrees
52
53 namelist /conf_guide_nml/ ncep, ini_anal, guide_u, guide_v, guide_t, &
54 guide_q, online, tau_min_u, tau_max_u, tau_min_v, tau_max_v, &
55 tau_min_t, tau_max_t, tau_min_q, tau_max_q, tau_min_p, tau_max_p, &
56 lat_min_guide_deg, lat_max_guide_deg
57
58 !-----------------------------------------------------------------------
59
60 print *, "Call sequence information: conf_guide"
61
62 print *, "Enter namelist 'conf_guide_nml'."
63 read(unit=*, nml=conf_guide_nml)
64 write(unit_nml, nml=conf_guide_nml)
65
66 lat_min_guide = lat_min_guide_deg / 180. * pi
67 lat_max_guide = lat_max_guide_deg / 180. * pi
68
69 ok_guide = any((/guide_u, guide_v, guide_t, guide_q/))
70 if (ok_guide .and. mod(day_step, 4 * iperiod) /= 0) call &
71 abort_gcm(modname = "conf_guide", &
72 message = 'ok_guide day_step iperiod', ierr = 1)
73
74 if (ok_guide .and. online) then
75 factt = dtvr * iperiod / daysec
76 print *, "factt = ", factt
77 if (abs(grossismx - 1.) >= 0.1 .and. abs(grossismy - 1.) >= 0.1) then
78 if (guide_u) call assert(factt / tau_min_u < 1, &
79 "conf_guide tau_min_u")
80 if (guide_v) call assert(factt / tau_min_v < 1, &
81 "conf_guide tau_min_v")
82 if (guide_t) call assert(factt / tau_min_t < 1, &
83 "conf_guide tau_min_t")
84 if (guide_q) call assert(factt / tau_min_q < 1, &
85 "conf_guide tau_min_q")
86 end if
87 end if
88
89 end SUBROUTINE conf_guide
90
91 end module conf_guide_m

  ViewVC Help
Powered by ViewVC 1.1.21