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

Contents of /trunk/dyn3d/Guide/conf_guide.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 210 - (show annotations)
Tue Dec 13 16:02:23 2016 UTC (7 years, 6 months ago) by guez
Original Path: trunk/Sources/dyn3d/Guide/conf_guide.f
File size: 2316 byte(s)
Replaced explicit Euler integration of nudged fields by exact
integration (following LMDZ revision 2134).

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
15 LOGICAL:: ini_anal = .false. ! Initial = analyse
16 LOGICAL:: guide_u = .false. ! guidage de u
17 LOGICAL:: guide_v = .false. ! gvidage de v
18 LOGICAL:: guide_t = .false. ! guidage de T
19 LOGICAL:: guide_q = .false. ! guidage de q
20
21 logical:: online = .true. ! contr\^ole du guidage
22 ! hors-ligne: x = x_rea
23
24 ! Dans le cas où on n'a les analyses que sur une bande de latitudes :
25 REAL, save:: lat_min_guide ! minimum latitude for nudging, in rad
26 real, save:: lat_max_guide ! maximum latitude for nudging, in rad
27
28 logical, save:: ok_guide ! guidage
29 REAL, save:: factt ! pas de temps entre deux appels au guidage, en jours
30
31 contains
32
33 SUBROUTINE conf_guide
34
35 ! From LMDZ4/libf/dyn3d/conf_guide.F, version 1.1.1.1 2004/05/19 12:53:07
36 ! Parametres de controle du run:
37
38 use abort_gcm_m, only: abort_gcm
39 use comconst, only: daysec, dtvr
40 use conf_gcm_m, only: day_step, iperiod
41 use nr_util, only: assert, pi
42 use unit_nml_m, only: unit_nml
43
44 ! Local:
45
46 REAL:: lat_min_guide_deg = -90. ! in degrees
47 real:: lat_max_guide_deg = 90. ! in degrees
48
49 namelist /conf_guide_nml/ ini_anal, guide_u, guide_v, guide_t, guide_q, &
50 online, tau_min_u, tau_max_u, tau_min_v, tau_max_v, tau_min_t, &
51 tau_max_t, tau_min_q, tau_max_q, lat_min_guide_deg, lat_max_guide_deg
52
53 !-----------------------------------------------------------------------
54
55 print *, "Call sequence information: conf_guide"
56
57 print *, "Enter namelist 'conf_guide_nml'."
58 read(unit=*, nml=conf_guide_nml)
59 write(unit_nml, nml=conf_guide_nml)
60
61 lat_min_guide = lat_min_guide_deg / 180. * pi
62 lat_max_guide = lat_max_guide_deg / 180. * pi
63
64 ok_guide = any((/guide_u, guide_v, guide_t, guide_q/))
65 if (ok_guide .and. mod(day_step, 4 * iperiod) /= 0) call &
66 abort_gcm("conf_guide", 'ok_guide day_step iperiod')
67
68 if (ok_guide .and. online) then
69 factt = dtvr * iperiod / daysec
70 print *, "factt = ", factt
71 end if
72
73 end SUBROUTINE conf_guide
74
75 end module conf_guide_m

  ViewVC Help
Powered by ViewVC 1.1.21