/[lmdze]/trunk/dyn3d/init_dynzon.f90
ViewVC logotype

Annotation of /trunk/dyn3d/init_dynzon.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 335 - (hide annotations)
Thu Sep 12 21:22:46 2019 UTC (4 years, 8 months ago) by guez
File size: 4010 byte(s)
Julian dates be in double precision

`ConfigureCompilerFlags.cmake` and `TAGS.cmake` are now copied into
LMDZE, to avoid dependency on the environment.

Julian dates must be in double precision, to get time step precision.

Add optional attribute to argument sec of procedure ju2ymds. We do
not need sec in procedure dynredem0.

In procedure ju2ymds, by construction, sec cannot be > `un_jour`.

Remove useless intermediary variables in procedure ymds2ju.

1 guez 57 module init_dynzon_m
2    
3     IMPLICIT NONE
4    
5     integer, parameter:: ntr = 5
6     integer, parameter:: nQ = 7
7     integer ncum, fileid
8     character(len=10) znom(ntr, nQ)
9     character(len=4), parameter:: nom(nQ) = (/'T ', 'gz ', 'K ', 'ang ', &
10     'u ', 'ovap', 'un '/)
11    
12     contains
13    
14     SUBROUTINE init_dynzon(dt_app)
15    
16     ! From LMDZ4/libf/dyn3d/bilan_dyn.F, version 1.5 2005/03/16 10:12:17
17    
18 guez 62 USE conf_gcm_m, ONLY: day_step, iperiod, periodav
19 guez 265 USE dimensions, ONLY: jjm, llm
20 guez 92 USE disvert_m, ONLY: presnivs
21 guez 313 use dynetat0_m, only: rlatv, itau_dyn
22     use dynetat0_chosen_m, only: day_ref, annee_ref
23 guez 62 USE histbeg_totreg_m, ONLY: histbeg_totreg
24     USE histdef_m, ONLY: histdef
25     USE histend_m, ONLY: histend
26     USE histvert_m, ONLY: histvert
27 guez 92 USE nr_util, ONLY: pi
28     USE ymds2ju_m, ONLY: ymds2ju
29 guez 57
30     real, intent(in):: dt_app
31    
32     ! Local:
33    
34     real dt_cum
35     character(len=5), parameter:: unites(nQ) = (/'K ', 'm2/s2', 'm2/s2', &
36     'ang ', 'm/s ', 'kg/kg', 'un '/)
37    
38 guez 62 ! Champs de tansport en moyenne zonale
39 guez 57 integer itr
40 guez 62 character(len=26) noml(ntr, nQ)
41 guez 57 character(len=12) zunites(ntr, nQ)
42     character(len=3), parameter:: ctrs(ntr) = (/' ', 'TOT', 'MMC', 'TRS', &
43     'STN'/)
44     integer iQ
45    
46     ! Initialisation du fichier contenant les moyennes zonales.
47    
48 guez 62 integer horiid, vertiid
49 guez 335 double precision julian
50 guez 57 real rlong(jjm), rlatg(jjm)
51    
52     !-----------------------------------------------------------------
53    
54     print *, "Call sequence information: init_dynzon"
55    
56 guez 62 ! Initialisation des fichiers
57 guez 57 ! ncum est la frequence de stokage en pas de temps
58     ncum = day_step / iperiod * periodav
59     dt_cum = ncum * dt_app
60    
61     ! Initialisation du fichier contenant les moyennes zonales
62    
63 guez 129 CALL ymds2ju(annee_ref, 1, day_ref, 0.0, julian)
64 guez 57
65     rlong = 0.
66 guez 62 rlatg = rlatv * 180. / pi
67 guez 57
68     call histbeg_totreg('dynzon', rlong(:1), rlatg, 1, 1, 1, jjm, itau_dyn, &
69 guez 62 julian, dt_cum, horiid, fileid)
70 guez 57
71 guez 139 ! Appel \`a histvert pour la grille verticale
72 guez 57
73 guez 67 call histvert(fileid, 'presnivs', 'Niveaux sigma', 'mb', presnivs, vertiid)
74 guez 57
75 guez 139 ! Appels \`a histdef pour la d\'efinition des variables \`a sauvegarder
76 guez 57 do iQ = 1, nQ
77     do itr = 1, ntr
78     if (itr == 1) then
79     znom(itr, iQ) = nom(iQ)
80 guez 62 noml(itr, iQ) = nom(iQ)
81 guez 57 zunites(itr, iQ) = unites(iQ)
82     else
83 guez 62 znom(itr, iQ) = ctrs(itr) // 'v' // nom(iQ)
84     noml(itr, iQ) = 'transport: v * ' // nom(iQ) // ' ' // ctrs(itr)
85     zunites(itr, iQ) = 'm/s * ' // unites(iQ)
86 guez 57 endif
87     enddo
88     enddo
89    
90 guez 139 ! D\'eclarations des champs avec dimension verticale
91 guez 57 do iQ = 1, nQ
92     do itr = 1, ntr
93 guez 62 call histdef(fileid, znom(itr, iQ), noml(itr, iQ), &
94     zunites(itr, iQ), 1, jjm, horiid, llm, 1, llm, vertiid, &
95 guez 57 'ave(X)', dt_cum, dt_cum)
96     enddo
97 guez 139 ! D\'eclarations pour les fonctions de courant
98 guez 62 call histdef(fileid, 'psi' // nom(iQ), 'stream fn. ' // noml(2, iQ), &
99     zunites(2, iQ), 1, jjm, horiid, llm, 1, llm, vertiid, &
100 guez 57 'ave(X)', dt_cum, dt_cum)
101     enddo
102    
103 guez 139 ! D\'eclarations pour les champs de transport d'air
104 guez 62 call histdef(fileid, 'masse', 'masse', 'kg', 1, jjm, horiid, llm, 1, &
105     llm, vertiid, 'ave(X)', dt_cum, dt_cum)
106     call histdef(fileid, 'v', 'v', 'm/s', 1, jjm, horiid, llm, 1, llm, &
107     vertiid, 'ave(X)', dt_cum, dt_cum)
108 guez 139 ! D\'eclarations pour les fonctions de courant
109 guez 62 call histdef(fileid, 'psi', 'stream fn. MMC ', 'mega t/s', 1, jjm, &
110     horiid, llm, 1, llm, vertiid, 'ave(X)', dt_cum, dt_cum)
111 guez 57
112 guez 139 ! D\'eclaration des champs 1D de transport en latitude
113 guez 57 do iQ = 1, nQ
114     do itr = 2, ntr
115 guez 62 call histdef(fileid, 'a' // znom(itr, iQ), noml(itr, iQ), &
116     zunites(itr, iQ), 1, jjm, horiid, 1, 1, 1, -99, 'ave(X)', &
117     dt_cum, dt_cum)
118 guez 57 enddo
119     enddo
120    
121     CALL histend(fileid)
122    
123     end SUBROUTINE init_dynzon
124    
125     end module init_dynzon_m

  ViewVC Help
Powered by ViewVC 1.1.21