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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 66 - (hide annotations)
Thu Sep 20 13:00:41 2012 UTC (11 years, 8 months ago) by guez
File size: 4033 byte(s)
Changed name of module "comvert" to "disvert_m". Changed constant
1. to 0.3 in vertical sampling "strato".

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     USE histbeg_totreg_m, ONLY: histbeg_totreg
20     USE histdef_m, ONLY: histdef
21     USE histend_m, ONLY: histend
22     USE histvert_m, ONLY: histvert
23     USE calendar, ONLY: ymds2ju
24     USE dimens_m, ONLY: jjm, llm
25 guez 66 USE disvert_m, ONLY: presnivs
26 guez 62 USE comgeom, ONLY: rlatv
27     USE temps, ONLY: annee_ref, day_ref, itau_dyn
28     USE nr_util, ONLY: pi
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     real julian
50     integer an, dayref
51 guez 57 real rlong(jjm), rlatg(jjm)
52    
53     !-----------------------------------------------------------------
54    
55     print *, "Call sequence information: init_dynzon"
56    
57 guez 62 ! Initialisation des fichiers
58 guez 57 ! ncum est la frequence de stokage en pas de temps
59     ncum = day_step / iperiod * periodav
60     dt_cum = ncum * dt_app
61    
62     ! Initialisation du fichier contenant les moyennes zonales
63    
64 guez 62 an = annee_ref
65 guez 57 dayref = day_ref
66 guez 62 CALL ymds2ju(an, 1, dayref, 0.0, julian)
67 guez 57
68     rlong = 0.
69 guez 62 rlatg = rlatv * 180. / pi
70 guez 57
71     call histbeg_totreg('dynzon', rlong(:1), rlatg, 1, 1, 1, jjm, itau_dyn, &
72 guez 62 julian, dt_cum, horiid, fileid)
73 guez 57
74     ! Appel à histvert pour la grille verticale
75    
76     call histvert(fileid, 'presnivs', 'Niveaux sigma', 'mb', llm, presnivs, &
77 guez 62 vertiid)
78 guez 57
79     ! Appels à histdef pour la définition des variables à sauvegarder
80     do iQ = 1, nQ
81     do itr = 1, ntr
82     if (itr == 1) then
83     znom(itr, iQ) = nom(iQ)
84 guez 62 noml(itr, iQ) = nom(iQ)
85 guez 57 zunites(itr, iQ) = unites(iQ)
86     else
87 guez 62 znom(itr, iQ) = ctrs(itr) // 'v' // nom(iQ)
88     noml(itr, iQ) = 'transport: v * ' // nom(iQ) // ' ' // ctrs(itr)
89     zunites(itr, iQ) = 'm/s * ' // unites(iQ)
90 guez 57 endif
91     enddo
92     enddo
93    
94     ! Déclarations des champs avec dimension verticale
95     do iQ = 1, nQ
96     do itr = 1, ntr
97 guez 62 call histdef(fileid, znom(itr, iQ), noml(itr, iQ), &
98     zunites(itr, iQ), 1, jjm, horiid, llm, 1, llm, vertiid, &
99 guez 57 'ave(X)', dt_cum, dt_cum)
100     enddo
101     ! Déclarations pour les fonctions de courant
102 guez 62 call histdef(fileid, 'psi' // nom(iQ), 'stream fn. ' // noml(2, iQ), &
103     zunites(2, iQ), 1, jjm, horiid, llm, 1, llm, vertiid, &
104 guez 57 'ave(X)', dt_cum, dt_cum)
105     enddo
106    
107     ! Déclarations pour les champs de transport d'air
108 guez 62 call histdef(fileid, 'masse', 'masse', 'kg', 1, jjm, horiid, llm, 1, &
109     llm, vertiid, 'ave(X)', dt_cum, dt_cum)
110     call histdef(fileid, 'v', 'v', 'm/s', 1, jjm, horiid, llm, 1, llm, &
111     vertiid, 'ave(X)', dt_cum, dt_cum)
112 guez 57 ! Déclarations pour les fonctions de courant
113 guez 62 call histdef(fileid, 'psi', 'stream fn. MMC ', 'mega t/s', 1, jjm, &
114     horiid, llm, 1, llm, vertiid, 'ave(X)', dt_cum, dt_cum)
115 guez 57
116     ! Déclaration des champs 1D de transport en latitude
117     do iQ = 1, nQ
118     do itr = 2, ntr
119 guez 62 call histdef(fileid, 'a' // znom(itr, iQ), noml(itr, iQ), &
120     zunites(itr, iQ), 1, jjm, horiid, 1, 1, 1, -99, 'ave(X)', &
121     dt_cum, dt_cum)
122 guez 57 enddo
123     enddo
124    
125     CALL histend(fileid)
126    
127     end SUBROUTINE init_dynzon
128    
129     end module init_dynzon_m

  ViewVC Help
Powered by ViewVC 1.1.21