Ignore:
Timestamp:
Nov 7, 2022, 3:09:43 AM (19 months ago)
Author:
dcugnet
Message:
  • simplify the parser usage:
    • the getKey_init routine is now embedded in the readTracersFile routine.
    • the initIsotopes routine is now embedded in the readIsotopesFile routine.
    • the database is now unique, but can be changed using the get/setKeysDBase.
    • the derived types descriptions, originally located in trac_types_mod, are moved to readTracFiles_mod.
    • few checkings moved from infotrac to the routine testIsotopes, contained in the readIsotopesFile function from readTracFiles_mod.
    • the readTracersFiles and readIsotopesFile routines no longer use a tracers/isotopes argument.
  • remove tnat and alpha_ideal from infotrac ; use instead getKey to get them where they are used (check_isotopes, dynetat0, iniacademic)
  • the trac_type field %Childs is renamed %Children
  • move the isoSelect routine and the corresponding variables routine from infotrac and infotrac_phy to readTracFiles_mod
  • infotrac_phy routine is now fully independant of the (very similar) routine infotrac (init_infotrac_phy has no arguments left).
  • all the explicit keys of the trac_type are now included in the embedded keys database, accessible using the getKey function.
  • the getKey/addKey routines are expanded to handle vectors of integers, reals, logicals or strings.
  • few subroutines converted into functions with error return value.
  • corrections for isotopic tagging tracers mode (to be continued).
