source: LMDZ6/trunk/libf/phylmdiso/isotrac_mod.F90 @ 4889

Last change on this file since 4889 was 4493, checked in by crisi, 14 months ago

faire planter avec un abort quand probleme d'option de water tagging

  • Property svn:executable set to *
File size: 32.6 KB
Line 
1#ifdef ISO
2#ifdef ISOTRAC
3
4MODULE isotrac_mod
5  USE infotrac_phy,      ONLY: niso, ntiso, nzone
6  USE readTracFiles_mod, ONLY: delPhase
7  USE isotopes_mod,      ONLY: ridicule, get_in
8
9  IMPLICIT NONE
10  SAVE
11
12!=== CONTENT: ALL THE ISOTOPIC TRACERS RELATED VARIABLES ===
13!
14! option 1: on trace evap ocean et continent separement 
15! option 2: on trace evap ocean, continent et evap precip
16! option 3: on trace evap differents bassins oceaniques
17!       + continents + residu
18!       attention, choisir dans ce cas les bassins oceaniques
19!       dans iso_traceurs_opt3F90.h
20! option 4: tracage par temperature minimale
21!       dans ce cas, on definit des bins dans iso_traceurs_opt4.h
22! option 5: pour AMMA: on taggue residu/AEJ/flux mousson/Harmattan
23! option 6: taggage des ddfts
24! option 7: pour Sandrine: taggage de la vapeur a 700hPa pour omega500<-20 TODO
25! option 8: pour Sandrine: taggage de la vapeur entre 950 et 800hPa, omega de 0 a 25 hPa et de l'evaoration en omega<-20. TODO
26! option 9: taggage du condensat et de la revap precip
27! option 10: taggage evap oce, transpiration et evaporation
28! fractionante. A utiliser quand on couple avec ORCHIDEE
29! option 11: comme 2, mais on trace juste revap precip et reste
30! option 12: taggage evap oce, sol nu, canop et reste evap cont.
31! A utiliser quand on couple avec ORCHIDEE
32! option 13: taggage temperature minimale + revap precip
33! option 14: taggage lat et altitude de derniere saturation (niveaux de pression) + evap surf
34! otion 15: taggage irrigation
35! option 16: taggage precip selon saisons et fonte neige: seulement pour ORCHIDEE
36! option 17: taggage temperature minimum de condensation directement dans la convection et la cond LS, + evap sfc, condensat et precipitation
37! option 18: idem 17 mais on tague qsmin au lieu de Tmin
38! option 19: on tag vap residuelle, vap residuelle dans ddfts, sfc, cond, rev
39! option 20: on taggue vapeur tropicale vs vapeur extratropicale
40! option 21: taggage de 2 boites 3D: extratropiques (>35°) et UT tropicale (15-15°, > 500hPa)
41! option 22: tagage de la vapeur proccessee dans les zones tres convectives
42               
43   !--- nzone_opt (value of nzone for the selected option) must be equal to nzone as defined in onfotrac
44   REAL, PARAMETER :: ridicule_trac = ridicule * 1e4
45   INTEGER, SAVE :: option_traceurs, nzone_opt, nzoneOR
46!$OMP THREADPRIVATE(option_traceurs,nzone_opt,nzoneOR)
47   INTEGER, SAVE :: initialisation_isotrac
48!$OMP THREADPRIVATE(initialisation_isotrac)     
49                ! 1 pour idealise
50                ! 0 pour lecture dans fichier
51
52   !=== VARIABLES SPECIFIC TO THE SELECTED OPTION, BUT NEEDED FOR THE COMPUTATION OF THE NUMBER OF ZONES ; TO BE INITIALIZED IN traceurs_init
53
54   !--- option 3
55   LOGICAL, SAVE :: use_bassin_Austral, use_bassin_Atlantic, use_bassin_MidLats, use_bassin_SouthIndian, use_bassin_MerArabie
56!$OMP THREADPRIVATE(use_bassin_Austral, use_bassin_Atlantic, use_bassin_MidLats, use_bassin_SouthIndian, use_bassin_MerArabie)
57   INTEGER, SAVE ::     bassin_Austral,     bassin_Atlantic,     bassin_MidLats,     bassin_SouthIndian,     bassin_MerArabie
58!$OMP THREADPRIVATE(    bassin_Austral,     bassin_Atlantic,     bassin_MidLats,     bassin_SouthIndian,     bassin_MerArabie)
59   LOGICAL, SAVE :: use_bassin_Pacific, use_bassin_Indian,   use_bassin_Tropics, use_bassin_BengalGolf,  use_bassin_HighLats, use_bassin_Medit
60!$OMP THREADPRIVATE(use_bassin_Pacific, use_bassin_Indian,   use_bassin_Tropics, use_bassin_BengalGolf,  use_bassin_HighLats, use_bassin_Medit)
61   INTEGER, SAVE ::     bassin_Pacific,     bassin_Indian,       bassin_Tropics,     bassin_BengalGolf,      bassin_HighLats,     bassin_Medit
62!$OMP THREADPRIVATE(    bassin_Pacific,     bassin_Indian,       bassin_Tropics,     bassin_BengalGolf,      bassin_HighLats,     bassin_Medit)
63
64   !--- option 4
65   INTEGER, PARAMETER :: nzone_temp = 1
66   REAL,   SAVE ::  zone_temp1, zone_tempf, zone_tempa 
67!$OMP THREADPRIVATE(zone_temp1, zone_tempf, zone_tempa)
68   REAL,   SAVE ::  zone_temp(nzone_temp-1)
69!$OMP THREADPRIVATE(zone_temp)
70
71   !--- option 5
72   INTEGER, SAVE :: izone_aej, izone_harmattan, izone_mousson
73!$OMP THREADPRIVATE(izone_aej, izone_harmattan, izone_mousson)
74
75   !--- option 6
76   INTEGER, SAVE :: izone_ddft
77!$OMP THREADPRIVATE(izone_ddft)
78
79   !--- option 10
80   INTEGER, SAVE :: izone_contfrac
81!$OMP THREADPRIVATE(izone_contfrac)
82
83   !--- option 12       
84   INTEGER, SAVE :: izone_contcanop
85!$OMP THREADPRIVATE(izone_contcanop)
86
87   !--- option 13
88   INTEGER, PARAMETER :: nzone_pres = 3
89   REAL, SAVE ::  zone_pres(nzone_pres-1)
90!$OMP THREADPRIVATE(zone_pres)
91
92   !--- option 14
93   INTEGER, PARAMETER :: nzone_lat = 4
94   REAL,    SAVE :: zone_pres1, zone_presf, zone_presa
95!$OMP THREADPRIVATE(zone_pres1, zone_presf, zone_presa)
96   REAL,    SAVE :: dlattag, lattag_min, zone_lat(nzone_lat-1)
97!$OMP THREADPRIVATE(dlattag, lattag_min, zone_lat)
98
99   !--- option 15
100   INTEGER, SAVE :: izone_irrig
101!$OMP THREADPRIVATE(izone_irrig)
102
103   !--- option 17
104   REAL,    SAVE :: seuil_tag_tmin, seuil_tag_tmin_ls
105!$OMP THREADPRIVATE(seuil_tag_tmin, seuil_tag_tmin_ls)
106  INTEGER,  SAVE :: option_seuil_tag_tmin
107!$OMP THREADPRIVATE(option_seuil_tag_tmin)
108
109   !--- option 20
110   INTEGER, SAVE :: izone_trop, izone_extra
111!$OMP THREADPRIVATE(izone_trop, izone_extra)
112   REAL,    SAVE :: lim_tag20
113!$OMP THREADPRIVATE(lim_tag20)
114
115   !--- option 21: on garde izone_trop, izone_extra 
116
117   !--- option 22
118   INTEGER, SAVE :: izone_conv_BT, izone_conv_UT
119!$OMP THREADPRIVATE(izone_conv_BT, izone_conv_UT)
120   REAL,    SAVE :: lim_precip_tag22
121!$OMP THREADPRIVATE(lim_precip_tag22)
122
123       
124  INTEGER, ALLOCATABLE, SAVE :: index_iso(:), index_zone(:), itZonIso_loc(:,:)
125!$OMP THREADPRIVATE(            index_iso,    index_zone,    itZonIso_loc)
126  CHARACTER(LEN=3), ALLOCATABLE :: strtrac(:)
127!$OMP THREADPRIVATE(               strtrac)
128  INTEGER, ALLOCATABLE, SAVE :: bassin_map(:), boite_map(:,:)
129!$OMP THREADPRIVATE(            bassin_map,    boite_map)
130
131   !=== RECYCLING AND EVAPORATION TREATMENT
132   INTEGER, SAVE :: izone_cont, izone_oce        !--- For land and ocean recycling
133!$OMP THREADPRIVATE(izone_cont, izone_oce)
134   INTEGER, SAVE :: izone_poubelle               !--- For small numerical residues
135!$OMP THREADPRIVATE(izone_poubelle)
136   INTEGER, SAVE :: izone_init                   !--- For default initialization
137!$OMP THREADPRIVATE(izone_init)
138   INTEGER, SAVE :: izone_revap                  !--- For droplets evaporation
139!$OMP THREADPRIVATE(izone_revap)
140   INTEGER, SAVE :: option_revap, option_tmin, option_cond, izone_cond
141!$OMP THREADPRIVATE(option_revap, option_tmin, option_cond, izone_cond)
142   REAL, PARAMETER :: evap_franche = 1e-6        !--- In kg/m2/s
143
144CONTAINS
145
146   SUBROUTINE iso_traceurs_init()
147
148   USE infotrac_phy, ONLY: itZonIso, isoName, isoZone
149   USE isotopes_mod, ONLY: iso_eau, ntracisoOR, initialisation_iso
150   USE dimphy,       ONLY: klon, klev
151   USE  strings_mod, ONLY: int2str, strStack, strTail, strHead, strIdx, fmsg
152
153   IMPLICIT NONE
154   ! Define which zones and isotopes correspond to isotopic tagging tracers
155   ! Modify traceurs.h variables
156   INTEGER :: izone, ixt, k
157   INTEGER :: izone_pres, izone_lat
158   INTEGER :: nzone_opt
159
160   IF(fmsg("traceurs_init 18: isotrac ne marche que si on met l'eau comme isotope", 'iso_traceurs_init', iso_eau==0)) STOP
161
162   !--- Initialize
163   option_traceurs = 0
164   initialisation_isotrac = 0
165
166   !--- Allocate
167   ALLOCATE(index_iso (ntiso))
168   ALLOCATE(index_zone(ntiso))
169   ALLOCATE(itZonIso_loc(nzone,niso))
170   ALLOCATE(strtrac(nzone))
171   ALLOCATE(bassin_map(klon))
172   ALLOCATE( boite_map(klon,klev))
173
174   IF(initialisation_iso == 0) CALL get_in('initialisation_isotrac', initialisation_isotrac)
175
176   !--- Read tracing option
177   CALL get_in('option_traceurs', option_traceurs)
178
179   !--- Genral case: no traceurs in ORCHIDEE
180   ntracisoOR=niso
181
182   ! partie a editer ! pour definir les differentes zones
183   SELECT CASE(option_traceurs)
184      !========================================================================================================================
185      CASE(1)      !=== TRACING LAND/OCEAN
186      !========================================================================================================================
187         nzone_opt=2
188         izone_cont=1
189         izone_oce=2
190         izone_poubelle=2    ! zone ou on met les flux non physiques, de reajustement
191         izone_init=2        ! zone d'initialisation par defaut         
192         option_revap=0
193         option_tmin=0
194         izone_revap=0
195         option_cond=0
196         strtrac(izone_cont) = 'con'
197         strtrac(izone_oce)  = 'oce'
198      !========================================================================================================================
199      CASE(2)      !=== TRACING LAND/OCEAN/DROPLETS REEVAPORATION
200      !========================================================================================================================
201         nzone_opt=3
202         izone_cont=1
203         izone_oce=2
204         izone_poubelle=2    ! zone ou on met les flux non physiques, de reajustement
205         izone_init=2        ! zone d'initialisation par defaut         
206         option_revap=1
207         option_tmin=0
208         izone_revap=3
209         option_cond=0
210         strtrac(izone_cont) = 'con'
211         strtrac(izone_oce)  = 'oce'
212         strtrac(izone_revap)= 'rev'
213      !========================================================================================================================
214      CASE(3)      !=== TRACING OCEANS BASINS + RESIDUE (LAST DIMENSION). NO DROPLETS EVAPORATION TRACING.
215      !========================================================================================================================
216         ! lire les use_bassin
217         CALL get_in('use_bassin_Atlantic',   use_bassin_Atlantic)
218         CALL get_in('use_bassin_Medit',      use_bassin_Medit)
219         CALL get_in('use_bassin_Indian',     use_bassin_Indian)
220         CALL get_in('use_bassin_Austral',    use_bassin_Austral)
221         CALL get_in('use_bassin_Pacific',    use_bassin_Pacific)
222         CALL get_in('use_bassin_MerArabie',  use_bassin_MerArabie)
223         CALL get_in('use_bassin_BengalGolf', use_bassin_BengalGolf)
224         CALL get_in('use_bassin_SouthIndian',use_bassin_SouthIndian)
225         CALL get_in('use_bassin_Tropics',    use_bassin_Tropics)
226         CALL get_in('use_bassin_Midlats',    use_bassin_Midlats)
227         CALL get_in('use_bassin_HighLats',   use_bassin_HighLats)
228         nzone_opt  =  2  +  COUNT([use_bassin_Atlantic, use_bassin_Medit,     use_bassin_Indian,     &
229            use_bassin_Austral,     use_bassin_Pacific,  use_bassin_MerArabie, use_bassin_BengalGolf, &
230            use_bassin_SouthIndian, use_bassin_Tropics,  use_bassin_Midlats,   use_bassin_HighLats])
231         izone_cont=nzone
232         izone_oce=0             ! pas de sens car separee en bassins         
233         izone_poubelle=nzone-1  ! zone ou on met les flux non physiques, de reajustement
234         izone_init=nzone-1      ! zone d'initialisation par defaut
235         option_revap=0          ! on ne trace pas les gouttes
236         option_tmin=0
237         izone_revap=0           ! pas de sens car on taggue pas les gouttes separemment 
238         option_cond=0
239#ifdef ISOVERIF
240         IF(use_bassin_Indian) THEN   !=== NON COMPATIBLE WITH A DETAILED INDIAN CUTTING
241            IF(use_bassin_MerArabie .OR. use_bassin_SouthIndian .OR. use_bassin_BengalGolf) THEN
242               WRITE(*,*) 'traceurs_init 73'; STOP
243            END IF
244!           CALL iso_verif_egalite(float(use_bassin_MerArabie),   0.0, 'iso_traceurs_init 73: revoir def des bassins')
245!           CALL iso_verif_egalite(float(use_bassin_BengalGolf),  0.0, 'iso_traceurs_init 73: revoir def des bassins')
246!           CALL iso_verif_egalite(float(use_bassin_SouthIndian), 0.0, 'iso_traceurs_init 73: revoir def des bassins')
247         END IF
248#endif   
249         bassin_Atlantic   = 1
250         bassin_Medit      = bassin_Atlantic    + COUNT([use_bassin_Medit]);       WRITE(*,*) 'bassin_Atlantic    =' ,bassin_Atlantic
251         bassin_Indian     = bassin_Medit       + COUNT([use_bassin_Indian]);      WRITE(*,*) 'bassin_Medit       =' ,bassin_Medit
252         bassin_Austral    = bassin_Indian      + COUNT([use_bassin_Austral]);     WRITE(*,*) 'bassin_Indian      =' ,bassin_Indian
253         bassin_Pacific    = bassin_Austral     + COUNT([use_bassin_Pacific]);     WRITE(*,*) 'bassin_Austral     =' ,bassin_Austral
254         bassin_MerArabie  = bassin_Pacific     + COUNT([use_bassin_MerArabie]);   WRITE(*,*) 'bassin_MerArabie   =' ,bassin_MerArabie
255         bassin_BengalGolf = bassin_MerArabie   + COUNT([use_bassin_BengalGolf]);  WRITE(*,*) 'bassin_BengalGolf  =' ,bassin_BengalGolf
256         bassin_SouthIndian= bassin_BengalGolf  + COUNT([use_bassin_SouthIndian]); WRITE(*,*) 'bassin_SouthIndian =' ,bassin_SouthIndian
257         bassin_Tropics    = bassin_SouthIndian + COUNT([use_bassin_Tropics]);     WRITE(*,*) 'bassin_Tropics     =' ,bassin_Tropics
258         bassin_MidLats    = bassin_Tropics     + COUNT([use_bassin_MidLats]);     WRITE(*,*) 'bassin_MidLats     =' ,bassin_MidLats
259         bassin_HighLats   = bassin_MidLats     + COUNT([use_bassin_HighLats]);    WRITE(*,*) 'bassin_HighLats    =' ,bassin_HighLats
260         IF(use_bassin_atlantic   ) strtrac(bassin_atlantic)   = 'atl'
261         IF(use_bassin_medit      ) strtrac(bassin_medit)      = 'med'
262         IF(use_bassin_indian     ) strtrac(bassin_indian)     = 'ind'
263         IF(use_bassin_austral    ) strtrac(bassin_austral)    = 'aus'
264         IF(use_bassin_pacific    ) strtrac(bassin_pacific)    = 'pac'
265         IF(use_bassin_merarabie  ) strtrac(bassin_merarabie)  = 'ara'
266         IF(use_bassin_BengalGolf ) strtrac(bassin_BengalGolf) = 'ben'
267         IF(use_bassin_SouthIndian) strtrac(bassin_SouthIndian)= 'ins'
268         IF(use_bassin_tropics    ) strtrac(bassin_tropics)    = 'tro'
269         IF(use_bassin_midlats    ) strtrac(bassin_midlats)    = 'mid'
270         IF(use_bassin_HighLats   ) strtrac(bassin_HighLats)   = 'hau'
271         strtrac(nzone-1)='res'
272         strtrac(nzone)='con'
273      !========================================================================================================================
274      CASE(4)      !=== TRACING MINIMAL EXPERIENCED TEMPERATURE AS IN THE ARTICLE ON LfG, EXCEPT NO REVAPORATION
275      !========================================================================================================================
276         zone_temp1 = 293.0  ! en K
277!        zone_tempf = 223.0  ! en K
278         zone_tempf = 243.0  ! en K
279        ! courbure de la relation entre l'indice et la temperature: 0 pour lineaire, <0 pour plus de detal en bas
280        ! zone 1: >= zone_temp1
281        ! zone 2 a 4: intermediaire,
282        ! zone 5: <zone_tempf
283         nzone_opt=nzone_temp+1
284         zone_tempa=-4.0     ! en K
285         izone_cont=nzone
286         izone_oce=nzone 
287         izone_poubelle=nzone
288         izone_init=nzone    ! zone d'initialisation par defaut
289         option_revap=0
290         option_tmin=0 
291         izone_revap=0
292         option_cond=0
293         DO izone=1,nzone_temp
294            strtrac(izone) = 't'//TRIM(int2str(izone))
295            WRITE(*,*) 'izone, strtrac=', izone, strtrac(izone)
296         END DO
297         strtrac(izone_poubelle)='pou'
298         ! Initialization of temperatures zones
299         DO izone=1,nzone_temp-1
300            zone_temp(izone) = zone_temp1+float(izone-1)            &
301                            * (zone_tempa*float(izone-nzone_temp+1) &
302                            + (zone_tempf-zone_temp1)/float(nzone_temp-2))
303         END DO
304         WRITE(*,*) 'iso_trac_init 183: zone_temp=', zone_temp
305      !========================================================================================================================
306      CASE(5)      !=== TRACING AEJ/MOONSOON FLUX/Harmattan
307      !========================================================================================================================
308!        WRITE*,*) 'iso_traceurs_init 129'
309         nzone_opt=4
310         izone_cont=1
311         izone_oce=1
312         izone_poubelle=1    ! zone ou on met les flux non physiques, de reajustement
313         izone_init=1        ! zone d'initialisation par defaut         
314         option_revap=0
315         option_tmin=0
316         izone_revap=0
317         izone_aej=2
318         izone_mousson=3
319         izone_harmattan=4
320         option_cond=0
321         strtrac(izone_poubelle) = 'res'
322         strtrac(izone_aej)      = 'aej'
323         strtrac(izone_mousson)  = 'mou'
324         strtrac(izone_harmattan)= 'sah'
325      !========================================================================================================================
326      CASE(6)      !=== TRACING DDFTS
327      !========================================================================================================================
328         nzone_opt=2
329         izone_cont=1
330         izone_oce=1
331         izone_poubelle=1    ! zone ou on met les flux non physiques, de reajustement
332         izone_init=1        ! zone d'initialisation par defaut         
333         option_revap=0
334         option_tmin=0
335         izone_revap=0
336         izone_ddft=2
337         option_cond=0
338         strtrac(izone_poubelle)='res'
339         strtrac(izone_ddft)='dft'
340      !========================================================================================================================
341      CASE(9)      !=== TRACING CONDENSATION
342      !========================================================================================================================
343         nzone_opt=3
344         izone_cont=1
345         izone_oce=1
346         izone_poubelle=1    ! zone ou on met les flux non physiques, de reajustement
347         izone_init=1        ! zone d'initialisation par defaut         
348         option_revap=1
349         option_tmin=0
350         izone_revap=2
351         izone_cond=3
352         option_cond=1
353         ! 1 par defaut pour colorier a la fois condensat LS et condensat convectif.
354         ! Mais on peut mettre 2 si on ne veut que colorier que le condensat convectif.
355         CALL get_in('option_cond',option_cond)
356         strtrac(izone_poubelle)='res'
357         strtrac(izone_cond)='con'
358         strtrac(izone_revap)='rev'
359      !========================================================================================================================
360      CASE(10)     !=== TRACING EVAPORATION FROM OCEAN/LAND, NON FRAC/LAND FRAC ; ONLY WHEN COUPLED WITH ORCHIDEE
361      !========================================================================================================================
362#ifndef CPP_VEGET
363         WRITE(*,*) 'iso_traceurs_init 219: option_traceurs=10 inutile si on ne couple pas avec ORCHIDEE'; STOP
364#endif         
365         nzone_opt=3
366         izone_cont=1        ! sous-entendu non fractionnant
367         izone_oce=2
368         izone_poubelle=2    ! zone ou on met les flux non physiques, de reajustement
369         izone_init=2        ! zone d'initialisation par defaut
370         option_revap=0
371         option_tmin=0
372         izone_revap=0
373         izone_contfrac=3
374         izone_contcanop=3
375         izone_irrig=0
376         option_cond=0
377         strtrac(izone_oce)='oce'
378         strtrac(izone_cont)='con' 
379         strtrac(izone_contfrac)='enu'  ! evap sol nu
380      !========================================================================================================================
381      CASE(11)     !=== TRACING DROPLETS REEVAPORATION + REST
382      !========================================================================================================================
383         nzone_opt=2
384         izone_cont=1
385         izone_oce=1
386         izone_poubelle=1    ! zone ou on met les flux non physiques, de reajustement
387         izone_init=1        ! zone d'initialisation par defaut
388         option_revap=1
389         option_tmin=0
390         izone_revap=2
391         izone_irrig=0
392         option_cond=0
393         strtrac(izone_poubelle)='res'
394         strtrac(izone_revap)='rev'
395      !========================================================================================================================
396      CASE(12)     !=== TRACING NAKED GROUND EVAPORATION, CANOPY EVAPORATION, REST OF LAND EVAPORATION AND OCEAN EVAPORATION
397      !========================================================================================================================
398#ifndef CPP_VEGET
399         WRITE(*,*) 'iso_traceurs_init 257: option_traceurs=10 inutile si on ne couple pas avec ORCHIDEE'; STOP
400#endif           
401         nzone_opt=2
402         izone_cont=1
403         izone_oce=2
404         izone_poubelle=2    ! zone ou on met les flux non physiques, de reajustement
405         izone_init=2        ! zone d'initialisation par defaut
406         option_revap=0
407         option_tmin=0
408         izone_revap=0
409         izone_contfrac=3
410         izone_contcanop=4
411         izone_irrig=0   
412         option_cond=0
413         strtrac(izone_oce)='oce'
414         strtrac(izone_cont)='con'
415         strtrac(izone_contfrac)='enu' ! evap sol nu
416         strtrac(izone_contcanop)='eca'! evap canop
417      !========================================================================================================================
418      CASE(13)     !=== TRACING MINIMUM EXPERIENCED TEMPERATIRES + REEVAPORATION AS IN THE ARTICLE ON LdG
419      !========================================================================================================================
420         zone_temp1=293.0    ! en K       
421!        zone_tempf=223.0    ! en K
422         zone_tempf=243.0    ! en K
423         zone_tempa=-4.0     ! courbure de la relation entre l'indice et la temperature: 0 pour lineaire, <0 pour plus de detal en bas
424         ! zone 1: >= zone_temp1
425         ! zone 2 a 4: intermediaire,
426         ! zone 5: <zone_tempf
427         nzone_opt=nzone_temp+1
428         izone_cont=1
429         izone_oce=1 
430         izone_poubelle=1
431         izone_init=1        ! zone d'initialisation par defaut
432         option_revap=1   
433         option_tmin=0
434         izone_revap=nzone
435         izone_irrig=0
436         option_cond=0
437         DO izone=1,nzone_temp
438            strtrac(izone) = 't'//TRIM(int2str(izone))
439            WRITE(*,*) 'izone, strtrac = ', izone, strtrac(izone)
440         END DO
441         strtrac(izone_revap)='rev'
442         ! initialisation des zones de tempearture
443         DO izone=1,nzone_temp-1
444            zone_temp(izone) = zone_temp1+float(izone-1) &
445                             *(zone_tempa*float(izone-nzone_temp+1) &
446                             +(zone_tempf-zone_temp1)/float(nzone_temp-2))
447         END DO
448         WRITE(*,*) 'zone_temp=',zone_temp
449      !========================================================================================================================
450      CASE(14)     !=== TRACING PRES AND LAT OF LAST SATURATION DEFINED AS rh>90%
451      !========================================================================================================================
452         zone_pres1=600.0*100.0   ! en Pa       
453         zone_presf=300.0*100.0   ! en Pa
454         zone_presa=0.0           ! courbure de la relation entre l'indice et la temperature: 0 pour lineaire
455         lattag_min=10.0          ! en degres
456         dlattag=15.0
457         ! zone 1: >= zone_pres1
458         ! zone 2 a 4: intermediaire,
459         ! zone 5: <zone_presf
460         nzone_opt=nzone_pres*nzone_lat+1         
461         izone_cont=nzone
462         izone_oce=nzone
463         izone_poubelle=nzone
464         izone_init=nzone         ! zone d'initialisation par defaut
465         option_revap=0 
466         option_tmin=0
467         izone_revap=0
468         izone_irrig=0
469         option_cond=0
470         DO izone_pres=1,nzone_pres
471            DO izone_lat=1,nzone_lat
472               izone=izone_lat+(izone_pres-1)*nzone_lat
473               strtrac(izone) = 't'//TRIM(int2str(izone_pres))//TRIM(int2str(izone_lat))
474               write(*,*) 'izone_pres, izone_lat, izone, strtrac = ',izone_pres, izone_lat, izone, strtrac(izone)
475            END DO
476         END DO
477         strtrac(nzone)='sfc'
478         ! initialisation des zones de temperature
479         DO izone=1,nzone_pres-1
480            zone_pres(izone) = zone_pres1+float(izone-1) &
481                             *(zone_presa*float(izone-nzone_pres+1) &
482                             +(zone_presf-zone_pres1)/float(nzone_pres-2))
483         END DO
484         WRITE(*,*) 'traceurs_init 332: zone_pres=',zone_pres
485      !========================================================================================================================
486      CASE(15)     !=== TRACING IRRIGATION IN ORCHIDEE
487      !========================================================================================================================
488#ifndef CPP_VEGET
489         WRITE(*,*) 'iso_traceurs_init 257: option_traceurs=15 inutile si on ne couple pas avec ORCHIDEE'; STOP
490#endif
491         nzone_opt=1
492         izone_cont=1
493         izone_oce=1
494         izone_poubelle=1    ! zone ou on met les flux non physiques, de reajustement
495         izone_init=1        ! zone d'initialisation par defaut
496         option_revap=0
497         option_tmin=0
498         izone_revap=0
499         izone_contfrac=0
500         izone_contcanop=0
501         izone_irrig=2
502         option_cond=0
503         strtrac(izone_poubelle)='res'
504         strtrac(izone_irrig)='irrig'
505         ! dans ce cas particulier, il y a des traceurs dans ORCHIDEE
506         ntracisoOR=ntiso
507      !========================================================================================================================
508      CASE(17,18)  !=== TRACING MINIMAL EXPERIENCES TEMPERATURES AS IN THE ARTICLE ABOUT LdG, BUT NO EVAPORATION
509      !========================================================================================================================
510         zone_temp1=12.0e-3  ! en kg/kg       
511         zone_tempf=0.2e-3   ! en kg/kg
512         zone_tempa=1.2e-3   ! courbure de la relation entre l'indice et la temperature: 0 pour lineaire
513!        zone_temp1=14.0e-3  ! en kg/kg       
514!        zone_tempf=0.2e-3   ! en kg/kg
515!        zone_tempa=0.5e-3       
516!        zone_temp1=10.0e-3  ! en kg/kg
517!        zone_tempf=0.5e-3   ! en kg/kg
518!        zone_tempa=0.5e-3
519         ! zone 1: >= zone_temp1
520         ! zone 2 a 4: intermediaire,
521         ! zone 5: <zone_tempf
522         nzone_opt=nzone_temp+3
523         izone_cont=nzone_temp+1
524         izone_oce=nzone_temp+1
525         izone_poubelle=nzone_temp+1
526         izone_init=nzone_temp+1 ! zone d'initialisation par defaut
527         option_revap=1 
528         option_tmin=1
529         option_cond=1
530         izone_revap=nzone_temp+3
531         izone_cond=nzone_temp+2
532         DO izone=1,nzone_temp
533            strtrac(izone) = 't'//TRIM(int2str(izone))
534            WRITE(*,*) 'izone, strtrac = ', izone, strtrac(izone)
535         END DO !do izone=1,nzone_temp
536         strtrac(izone_poubelle)='sfc'
537         strtrac(izone_cond)='con'
538         strtrac(izone_revap)='rev'
539         ! initialisation des zones de tempearture
540         DO izone=1,nzone_temp-1
541            zone_temp(izone) = zone_temp1+float(izone-1) &
542                             *(zone_tempa*float(izone-nzone_temp+1) &
543                             +(zone_tempf-zone_temp1)/float(nzone_temp-2))
544         END DO
545         WRITE(*,*) 'zone_temp1,zone_tempf,zone_tempa=',zone_temp1,zone_tempf,zone_tempa
546         WRITE(*,*) 'zone_temp=',zone_temp
547!        STOP         
548      !========================================================================================================================
549      CASE(19)     !=== TRACING TROPICAL AND EXTRATROPICAL VAPOUR
550      !========================================================================================================================
551         zone_temp1=12.0e-3  ! en kg/kg       
552         zone_tempf=0.2e-3   ! en kg/kg
553         zone_tempa=1.2e-3   ! courbure de la relation entre l'indice et la temperature: 0 pour lineaire, <0 pour plus de detail en bas
554!        zone_temp1=14.0e-3  ! en kg/kg       
555!        zone_tempf=0.2e-3   ! en kg/kg
556!        zone_tempa=0.5e-3
557!        zone_temp1=10.0e-3  ! en kg/kg       
558!        zone_tempf=0.5e-3   ! en kg/kg
559!        zone_tempa=0.5e-3
560         ! zone 1: >= zone_temp1
561         ! zone 2 a 4: intermediaire,
562         ! zone 5: <zone_tempf
563         nzone_opt=nzone_temp+4
564         izone_cont=nzone_temp+1
565         izone_oce=nzone_temp+1
566         izone_poubelle=nzone_temp+1
567         IF(option_seuil_tag_tmin == 1) THEN
568            izone_init=nzone_temp+1 ! zone d'initialisation par defaut
569         ELSE
570            izone_init=nzone_temp
571         END IF
572         option_revap=1   
573         izone_revap=nzone_temp+3
574         izone_cond=nzone_temp+2
575         izone_ddft=nzone_temp+4
576         option_tmin=1         
577         option_cond=1
578         DO izone=1,nzone_temp
579            strtrac(izone) = 't'//TRIM(int2str(izone))
580            WRITE(*,*) 'izone, strtrac = ', izone, strtrac(izone)
581         END DO
582         strtrac(izone_poubelle)='sfc'
583         strtrac(izone_cond)='con'
584         strtrac(izone_revap)='rev'
585         strtrac(izone_ddft)='dft'
586      !========================================================================================================================
587      CASE(20)     !=== TRACING TROPICAL/EXTRATROPICAL/EXTRATROPICAL RECYCLING TO STUDY HUMIDITY AND SUBTROPICAL ISOTOPES CONTROL
588      !========================================================================================================================
589         CALL get_in('lim_tag20', lim_tag20, 35.0)
590         nzone_opt=3
591         izone_cont=1
592         izone_oce=1
593         izone_poubelle=2    ! zone ou on met les flux non physiques, de reajustement
594         izone_init=2        ! zone d'initialisation par defaut
595         option_revap=0
596         option_tmin=0
597         izone_revap=0
598         izone_trop=2
599         izone_extra=3
600         strtrac(izone_trop)='tro'     ! tropical vapour
601         strtrac(izone_extra)='ext'    ! extratropical vapour evaporated in the tropics
602         strtrac(izone_cont)='rec'     ! recycling
603      !========================================================================================================================
604      CASE(21)     !=== TRACING TWO 3D BOXES: TROPICAL UT AND EXTRATROPICS ; SIMILAR TO 5 FOR AMMA ZONES TAGGING
605      !========================================================================================================================
606!        WRITE(*,*) 'iso_traceurs_init 129'
607         nzone_opt=3
608         izone_cont=1
609         izone_oce=1
610         izone_poubelle=1    ! zone ou on met les flux non physiques, de reajustement
611         izone_init=1        ! zone d'initialisation par defaut
612         option_revap=0
613         option_tmin=0
614         izone_revap=0
615         izone_trop=2
616         izone_extra=3
617         option_cond=0
618         strtrac(izone_poubelle)='res'
619         strtrac(izone_trop)='tro'
620         strtrac(izone_extra)='ext'
621      !========================================================================================================================
622      CASE(22)     !=== TRACING WATER VAPOUR PROCESSED IN THE 3-LEVELS SCONVECTION ZONES BT, MT AND UT
623      !========================================================================================================================
624         CALL get_in('lim_precip_tag22', lim_precip_tag22, 20.0)
625         nzone_opt=3
626         izone_cont=1
627         izone_oce=1
628         izone_poubelle=1    ! zone ou on met les flux non physiques, de reajustement
629         izone_init=1        ! zone d'initialisation par defaut
630         option_revap=0
631         option_tmin=0
632         izone_revap=0
633         izone_conv_BT=2
634         izone_conv_UT=3
635         option_cond=0
636         strtrac(izone_poubelle)='res'
637         strtrac(izone_conv_BT)='cbt'
638         strtrac(izone_conv_UT)='cut'
639      CASE DEFAULT
640         WRITE(*,*) 'traceurs_init 36: option pas encore prevue'
641         CALL abort_physic ('isotrac_mod 641','option pas encore prevue',1)
642   END SELECT
643
644   IF(nzone_opt /= nzone) THEN
645      WRITE(*,*) 'nzone_opt, nzone=', nzone_opt, nzone
646      CALL abort_physic ('isotrac_mod','nzone incoherent',1)
647   END IF
648
649   !--- Condensation rate threshold
650   IF(option_tmin == 1) THEN
651      seuil_tag_tmin = 0.01
652      CALL get_in('seuil_tag_tmin',        seuil_tag_tmin,        0.01)
653      CALL get_in('seuil_tag_tmin_ls',     seuil_tag_tmin_ls,     seuil_tag_tmin)
654      CALL get_in('option_seuil_tag_tmin', option_seuil_tag_tmin, 1)
655   END IF
656
657   index_zone = [(strIdx(isoZone, strTail(isoName(ixt) ,'_',.TRUE.)), ixt=1, ntiso)]
658   index_iso  = [(strIdx(isoName, strHead(isoName(ixt) ,'_',.TRUE.)), ixt=1, ntiso)]
659   itZonIso_loc = itZonIso(:,:)
660#ifdef ISOVERIF
661   WRITE(*,*) 'traceurs_init 65: bilan de l''init:'
662   WRITE(*,*) 'index_zone = '//TRIM(strStack(int2str(index_zone(1:ntiso))))
663   WRITE(*,*) 'index_iso  = '//TRIM(strStack(int2str(index_iso (1:ntiso))))
664   DO izone=1,nzone
665      WRITE(*,*)'itZonIso('//TRIM(int2str(izone))//',:) = '//strStack(int2str(itZonIso(izone,:)))
666   END DO
667   DO izone=1,nzone
668      WRITE(*,*)'strtrac('//TRIM(int2str(izone))//',:) = '//TRIM(strtrac(izone))
669   END DO
670   WRITE(*,*) 'ntracisoOR=',ntracisoOR
671#endif 
672
673END SUBROUTINE iso_traceurs_init
674
675END MODULE isotrac_mod
676#endif
677#endif
Note: See TracBrowser for help on using the repository browser.