File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmdiso/isotrac_mod.F90

    r4143 r4325  
    11#ifdef ISO
    22#ifdef ISOTRAC
    3 ! $Id: $
    43
    54MODULE isotrac_mod
    6 use infotrac_phy, ONLY: niso,ntiso,ntraceurs_zone=>nzone
    7 use isotopes_mod, only: ridicule
    8 
    9 IMPLICIT NONE
    10 SAVE
    11 
    12 ! contient toutes les variables traceurs isotopiques + les routines specifiquement
    13 ! traceurs isotopiques
    14 
    15       real ridicule_trac
    16       parameter (ridicule_trac=ridicule*1e4)
    17 
    18 integer, save ::  option_traceurs
    19 integer, save ::  ntraceurs_zone_opt ! ntraceurs_zone propre à l'option
    20 ! on vérifie que ça correspond bien à ntraceurs_zone d'infotrac
    21 integer, save ::  ntraceurs_zoneOR
    22 !$OMP THREADPRIVATE(option_traceurs,ntraceurs_zone_opt,ntraceurs_zoneOR)
    23 integer, save ::  initialisation_isotrac
    24                 ! 1 pour idéalisé
    25                 ! 0 pour lecture dans fichier
    26 !$OMP THREADPRIVATE(initialisation_isotrac)
    27 
    28 ! variables spécifiques aux différentes options, mais necessaires au
    29 ! calcul du nombre de zones de traceurs
    30 ! si option=3
    31 integer, save :: use_bassin_atlantic
    32 !$OMP THREADPRIVATE(use_bassin_atlantic)
    33 integer, save :: use_bassin_medit
    34 !$OMP THREADPRIVATE(use_bassin_medit)
    35 integer, save :: use_bassin_indian
    36 !$OMP THREADPRIVATE(use_bassin_indian)
    37 integer, save :: use_bassin_austral
    38 !$OMP THREADPRIVATE(use_bassin_austral)
    39 integer, save :: use_bassin_pacific
    40 !$OMP THREADPRIVATE(use_bassin_pacific)
    41 integer, save :: use_bassin_merarabie
    42 !$OMP THREADPRIVATE(use_bassin_merarabie)
    43 integer, save :: use_bassin_golfebengale
    44 !$OMP THREADPRIVATE(use_bassin_golfebengale)
    45 integer, save :: use_bassin_indiansud
    46 !$OMP THREADPRIVATE(use_bassin_indiansud)
    47 integer, save :: use_bassin_tropics
    48 !$OMP THREADPRIVATE(use_bassin_tropics)
    49 integer, save :: use_bassin_midlats
    50 !$OMP THREADPRIVATE(use_bassin_midlats)
    51 integer, save :: use_bassin_hauteslats
    52 !$OMP THREADPRIVATE(use_bassin_hauteslats)
    53 integer, save :: bassin_atlantic
    54 !$OMP THREADPRIVATE(bassin_atlantic)
    55 integer, save :: bassin_medit
    56 !$OMP THREADPRIVATE(bassin_medit)
    57 integer, save :: bassin_indian
    58 !$OMP THREADPRIVATE(bassin_indian)
    59 integer, save :: bassin_austral
    60 !$OMP THREADPRIVATE(bassin_austral)
    61 integer, save :: bassin_pacific
    62 !$OMP THREADPRIVATE(bassin_pacific)
    63 integer, save :: bassin_merarabie
    64 !$OMP THREADPRIVATE(bassin_merarabie)
    65 integer, save :: bassin_golfebengale
    66 !$OMP THREADPRIVATE(bassin_golfebengale)
    67 integer, save :: bassin_indiansud
    68 !$OMP THREADPRIVATE(bassin_indiansud)
    69 integer, save :: bassin_tropics
    70 !$OMP THREADPRIVATE(bassin_tropics)
    71 integer, save :: bassin_midlats
    72 !$OMP THREADPRIVATE(bassin_midlats)
    73 integer, save :: bassin_hauteslats
    74 !$OMP THREADPRIVATE(bassin_hauteslats)
    75 ! si option=4
    76 integer nzone_temp
    77 parameter (nzone_temp=1)
    78 real, save :: zone_temp1,zone_tempf,zone_tempa 
    79 !$OMP THREADPRIVATE(zone_temp1,zone_tempf,zone_tempa)
    80 ! si option 14
    81 integer nzone_lat
    82 parameter (nzone_lat=4)
    83 integer nzone_pres
    84 parameter (nzone_pres=3)
    85 real, save :: zone_pres1,zone_presf,zone_presa
    86 !$OMP THREADPRIVATE(zone_pres1,zone_presf,zone_presa)
    87 real, save :: dlattag,lattag_min
    88 !$OMP THREADPRIVATE(dlattag,lattag_min)
    89 
    90 
    91 ! option 1: on trace evap ocean et continent séparement 
     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 
    9215! option 2: on trace evap ocean, continent et evap precip
    93 ! option 3: on trace evap différents bassins océaniques
    94 !       + continents + résidu
    95 !       attention, choisir dans ce cas les bassins océaniques
     16! option 3: on trace evap differents bassins oceaniques
     17!       + continents + residu
     18!       attention, choisir dans ce cas les bassins oceaniques
    9619!       dans iso_traceurs_opt3F90.h
    97 ! option 4: tracage par température minimale
    98 !       dans ce cas, on définit des bins dans iso_traceurs_opt4.h
    99 ! option 5: pour AMMA: on taggue résidu/AEJ/flux mousson/Harmattan
     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
    10023! option 6: taggage des ddfts
    101 ! option 7: pour Sandrine: taggage de la vapeur à 700hPa pour omega500<-20 TODO
    102 ! option 8: pour Sandrine: taggage de la vapeur entre 950 et 800hPa, omega de 0 à 25 hPa et de l'évaoration en omega<-20. TODO
     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
    10326! option 9: taggage du condensat et de la revap precip
    10427! option 10: taggage evap oce, transpiration et evaporation
     
    10730! option 12: taggage evap oce, sol nu, canop et reste evap cont.
    10831! A utiliser quand on couple avec ORCHIDEE
    109 ! option 13: taggage température minimale + revap precip
    110 ! option 14: taggage lat et altitude de dernière saturation (niveaux de pression) + evap surf
     32! option 13: taggage temperature minimale + revap precip
     33! option 14: taggage lat et altitude de derniere saturation (niveaux de pression) + evap surf
    11134! otion 15: taggage irrigation
    11235! option 16: taggage precip selon saisons et fonte neige: seulement pour ORCHIDEE
    113 ! option 17: taggage température minimum de condensation directement dans la convection et la cond LS, + evap sfc, condensat et precipitation
     36! option 17: taggage temperature minimum de condensation directement dans la convection et la cond LS, + evap sfc, condensat et precipitation
    11437! option 18: idem 17 mais on tague qsmin au lieu de Tmin
    11538! option 19: on tag vap residuelle, vap residuelle dans ddfts, sfc, cond, rev
    11639! option 20: on taggue vapeur tropicale vs vapeur extratropicale
    11740! option 21: taggage de 2 boites 3D: extratropiques (>35°) et UT tropicale (15-15°, > 500hPa)
    118 ! option 22: tagage de la vapeur proccessée dans les zones très convectives
     41! option 22: tagage de la vapeur proccessee dans les zones tres convectives
    11942               
    120         ! ces variables sont initialisées dans traceurs_init
     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
    121123       
    122 integer, ALLOCATABLE, DIMENSION(:), save :: index_iso
    123 !$OMP THREADPRIVATE(index_iso)
    124 integer, ALLOCATABLE, DIMENSION(:), save ::  index_zone
    125 !$OMP THREADPRIVATE(index_zone)
    126 integer, ALLOCATABLE, DIMENSION(:,:), save ::  itZonIso_loc ! il y a déjà un itZonIso dans infotrac: vérifier que c'est le même
    127 !$OMP THREADPRIVATE(itZonIso_loc)
    128 character*3, ALLOCATABLE, DIMENSION(:), save :: strtrac
    129 !$OMP THREADPRIVATE(strtrac)
    130 ! -> tout ça passe maintenant par infotrac
    131 
    132 integer, ALLOCATABLE, DIMENSION(:), save :: bassin_map
    133 integer, ALLOCATABLE, DIMENSION(:,:), save :: boite_map
    134 !$OMP THREADPRIVATE(bassin_map,boite_map)
    135 
    136 
    137         ! traitement recyclage et evap
    138 integer, save :: izone_cont ! pour le recyclage continental
    139 !$OMP THREADPRIVATE(izone_cont)
    140 integer, save :: izone_oce ! pour l'océan
    141 !$OMP THREADPRIVATE(izone_oce)
    142 integer, save :: izone_poubelle ! pour les petits résidus numériques
     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
    143135!$OMP THREADPRIVATE(izone_poubelle)
    144 integer, save :: izone_init ! pour l'initialisation par défaut
     136   INTEGER, SAVE :: izone_init                   !--- For default initialization
    145137!$OMP THREADPRIVATE(izone_init)
    146 integer, save :: izone_revap ! pour l'évap des gouttes
     138   INTEGER, SAVE :: izone_revap                  !--- For droplets evaporation
    147139!$OMP THREADPRIVATE(izone_revap)
    148 integer, save :: option_revap
    149 !$OMP THREADPRIVATE(option_revap)
    150 integer, save :: option_tmin
    151 !$OMP THREADPRIVATE(option_tmin)
    152 integer, save :: option_cond
    153 !$OMP THREADPRIVATE(option_cond)
    154 integer, save :: izone_cond
    155 !$OMP THREADPRIVATE(izone_cond)
    156 real evap_franche
    157 parameter (evap_franche=1e-6) ! en kg/m2/s
    158 
    159 ! specifique à option 4:
    160 real, save ::  zone_temp(nzone_temp-1)
    161 !$OMP THREADPRIVATE(zone_temp)
    162 ! si option 5
    163 integer, save :: izone_aej
    164 !$OMP THREADPRIVATE(izone_aej)
    165 integer, save :: izone_harmattan
    166 !$OMP THREADPRIVATE(izone_harmattan)
    167 integer, save :: izone_mousson
    168 !$OMP THREADPRIVATE(izone_mousson)
    169 ! si option 6
    170 integer, save :: izone_ddft
    171 !$OMP THREADPRIVATE(izone_ddft)
    172 ! si option 10
    173 integer, save :: izone_contfrac
    174 !$OMP THREADPRIVATE(izone_contfrac)
    175 ! si option 12 
    176 integer, save :: izone_contcanop
    177 !$OMP THREADPRIVATE(izone_contcanop)
    178 ! specifique à option 13:
    179 real, save ::  zone_pres(nzone_pres-1)
    180 !$OMP THREADPRIVATE(zone_pres)
    181 ! si option 14
    182 real, save ::  zone_lat(nzone_lat-1)
    183 !$OMP THREADPRIVATE(zone_lat)
    184 ! si option 15
    185 integer, save :: izone_irrig
    186 !$OMP THREADPRIVATE(izone_irrig)
    187 ! si option 17
    188 real, save ::  seuil_tag_tmin
    189 !$OMP THREADPRIVATE(seuil_tag_tmin)
    190 real, save ::  seuil_tag_tmin_ls
    191 !$OMP THREADPRIVATE(seuil_tag_tmin_ls)
    192 integer, save :: option_seuil_tag_tmin
    193 !$OMP THREADPRIVATE(option_seuil_tag_tmin)
    194 ! si option 20
    195 integer, save :: izone_trop,izone_extra
    196 real, save ::  lim_tag20
    197 !$OMP THREADPRIVATE(izone_trop,izone_extra,lim_tag20)
    198 ! si option 21: on garde izone_trop,izone_extra 
    199 ! si opt 22
    200 integer, save :: izone_conv_BT,izone_conv_UT
    201 real, save ::  lim_precip_tag22
    202 !$OMP THREADPRIVATE(izone_conv_BT,izone_conv_UT,lim_precip_tag22)
    203 
     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
    204143
    205144CONTAINS
    206145
    207       subroutine iso_traceurs_init()
    208 
    209       use IOIPSL ! getin
    210       USE infotrac_phy, ONLY: itZonIso
    211       USE isotopes_mod, ONLY: iso_eau,ntracisoOR,initialisation_iso
    212       USE dimphy, only: klon,klev
    213 
    214         implicit none
    215 
    216 
    217         ! définition de quelles zones et quelles isotopes représentent
    218         ! les traceurs
    219 
    220         ! inputs, outputs
    221         ! ! c'est les variables dans traceurs.h qui sont modifiées
    222 
    223         ! locals
    224         integer itrac,izone,ixt,k
    225         integer izone_pres,izone_lat
    226         character*2 strz,strz_preslat
    227         character*1 strz_pres,strz_lat
    228         integer ntraceurs_zone_opt
    229 
    230         ! vérifier que on a bien l'eau comme traceurs
    231         if (iso_eau.eq.0) then
    232             write(*,*) 'traceurs_init 18: isotrac ne marche que si ', &
    233      &            'on met l''eau comme isotope'
    234             stop
    235         endif
    236 
    237         ! initialiser
    238         option_traceurs=0
    239         initialisation_isotrac=0
    240 
    241         ! allouer
    242         allocate (index_iso(ntiso))
    243         allocate (index_zone(ntiso))
    244         allocate (itZonIso_loc(ntraceurs_zone,niso))
    245         allocate (strtrac(ntraceurs_zone))
    246         allocate (bassin_map(klon))
    247         allocate (boite_map(klon,klev))
    248 
    249         if (initialisation_iso.eq.0) then
    250           call getin('initialisation_isotrac',initialisation_isotrac)
    251           write(*,*) 'initialisation_isotrac=',initialisation_isotrac
    252         endif !if (initialisation_iso.eq.0) then
    253 
    254         ! lire l'option de traçage
    255         call getin('option_traceurs',option_traceurs)
    256         write(*,*) 'option_traceurs=',option_traceurs
    257 
    258         ! cas général: pas de traceurs dans ORCHIDEE
    259         ntracisoOR=niso
    260 
    261         ! partie à éditer ! pour définir les différentes zones
    262         if (option_traceurs.eq.1) then
    263           ! on trace continents/ocean 
    264 
    265           ntraceurs_zone_opt=2
    266           izone_cont=1
    267           izone_oce=2         
    268           izone_poubelle=2 ! zone où on met les flux non physiques, de
    269                 ! réajustement
    270           izone_init=2 ! zone d'initialisation par défaut         
    271           option_revap=0
    272           option_tmin=0
    273           izone_revap=0
    274           option_cond=0
    275 
    276           strtrac(izone_cont)='con'
    277           strtrac(izone_oce)='oce'
    278 
    279         elseif (option_traceurs.eq.2) then
    280           ! on trace continent/ ocean/reevap des gouttes
    281 
    282           ntraceurs_zone_opt=3
    283           izone_cont=1
    284           izone_oce=2
    285           izone_poubelle=2 ! zone où on met les flux non physiques, de
    286                 ! réajustement
    287           izone_init=2 ! zone d'initialisation par défaut
    288           option_revap=1
    289           option_tmin=0
    290           izone_revap=3
    291           option_cond=0
    292 
    293           strtrac(izone_cont)='con'
    294           strtrac(izone_oce)='oce'
    295           strtrac(izone_revap)='rev'
    296          
    297 
    298         else if (option_traceurs.eq.3) then
    299             ! on trace des bassins océaniques + un résidu. On ne trace
    300             ! pas l'évap des gouttes à part
    301             ! le résidu est la dernère dimension
    302            
    303           ! lire les use_bassin
    304           call getin('use_bassin_atlantic',use_bassin_atlantic)     
    305           call getin('use_bassin_medit',use_bassin_medit)     
    306           call getin('use_bassin_indian',use_bassin_indian)     
    307           call getin('use_bassin_austral',use_bassin_austral)     
    308           call getin('use_bassin_pacific',use_bassin_pacific)     
    309           call getin('use_bassin_merarabie',use_bassin_merarabie)     
    310           call getin('use_bassin_golfebengale',use_bassin_golfebengale)     
    311           call getin('use_bassin_indiansud',use_bassin_indiansud)     
    312           call getin('use_bassin_tropics',use_bassin_tropics)     
    313           call getin('use_bassin_midlats',use_bassin_midlats)     
    314           call getin('use_bassin_hauteslats',use_bassin_hauteslats)
    315 
    316           write(*,*) 'use_bassin_atlantic=' ,use_bassin_atlantic 
    317           write(*,*) 'use_bassin_medit=' ,use_bassin_medit
    318           write(*,*) 'use_bassin_indian=' ,use_bassin_indian
    319           write(*,*) 'use_bassin_austral=' ,use_bassin_austral
    320           write(*,*) 'use_bassin_merarabie=' ,use_bassin_merarabie
    321           write(*,*) 'use_bassin_golfebengale=' ,use_bassin_golfebengale
    322           write(*,*) 'use_bassin_indiansud=' ,use_bassin_indiansud
    323           write(*,*) 'use_bassin_tropics=' ,use_bassin_tropics
    324           write(*,*) 'use_bassin_midlats=' ,use_bassin_midlats
    325           write(*,*) 'use_bassin_hauteslats=' ,use_bassin_hauteslats
    326 
    327        
    328           ntraceurs_zone_opt=2 &
    329      &                   +use_bassin_atlantic &
    330      &                   +use_bassin_medit &
    331      &                   +use_bassin_indian &
    332      &                   +use_bassin_austral &
    333      &                   +use_bassin_pacific &
    334      &                   +use_bassin_merarabie &
    335      &                   +use_bassin_golfebengale &
    336      &                   +use_bassin_indiansud &
    337      &                   +use_bassin_tropics &
    338      &                   +use_bassin_midlats &
    339      &                   +use_bassin_hauteslats
    340 
    341           izone_cont=ntraceurs_zone
    342           izone_oce=0 ! pas de sens car séparée en bassins         
    343           izone_poubelle=ntraceurs_zone-1 ! zone où on met les flux non physiques, de
    344                 ! réajustement
    345           izone_init=ntraceurs_zone-1 ! zone d'initialisation par défaut
    346           option_revap=0 ! on ne trace pas les gouttes
    347           option_tmin=0
    348           izone_revap=0 ! pas de sens car on taggue pas les gouttes séparemment 
    349           option_cond=0
    350 
    351           ! si on a use_bassin_indian, on n'a pas le découpage détaillé
    352           ! de l'indian:
     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, 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
    353239#ifdef ISOVERIF
    354           if (use_bassin_indian.eq.1) then
    355 !              call iso_verif_egalite(float(use_bassin_merarabie), &
    356 !     &            0.0,'iso_traceurs_init 73: revoir def des bassins')
    357                if ((use_bassin_merarabie.ne.0).or. &
    358       &            (use_bassin_indiansud.ne.0).or. &
    359       &            (use_bassin_golfebengale.ne.0)) then
    360                 write(*,*) 'traceurs_init 73'
    361                 stop
    362                endif
    363 !              call iso_verif_egalite(float(use_bassin_golfebengale), &
    364 !     &            0.0,'iso_traceurs_init 73: revoir def des bassins')
    365 !              call iso_verif_egalite(float(use_bassin_indiansud), &
    366 !     &            0.0,'iso_traceurs_init 73: revoir def des bassins')
    367           endif
     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
    368248#endif   
    369          
    370           bassin_atlantic= max(use_bassin_atlantic,1)
    371           bassin_medit=max(use_bassin_atlantic &
    372      &           +use_bassin_medit,1)
    373           bassin_indian=max(use_bassin_atlantic &
    374      &           +use_bassin_medit &
    375      &           +use_bassin_indian,1)
    376           bassin_austral=max(use_bassin_atlantic &
    377      &           +use_bassin_medit &
    378      &           +use_bassin_indian &
    379      &           +use_bassin_austral,1)
    380           bassin_pacific=max(use_bassin_atlantic &
    381      &           +use_bassin_medit &
    382      &           +use_bassin_indian &
    383      &           +use_bassin_austral &
    384      &           +use_bassin_pacific,1)
    385           bassin_merarabie=max(use_bassin_atlantic &
    386      &           +use_bassin_medit &
    387      &           +use_bassin_indian &
    388      &           +use_bassin_austral &
    389      &           +use_bassin_pacific &
    390      &           +use_bassin_merarabie,1)
    391           bassin_golfebengale=max(use_bassin_atlantic&
    392      &           +use_bassin_medit &
    393      &           +use_bassin_indian &
    394      &           +use_bassin_austral &
    395      &           +use_bassin_pacific &
    396      &           +use_bassin_merarabie &
    397      &           +use_bassin_golfebengale,1)
    398           bassin_indiansud=max(use_bassin_atlantic &
    399      &           +use_bassin_medit &
    400      &           +use_bassin_indian &
    401      &           +use_bassin_austral &
    402      &           +use_bassin_pacific &
    403      &           +use_bassin_merarabie &
    404      &           +use_bassin_golfebengale &
    405      &           +use_bassin_indiansud,1)
    406           bassin_tropics=max(use_bassin_atlantic &
    407      &                       +use_bassin_medit &
    408      &                       +use_bassin_indian &
    409      &                       +use_bassin_austral &
    410      &                       +use_bassin_pacific &
    411      &                       +use_bassin_merarabie &
    412      &                       +use_bassin_golfebengale &
    413      &                       +use_bassin_indiansud, &
    414      &                       +use_bassin_tropics,1)
    415           bassin_midlats=max(use_bassin_atlantic &
    416      &                       +use_bassin_medit &
    417      &                       +use_bassin_indian &
    418      &                       +use_bassin_austral &
    419      &                       +use_bassin_pacific &
    420      &                       +use_bassin_merarabie &
    421      &                       +use_bassin_golfebengale &
    422      &                       +use_bassin_indiansud &
    423      &                       +use_bassin_tropics &
    424      &                       +use_bassin_midlats,1)
    425           bassin_hauteslats=max(use_bassin_atlantic &
    426      &                       +use_bassin_medit &
    427      &                       +use_bassin_indian &
    428      &                       +use_bassin_austral &
    429      &                       +use_bassin_pacific &
    430      &                       +use_bassin_merarabie &
    431      &                       +use_bassin_golfebengale &
    432      &                       +use_bassin_indiansud &
    433      &                       +use_bassin_tropics &
    434      &                       +use_bassin_midlats &
    435      &                       +use_bassin_hauteslats,1)
    436 
    437           write(*,*) 'bassin_atlantic=' ,bassin_atlantic 
    438           write(*,*) 'bassin_medit=' ,bassin_medit
    439           write(*,*) 'bassin_indian=' ,bassin_indian
    440           write(*,*) 'bassin_austral=' ,bassin_austral
    441           write(*,*) 'bassin_merarabie=' ,bassin_merarabie
    442           write(*,*) 'bassin_golfebengale=' ,bassin_golfebengale
    443           write(*,*) 'bassin_indiansud=' ,bassin_indiansud
    444           write(*,*) 'bassin_tropics=' ,bassin_tropics
    445           write(*,*) 'bassin_midlats=' ,bassin_midlats
    446           write(*,*) 'bassin_hauteslats=' ,bassin_hauteslats
    447 
    448           if (use_bassin_atlantic.eq.1) then
    449             strtrac(bassin_atlantic)='atl'
    450           endif
    451           if (use_bassin_medit.eq.1) then
    452             strtrac(bassin_medit)='med'
    453           endif
    454           if (use_bassin_indian.eq.1) then
    455             strtrac(bassin_indian)='ind'
    456           endif
    457           if (use_bassin_austral.eq.1) then
    458             strtrac(bassin_austral)='aus'
    459           endif
    460           if (use_bassin_pacific.eq.1) then
    461             strtrac(bassin_pacific)='pac'
    462           endif
    463           if (use_bassin_merarabie.eq.1) then
    464             strtrac(bassin_merarabie)='ara'
    465           endif
    466           if (use_bassin_golfebengale.eq.1) then
    467             strtrac(bassin_golfebengale)='ben'
    468           endif
    469           if (use_bassin_indiansud.eq.1) then
    470             strtrac(bassin_indiansud)='ins'
    471           endif
    472           if (use_bassin_tropics.eq.1) then
    473             strtrac(bassin_tropics)='tro'
    474           endif
    475           if (use_bassin_midlats.eq.1) then
    476             strtrac(bassin_midlats)='mid'
    477           endif
    478           if (use_bassin_hauteslats.eq.1) then
    479             strtrac(bassin_hauteslats)='hau'
    480           endif
    481           strtrac(ntraceurs_zone-1)='res'
    482           strtrac(ntraceurs_zone)='con'
    483 
    484         else if (option_traceurs.eq.4) then
    485           ! on trace les température minimales vécues
    486           ! comme dans article sur LdG sauf pas de revap
    487            
    488           zone_temp1=293.0 ! en K
    489 !          zone_tempf=223.0 ! en K
    490           zone_tempf=243.0 ! en K
    491  ! courbure de la relation entre l'indice et la température: 0 pour linéaire, <0 pour plus de détal en bas
    492 
     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
    493280        ! zone 1: >= zone_temp1
    494         ! zone 2 à 4: intermédiaire,
     281        ! zone 2 a 4: intermediaire,
    495282        ! zone 5: <zone_tempf
    496        
    497           ntraceurs_zone_opt=nzone_temp+1
    498 
    499           zone_tempa=-4.0 ! en K
    500           izone_cont=ntraceurs_zone
    501           izone_oce=ntraceurs_zone 
    502           izone_poubelle=ntraceurs_zone
    503           izone_init=ntraceurs_zone ! zone d'initialisation par défaut
    504           option_revap=0
    505           option_tmin=0 
    506           izone_revap=0
    507           option_cond=0
    508           do izone=1,nzone_temp
    509             write(strz,'(i2.2)') izone
    510             strtrac(izone)='t'//strz
    511             write(*,*) 'izone,strz,strtrac=',izone,strz,strtrac(izone)
    512           enddo
    513           strtrac(izone_poubelle)='pou'
    514 
    515           ! initialisation des zones de tempéarture
    516           do izone=1,nzone_temp-1
    517             zone_temp(izone)=zone_temp1+float(izone-1) &
    518      &                      *(zone_tempa*float(izone-nzone_temp+1) &
    519      &                      +(zone_tempf-zone_temp1)/float(nzone_temp-2))
    520           enddo
    521           write(*,*) 'iso_trac_init 183: zone_temp=',zone_temp         
    522 
    523         elseif (option_traceurs.eq.5) then
    524           ! on trace AEJ/flux de mousson/Harmattan
    525 !          write(*,*) 'iso_traceurs_init 129'
    526 
    527           ntraceurs_zone_opt=4
    528           izone_cont=1
    529           izone_oce=1
    530           izone_poubelle=1 ! zone où on met les flux non physiques, de
    531                 ! réajustement
    532           izone_init=1 ! zone d'initialisation par défaut
    533           option_revap=0
    534           option_tmin=0
    535           izone_revap=0
    536           izone_aej=2
    537           izone_mousson=3
    538           izone_harmattan=4
    539           option_cond=0
    540 
    541           strtrac(izone_poubelle)='res'
    542           strtrac(izone_aej)='aej'
    543           strtrac(izone_mousson)='mou'
    544           strtrac(izone_harmattan)='sah'
    545 
    546         elseif (option_traceurs.eq.6) then
    547           ! on trace les ddfts
    548 
    549           ntraceurs_zone_opt=2
    550           izone_cont=1
    551           izone_oce=1
    552           izone_poubelle=1 ! zone où on met les flux non physiques, de
    553                 ! réajustement
    554           izone_init=1 ! zone d'initialisation par défaut
    555           option_revap=0
    556           option_tmin=0
    557           izone_revap=0
    558           izone_ddft=2
    559           option_cond=0
    560 
    561           strtrac(izone_poubelle)='res'
    562           strtrac(izone_ddft)='dft'
    563 
    564         elseif (option_traceurs.eq.9) then
    565           ! on trace le condensat
    566 
    567           ntraceurs_zone_opt=3
    568           izone_cont=1
    569           izone_oce=1
    570           izone_poubelle=1 ! zone où on met les flux non physiques, de
    571                 ! réajustement
    572           izone_init=1 ! zone d'initialisation par défaut
    573           option_revap=1
    574           option_tmin=0
    575           izone_revap=2
    576           izone_cond=3
    577           option_cond=1
    578 
    579           ! 1 par défaut pour colorier à la fois condensat LS et
    580           ! condensat convectif. Mais on peut mettre 2 si on ne veut que
    581           ! collorier que le condensat convectif.
    582           call getin('option_cond',option_cond)
    583           write(*,*) 'option_cond=',option_cond
    584 
    585           strtrac(izone_poubelle)='res'
    586           strtrac(izone_cond)='con'
    587           strtrac(izone_revap)='rev'
    588 
    589         elseif (option_traceurs.eq.10) then
    590           ! on trace l'évap venant de ocean/continent no frac/continent frac
    591           !  utilse seulement si couplé avec ORCHIDEE
    592 #ifdef CPP_VEGET
    593 #else
    594           write(*,*) 'iso_traceurs_init 219: option_traceurs=10 ', &
    595      &                      'inutile si on ne couple pas avec ORCHIDEE'
    596           stop
     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
    597364#endif         
    598 
    599           ntraceurs_zone_opt=3
    600           izone_cont=1 ! sous-entendu non fractionnant
    601           izone_oce=2
    602           izone_poubelle=2 ! zone où on met les flux non physiques, de
    603                 ! réajustement
    604           izone_init=2 ! zone d'initialisation par défaut
    605           option_revap=0
    606           option_tmin=0
    607           izone_revap=0
    608           izone_contfrac=3
    609           izone_contcanop=3
    610           izone_irrig=0
    611           option_cond=0
    612 
    613           strtrac(izone_oce)='oce'
    614           strtrac(izone_cont)='con' 
    615           strtrac(izone_contfrac)='enu'  ! evap sol nu
    616 
    617         elseif (option_traceurs.eq.11) then
    618           ! on trace reevap des gouttes et le reste
    619 
    620           ntraceurs_zone_opt=2
    621           izone_cont=1
    622           izone_oce=1
    623           izone_poubelle=1 ! zone où on met les flux non physiques, de
    624                 ! réajustement
    625           izone_init=1 ! zone d'initialisation par défaut
    626           option_revap=1
    627           option_tmin=0
    628           izone_revap=2
    629           izone_irrig=0
    630           option_cond=0
    631 
    632           strtrac(izone_poubelle)='res'
    633           strtrac(izone_revap)='rev'
    634 
    635         elseif (option_traceurs.eq.12) then
    636           ! on trace evap du sol nu, evap de la canopée, reste de l'evap cont et
    637           ! evap oce
    638 #ifdef CPP_VEGET
    639 #else
    640           write(*,*) 'iso_traceurs_init 257: option_traceurs=10 ', &
    641      &                      'inutile si on ne couple pas avec ORCHIDEE'
    642           stop
     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
    643400#endif           
    644 
    645           ntraceurs_zone_opt=2
    646           izone_cont=1
    647           izone_oce=2
    648           izone_poubelle=2 ! zone où on met les flux non physiques, de
    649                 ! réajustement
    650           izone_init=2 ! zone d'initialisation par défaut
    651           option_revap=0
    652           option_tmin=0
    653           izone_revap=0
    654           izone_contfrac=3
    655           izone_contcanop=4
    656           izone_irrig=0   
    657           option_cond=0
    658 
    659           strtrac(izone_oce)='oce'
    660           strtrac(izone_cont)='con'
    661           strtrac(izone_contfrac)='enu'  ! evap sol nu
    662           strtrac(izone_contcanop)='eca'  ! evap canop
    663 
    664        else if (option_traceurs.eq.13) then
    665           ! on trace les température minimales vécues + la revap
    666           ! comme dans article sur LdG
    667            
    668         zone_temp1=293.0         ! en K       
    669 !        parameter (zone_tempf=223.0) ! en K
    670         zone_tempf=243.0 ! en K
    671         zone_tempa=-4.0 ! courbure de la relation entre l'indice et la température: 0 pour linéaire, <0 pour plus de détal en bas
    672 
    673         ! zone 1: >= zone_temp1
    674         ! zone 2 à 4: intermédiaire,
    675         ! zone 5: <zone_tempf
    676        
    677           ntraceurs_zone_opt=nzone_temp+1
    678          
    679           izone_cont=1
    680           izone_oce=1 
    681           izone_poubelle=1
    682           izone_init=1 ! zone d'initialisation par défaut
    683           option_revap=1   
    684           option_tmin=0
    685           izone_revap=ntraceurs_zone
    686           izone_irrig=0
    687           option_cond=0
    688           do izone=1,nzone_temp
    689             write(strz,'(i2.2)') izone
    690             strtrac(izone)='t'//strz
    691             write(*,*) 'izone,strz,strtrac=',izone,strz,strtrac(izone)
    692           enddo
    693           strtrac(izone_revap)='rev'
    694 
    695           ! initialisation des zones de tempéarture
    696           do izone=1,nzone_temp-1
    697             zone_temp(izone)=zone_temp1+float(izone-1) &
    698      &                      *(zone_tempa*float(izone-nzone_temp+1) &
    699      &                      +(zone_tempf-zone_temp1)/float(nzone_temp-2))
    700           enddo
    701           write(*,*) 'zone_temp=',zone_temp
    702 
    703        else if (option_traceurs.eq.14) then
    704           ! on trace les pres et lat de dernière saturation définies
    705           ! comme rh>90%
    706            
    707         zone_pres1=600.0*100.0 ! en Pa       
    708         zone_presf=300.0*100.0 ! en Pa
    709         zone_presa=0.0 ! courbure de la relation entre l'indice et la température: 0 pour linéaire, <0 pour plus de détal en bas
    710 
    711         lattag_min=10.0 ! en degrès
    712         dlattag=15.0
    713 
    714         ! zone 1: >= zone_pres1
    715         ! zone 2 à 4: intermédiaire,
    716         ! zone 5: <zone_presf
    717        
    718          ntraceurs_zone_opt=nzone_pres*nzone_lat+1         
    719           izone_cont=ntraceurs_zone
    720           izone_oce=ntraceurs_zone
    721           izone_poubelle=ntraceurs_zone
    722           izone_init=ntraceurs_zone ! zone d'initialisation par défaut
    723           option_revap=0 
    724           option_tmin=0
    725           izone_revap=0
    726           izone_irrig=0
    727           option_cond=0
    728           do izone_pres=1,nzone_pres
    729            do izone_lat=1,nzone_lat
    730             write(strz_pres,'(i1.1)') izone_pres
    731             write(strz_lat,'(i1.1)') izone_lat
    732             strz_preslat=strz_pres//strz_lat
    733             izone=izone_lat+(izone_pres-1)*nzone_lat
    734             strtrac(izone)='t'//strz_preslat
    735             write(*,*) 'izone_pres,izone_lat,strtrac=', &
    736      &                        izone_pres,izone_lat,izone,strtrac(izone)
    737            enddo !do izone_lat=1,nzone_lat
    738           enddo !do izone_pres=1,nzone_pres
    739           strtrac(ntraceurs_zone)='sfc'
    740 
    741           ! initialisation des zones de tempéarture
    742           do izone=1,nzone_pres-1
    743             zone_pres(izone)=zone_pres1+float(izone-1) &
    744      &                      *(zone_presa*float(izone-nzone_pres+1) &
    745      &                      +(zone_presf-zone_pres1)/float(nzone_pres-2))
    746           enddo !do izone=1,nzone_pres-1
    747           write(*,*) 'traceurs_init 332: zone_pres=',zone_pres
    748 !          stop
    749 !
    750        elseif (option_traceurs.eq.15) then
    751           ! on trace l'irrigation dans ORCHIDEE
    752 #ifdef CPP_VEGET
    753 #else
    754           write(*,*) 'iso_traceurs_init 257: option_traceurs=15 ', &
    755      &                      'inutile si on ne couple pas avec ORCHIDEE'
    756           stop
     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
    757490#endif
    758 
    759           ntraceurs_zone_opt=1
    760           izone_cont=1
    761           izone_oce=1
    762           izone_poubelle=1 ! zone où on met les flux non physiques, de
    763                 ! réajustement
    764           izone_init=1 ! zone d'initialisation par défaut
    765           option_revap=0
    766           option_tmin=0
    767           izone_revap=0
    768           izone_contfrac=0
    769           izone_contcanop=0
    770           izone_irrig=2
    771           option_cond=0
    772          
    773           strtrac(izone_poubelle)='res'
    774           strtrac(izone_irrig)='irrig'
    775 
    776           ! dans ce cas particulier, il y a des traceurs dans ORCHIDEE
    777           ntracisoOR=ntiso
    778 
    779         else if ((option_traceurs.eq.17).or. &
    780      &           (option_traceurs.eq.18)) then
    781           ! on trace les température minimales vécues
    782           ! comme dans article sur LdG sauf pas de revap
    783            
    784         zone_temp1=12.0e-3 ! en kg/kg       
    785         zone_tempf=0.2e-3 ! en kg/kg
    786         zone_tempa=1.2e-3 ! courbure de la relation entre l'indice et la température: 0 pour linéaire, <0 pour plus de détail en bas
    787 
    788 !       parameter (zone_temp1=14.0e-3) ! en kg/kg       
    789 !       parameter (zone_tempf=0.2e-3) ! en kg/kg
    790 !       parameter (zone_tempa=0.5e-3)       
    791 
    792 !        parameter (zone_temp1=10.0e-3) ! en kg/kg
    793 !       parameter (zone_tempf=0.5e-3) ! en kg/kg
    794 !       parameter (zone_tempa=0.5e-3)
    795 
    796         ! zone 1: >= zone_temp1
    797         ! zone 2 à 4: intermédiaire,
    798         ! zone 5: <zone_tempf
    799        
    800         ntraceurs_zone_opt=nzone_temp+3
    801        
    802           izone_cont=nzone_temp+1
    803           izone_oce=nzone_temp+1
    804           izone_poubelle=nzone_temp+1
    805           izone_init=nzone_temp+1 ! zone d'initialisation par défaut
    806           option_revap=1 
    807           option_tmin=1
    808           option_cond=1
    809 
    810           izone_revap=nzone_temp+3
    811           izone_cond=nzone_temp+2
    812           do izone=1,nzone_temp
    813             write(strz,'(i2.2)') izone
    814             strtrac(izone)='t'//strz
    815             write(*,*) 'izone,strz,strtrac=',izone,strz,strtrac(izone)
    816           enddo !do izone=1,nzone_temp
    817           strtrac(izone_poubelle)='sfc'
    818           strtrac(izone_cond)='con'
    819           strtrac(izone_revap)='rev'
    820 
    821           ! initialisation des zones de tempéarture
    822           do izone=1,nzone_temp-1
    823             zone_temp(izone)=zone_temp1+float(izone-1) &
    824      &                      *(zone_tempa*float(izone-nzone_temp+1) &
    825      &             +(zone_tempf-zone_temp1)/float(nzone_temp-2))
    826           enddo
    827          write(*,*) 'zone_temp1,zone_tempf,zone_tempa=', &
    828      &              zone_temp1,zone_tempf,zone_tempa
    829           write(*,*) 'zone_temp=',zone_temp
    830 !          stop         
    831 
    832         else if (option_traceurs.eq.19) then
    833 
    834         zone_temp1=12.0e-3 ! en kg/kg       
    835         zone_tempf=0.2e-3 ! en kg/kg
    836         zone_tempa=1.2e-3 ! courbure de la relation entre l'indice et la température: 0 pour linéaire, <0 pour plus de détail en bas
    837 
    838 !       parameter (zone_temp1=14.0e-3) ! en kg/kg       
    839 !       parameter (zone_tempf=0.2e-3) ! en kg/kg
    840 !       parameter (zone_tempa=0.5e-3)       
    841 
    842 !        parameter (zone_temp1=10.0e-3) ! en kg/kg
    843 !       parameter (zone_tempf=0.5e-3) ! en kg/kg
    844 !       parameter (zone_tempa=0.5e-3)
    845 
    846         ! zone 1: >= zone_temp1
    847         ! zone 2 à 4: intermédiaire,
    848         ! zone 5: <zone_tempf
    849        
    850         ntraceurs_zone_opt=nzone_temp+4
    851        
    852           izone_cont=nzone_temp+1
    853           izone_oce=nzone_temp+1
    854           izone_poubelle=nzone_temp+1
    855           if (option_seuil_tag_tmin.eq.1) then
    856             izone_init=nzone_temp+1 ! zone d'initialisation par défaut
    857           else
     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
    858570            izone_init=nzone_temp
    859           endif
    860           option_revap=1   
    861           izone_revap=nzone_temp+3
    862           izone_cond=nzone_temp+2
    863           izone_ddft=nzone_temp+4
    864           option_tmin=1         
    865           option_cond=1
    866           do izone=1,nzone_temp
    867             write(strz,'(i2.2)') izone
    868             strtrac(izone)='t'//strz
    869             write(*,*) 'izone,strz,strtrac=',izone,strz,strtrac(izone)
    870           enddo !do izone=1,nzone_temp
    871           strtrac(izone_poubelle)='sfc'
    872           strtrac(izone_cond)='con'
    873           strtrac(izone_revap)='rev'
    874           strtrac(izone_ddft)='dft'
    875 
    876         elseif (option_traceurs.eq.20) then
    877           ! on vapeur tropical/extractropicale/recyclage extractropical
    878           ! pour comprendre controles humidité et isotopes subtropicaux.       
    879          
    880           lim_tag20=35.0
    881           call getin('lim_tag20',lim_tag20)
    882           write(*,*) 'lim_tag20=',lim_tag20
    883 
    884           ntraceurs_zone_opt=3
    885           izone_cont=1
    886           izone_oce=1
    887           izone_poubelle=2 ! zone où on met les flux non physiques, de
    888                 ! réajustement
    889           izone_init=2 ! zone d'initialisation par défaut
    890           option_revap=0
    891           option_tmin=0
    892           izone_revap=0
    893           izone_trop=2
    894           izone_extra=3
    895 
    896           strtrac(izone_trop)='tro' ! vapeur tropicale
    897           strtrac(izone_extra)='ext' ! vapeur extractropicale evaporée
    898                 ! dans les tropiques
    899           strtrac(izone_cont)='rec' ! recyclage
    900 
    901         elseif (option_traceurs.eq.21) then
    902           ! on trace 2 boites 3D: UT tropicale et extratropiques
    903           ! fonctionnement similaire à option 5 pour taggage des zones
    904           ! AMMA
    905 !          write(*,*) 'iso_traceurs_init 129'
    906 
    907           ntraceurs_zone_opt=3
    908           izone_cont=1
    909           izone_oce=1
    910           izone_poubelle=1 ! zone où on met les flux non physiques, de
    911                 ! réajustement
    912           izone_init=1 ! zone d'initialisation par défaut
    913           option_revap=0
    914           option_tmin=0
    915           izone_revap=0
    916           izone_trop=2
    917           izone_extra=3
    918           option_cond=0
    919 
    920           strtrac(izone_poubelle)='res'
    921           strtrac(izone_trop)='tro'
    922           strtrac(izone_extra)='ext'
    923 
    924         elseif (option_traceurs.eq.22) then
    925           ! on trace la vapeur qui a été processée dans zones de
    926           ! convections à 3 niveaux: BT, MT et UT
    927 
    928           lim_precip_tag22=20.0
    929           call getin('lim_precip_tag22',lim_precip_tag22)
    930           write(*,*) 'lim_precip_tag22=',lim_precip_tag22
    931 
    932           ntraceurs_zone_opt=3
    933           izone_cont=1
    934           izone_oce=1
    935           izone_poubelle=1 ! zone où on met les flux non physiques, de
    936                 ! réajustement
    937           izone_init=1 ! zone d'initialisation par défaut
    938           option_revap=0
    939           option_tmin=0
    940           izone_revap=0
    941           izone_conv_BT=2
    942           izone_conv_UT=3
    943           option_cond=0
    944 
    945           strtrac(izone_poubelle)='res'
    946           strtrac(izone_conv_BT)='cbt'
    947           strtrac(izone_conv_UT)='cut'
    948 
    949         else
    950             write(*,*) 'traceurs_init 36: option pas encore prévue'
    951             stop
    952         endif
    953 
    954        
    955           if (ntraceurs_zone_opt.ne.ntraceurs_zone) then
    956                 write(*,*) 'ntraceurs_zone_opt,ntraceurs_zone=', &
    957                         & ntraceurs_zone_opt,ntraceurs_zone
    958                 call abort_physic ('isotrac_mod','ntraceurs_zone incoherent',1)
    959           endif
    960 
    961        
    962         ! seuil sur le taux de condensation
    963         if (option_tmin.eq.1) then
    964           seuil_tag_tmin=0.01
    965           call getin('seuil_tag_tmin',seuil_tag_tmin)
    966           write(*,*) 'seuil_tag_tmin=',seuil_tag_tmin
    967 
    968           seuil_tag_tmin_ls=seuil_tag_tmin
    969           call getin('seuil_tag_tmin_ls',seuil_tag_tmin_ls)
    970           write(*,*) 'seuil_tag_tmin_ls=',seuil_tag_tmin_ls
    971 
    972           option_seuil_tag_tmin=1
    973           call getin('option_seuil_tag_tmin',option_seuil_tag_tmin)
    974           write(*,*) 'option_seuil_tag_tmin=',option_seuil_tag_tmin
    975         endif
    976 
    977 
    978         do ixt=1,niso
    979            index_zone(ixt)=0
    980            index_iso(ixt)=ixt
    981         enddo
    982         itrac=niso       
    983         do izone=1,ntraceurs_zone
    984           do ixt=1,niso
    985             itrac=itrac+1
    986             index_zone(itrac)=izone
    987             index_iso(itrac)=ixt
    988             itZonIso_loc(izone,ixt)=itrac
    989             if (itZonIso(izone,ixt).ne.itZonIso_loc(izone,ixt)) then
    990                 write(*,*) 'isotrac 989: izone,ixt,itrac=',izone,ixt,itrac
    991                 CALL abort_physic ('isotrac','isotrac 989',1)
    992             endif
    993           enddo
    994         enddo
     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' ; STOP
     641   END SELECT
     642
     643   IF(nzone_opt /= nzone) THEN
     644      WRITE(*,*) 'nzone_opt, nzone=', nzone_opt, nzone
     645      CALL abort_physic ('isotrac_mod','nzone incoherent',1)
     646   END IF
     647
     648   !--- Condensation rate threshold
     649   IF(option_tmin == 1) THEN
     650      seuil_tag_tmin = 0.01
     651      CALL get_in('seuil_tag_tmin',        seuil_tag_tmin,        0.01)
     652      CALL get_in('seuil_tag_tmin_ls',     seuil_tag_tmin_ls,     seuil_tag_tmin)
     653      CALL get_in('option_seuil_tag_tmin', option_seuil_tag_tmin, 1)
     654   END IF
     655   DO ixt=1,niso
     656      index_zone(ixt)=0
     657      index_iso(ixt)=ixt
     658   END DO
     659
     660   index_zone = [(INDEX(isoZone, strTail(         isoName(ixt) ,'_')), ixt=1, ntiso)]
     661   index_iso  = [(INDEX(isoName, strHead(delPhase(isoName(ixt)),'_')), ixt=1, ntiso)]
     662   itZonIso_loc = itZonIso(:,:)
    995663#ifdef ISOVERIF
    996 !        call iso_verif_egalite(float(itrac),float(ntiso), &
    997 !     &           'traceurs_init 50')
    998         if (itrac.ne.ntiso) then
    999           write(*,*) 'traceurs_init 50'
    1000           stop
    1001         endif
    1002      
    1003         write(*,*) 'traceurs_init 65: bilan de l''init:'
    1004         write(*,*) 'index_zone=',index_zone(1:ntiso)
    1005         write(*,*) 'index_iso=',index_iso(1:ntiso)
    1006         write(*,*) 'itZonIso=',itZonIso(1:ntraceurs_zone,1:niso)
    1007         do izone=1,ntraceurs_zone
    1008           write(*,*) 'strtrac(',izone,')=',strtrac(izone)
    1009         enddo !do izone=1,ntraceurs_zone
    1010         write(*,*) 'ntracisoOR=',ntracisoOR
     664   WRITE(*,*) 'traceurs_init 65: bilan de l''init:'
     665   WRITE(*,*) 'index_zone = '//TRIM(strStack(int2str(index_zone(1:ntiso))))
     666   WRITE(*,*) 'index_iso  = '//TRIM(strStack(int2str(index_iso (1:ntiso))))
     667   DO izone=1,nzone
     668      WRITE(*,*)'itZonIso('//TRIM(int2str(izone))//',:) = '//strStack(int2str(itZonIso(izone,:)))
     669   END DO
     670   DO izone=1,nzone
     671      WRITE(*,*)'strtrac('//TRIM(int2str(izone))//',:) = '//TRIM(strtrac(izone))
     672   END DO
     673   WRITE(*,*) 'ntracisoOR=',ntracisoOR
    1011674#endif 
    1012675
    1013         end subroutine iso_traceurs_init
    1014 
     676END SUBROUTINE iso_traceurs_init
    1015677
    1016678END MODULE isotrac_mod
Note: See TracChangeset for help on using the changeset viewer.