MODULE infotrac USE strings_mod, ONLY: msg, find, strIdx, strFind, strHead, dispTable, cat, get_in, & fmsg, test, int2str, strParse, strTail, strReduce, strStack, modname, testFile USE readTracFiles_mod, ONLY: readTracersFiles, getKey_init, nphases, delPhase, aliasTracer, & tran0, readIsotopesFile, getKey, known_phases, addPhase, indexUpdate USE trac_types_mod, ONLY: tra, iso, kys IMPLICIT NONE PRIVATE !=== FOR TRACERS: PUBLIC :: tra, tracers, type_trac !--- Derived type, full database, tracers type keyword PUBLIC :: nqtot, nbtr, nqo !--- Main dimensions PUBLIC :: infotrac_init, aliasTracer !--- Initialization, tracers alias creation PUBLIC :: itr_indice !--- Indexes of the tracers passed to phytrac PUBLIC :: niadv !--- Indexes of true tracers (<=nqtot, such that iadv(idx)>0) PUBLIC :: solsym, conv_flg, pbl_flg !=== FOR ISOTOPES: General !--- General PUBLIC :: iso, isotopes, nbIso !--- Derived type, full isotopes families database + nb of families PUBLIC :: isoSelect , ixIso !--- Isotopes family selection tool + selected family index !=== FOR ISOTOPES: Specific to H2O isotopes PUBLIC :: iH2O, tnat, alpha_ideal !--- H2O isotopes index, natural abundance, fractionning coeff. !=== FOR ISOTOPES: Depending on selected isotopes family PUBLIC :: isotope, isoKeys !--- Selected isotopes database + associated keys (cf. getKey) PUBLIC :: isoName, isoZone, isoPhas !--- Isotopes and tagging zones names, phases PUBLIC :: niso, nzon, npha, nitr !--- " " numbers + isotopes & tagging tracers number PUBLIC :: iZonIso, iTraPha !--- 2D index tables to get "iq" index PUBLIC :: isoCheck !--- Run isotopes checking routines !=== FOR BOTH TRACERS AND ISOTOPES PUBLIC :: getKey !--- Get a key from "tracers" or "isotope" !=== FOR STRATOSPHERIC AEROSOLS #ifdef CPP_StratAer PUBLIC :: nbtr_bin, nbtr_sulgas, id_OCS_strat, id_H2SO4_strat, id_SO2_strat, id_BIN01_strat, id_TEST_strat #endif INTERFACE isoSelect; MODULE PROCEDURE isoSelectByIndex, isoSelectByName; END INTERFACE isoSelect !=== CONVENTIONS FOR TRACERS NUMBERS: ! |--------------------+----------------------+-----------------+---------------+----------------------------| ! | water in different | water tagging | water isotopes | other tracers | additional tracers moments | ! | phases: H2O-[gls] | isotopes | | | for higher order schemes | ! |--------------------+----------------------+-----------------+---------------+----------------------------| ! | | | | | | ! |<-- nqo -->|<-- nqo*niso* nzon -->|<-- nqo*niso -->|<-- nbtr -->|<-- (nmom) -->| ! | | | | ! | |<-- nqo*niso*(nzon+1) = nqo*nitr -->|<-- nqtottr = nbtr + nmom -->| ! | = nqtot - nqo*(nitr+1) | ! | | ! |<-- nqtrue = nbtr + nqo*(nitr+1) -->| | ! | | ! |<-- nqtot = nqtrue + nmom -->| ! | | ! |----------------------------------------------------------------------------------------------------------| ! NOTES FOR THIS TABLE: ! * The used "niso", "nzon" and "nitr" are the H2O components of "isotopes(ip)" (isotopes(ip)%prnt == 'H2O'), ! since water is so far the sole tracers family removed from the main tracers table. ! * For water, "nqo" is equal to the more general field "isotopes(ip)%npha". ! * "niso", "nzon", "nitr", "npha" are defined for other isotopic tracers families, if any. ! !=== TRACERS DESCRIPTOR: DERIVED TYPE EMBEDDING MOST OF THE USEFUL QUANTITIES (LENGTH: nqtot) ! Each entry is accessible using "%" sign. ! |------------+-------------------------------------------------+-------------+------------------------+ ! | entry | Meaning | Former name | Possible values | ! |------------+-------------------------------------------------+-------------+------------------------+ ! | name | Name (short) | tname | | ! | nam1 | Name of the 1st generation ancestor | / | | ! | prnt | Name of the parent | / | | ! | lnam | Long name (with adv. scheme suffix) for outputs | ttext | | ! | type | Type (so far: tracer or tag) | / | tracer,tag | ! | phas | Phases list ("g"as / "l"iquid / "s"olid) | / | [g][l][s] | ! | iadv | Advection scheme number | iadv | 1-20,30 exc. 3-9,15,19 | ! | igen | Generation (>=1) | / | | ! | itr | Index in "tr_seri" (0: absent from physics) | cf. niadv | 1:nqtottr | ! | iprnt | Index of the parent tracer | iqpere | 1:nqtot | ! | idesc | Indexes of the childs (all generations) | iqfils | 1:nqtot | ! | ndesc | Number of the descendants (all generations) | nqdesc | 1:nqtot | ! | nchld | Number of childs (first generation only) | nqfils | 1:nqtot | ! | keys | key/val pairs accessible with "getKey" routine | / | | ! | iso_num | Isotope name index in iso(igr)%name(:) | iso_indnum | 1:niso | ! | iso_zon | Isotope zone index in iso(igr)%zone(:) | zone_num | 1:nzon | ! | iso_pha | Isotope phase index in iso(igr)%phas | phase_num | 1:npha | ! +------------+-------------------------------------------------+-------------+------------------------+ ! !=== ISOTOPES DESCRIPTOR: DERIVED TYPE EMBEDDING MOST OF THE USEFUL QUANTITIES (LENGTH: NUMBER OF ISOTOPES FAMILIES USED) ! Each entry is accessible using "%" sign. ! |------------+-------------------------------------------------+-------------+-----------------------+ ! | entry | Meaning | Former name | Possible values | ! |------------+-------------------------------------------------+-------------+-----------------------+ ! | prnt | Parent tracer (isotopes family name) | | | ! | trac, nitr | Isotopes & tagging tracers + number of elements | | | ! | zone, nzon | Geographic tagging zones + number of elements | | | ! | phas, npha | Phases list + number of elements | | [g][l][s], 1:3 | ! | niso | Number of isotopes, excluding tagging tracers | | | ! | iTraPha | Index in "xt" = f(iname(niso+1:nitr),iphas) | iqiso | 1:niso | ! | iZonIso | Index in "xt" = f(izone, iname(1:niso)) | index_trac | 1:nzon | ! |------------+-------------------------------------------------+-------------+-----------------------+ !=== DIMENSIONS OF THE TRACERS TABLES AND OTHER SCALAR VARIABLES INTEGER, SAVE :: nqtot, & !--- Tracers nb in dynamics (incl. higher moments & water) nbtr, & !--- Tracers nb in physics (excl. higher moments & water) nqo, & !--- Number of water phases nbIso !--- Number of available isotopes family CHARACTER(LEN=256), SAVE :: type_trac !--- Keyword for tracers type !$OMP THREADPRIVATE(nqtot, nbtr, nqo, nbIso, type_trac) !=== DERIVED TYPES EMBEDDING MOST INFORMATIONS ABOUT TRACERS AND ISOTOPES FAMILIES TYPE(tra), TARGET, SAVE, ALLOCATABLE :: tracers(:) !=== TRACERS DESCRIPTORS VECTOR TYPE(iso), TARGET, SAVE, ALLOCATABLE :: isotopes(:) !=== ISOTOPES PARAMETERS VECTOR !$OMP THREADPRIVATE(tracers, isotopes) !=== ALIASES FOR CURRENTLY SELECTED ISOTOPES FAMILY OF VARIABLES EMBEDDED IN THE VECTOR "isotopes" TYPE(iso), SAVE, POINTER :: isotope !--- CURRENTLY SELECTED ISOTOPES FAMILY DESCRIPTOR INTEGER, SAVE :: ixIso, iH2O !--- Index of the selected isotopes family and H2O family LOGICAL, SAVE, POINTER :: isoCheck !--- Flag to trigger the checking routines TYPE(kys), SAVE, POINTER :: isoKeys(:) !--- ONE SET OF KEYS FOR EACH ISOTOPE (LISTED IN isoName) CHARACTER(LEN=256), SAVE, POINTER :: isoName(:), & !--- ISOTOPES NAMES FOR THE CURRENTLY SELECTED FAMILY isoZone(:), & !--- TAGGING ZONES FOR THE CURRENTLY SELECTED FAMILY isoPhas !--- USED PHASES FOR THE CURRENTLY SELECTED FAMILY INTEGER, SAVE :: niso, nzon, npha, & !--- NUMBER OF ISOTOPES, TAGGING ZONES AND PHASES nitr !--- NUMBER OF ISOTOPES + ISOTOPIC TAGGING TRACERS INTEGER, SAVE, POINTER :: iZonIso(:,:) !--- INDEX IN "isoTrac" AS f(tagging zone, isotope) INTEGER, SAVE, POINTER :: iTraPha(:,:) !=== INDEX IN "isoTrac" AS f(isotopic tracer, phase) !$OMP THREADPRIVATE(isotope, ixIso,iH2O, isoCheck, isoKeys, isoName,isoZone,isoPhas, niso,nzon,npha,nitr, iZonIso,iTraPha) !=== VARIABLES EMBEDDED IN "tracers", BUT DUPLICATED, AS THEY ARE RATHER FREQUENTLY USED + VARIABLES FOR INCA REAL, SAVE, ALLOCATABLE :: tnat(:), & !--- Natural relative abundance of water isotope (niso) alpha_ideal(:) !--- Ideal fractionning coefficient (for initial state) (niso) INTEGER, SAVE, ALLOCATABLE :: conv_flg(:), & !--- Convection activation ; needed for INCA (nbtr) pbl_flg(:), & !--- Boundary layer activation ; needed for INCA (nbtr) itr_indice(:), & !--- Indexes of the tracers passed to phytrac (nqtottr) niadv(:) CHARACTER(LEN=8), SAVE, ALLOCATABLE :: solsym(:) !--- Names from INCA (nbtr) !OMP THREADPRIVATE(tnat, alpha_ideal, conv_flg, pbl_flg, itr_indice, solsym) #ifdef CPP_StratAer !=== SPECIFIC TO STRATOSPHERIC AEROSOLS (CK/OB) INTEGER, SAVE :: nbtr_bin, nbtr_sulgas, id_OCS_strat, id_H2SO4_strat, id_SO2_strat, id_BIN01_strat, id_TEST_strat !OMP THREADPRIVATE(nbtr_bin, nbtr_sulgas, id_OCS_strat, id_H2SO4_strat, id_SO2_strat, id_BIN01_strat, id_TEST_strat) #endif CONTAINS SUBROUTINE infotrac_init USE control_mod, ONLY: planet_type, config_inca #ifdef REPROBUS USE chem_rep, ONLY: Init_chem_rep_trac #endif !============================================================================================================================== ! ! Auteur: P. Le Van /L. Fairhead/F.Hourdin ! ------- ! ! Modifications: ! -------------- ! 05/94: F.Forget Modif special traceur ! 02/02: M-A Filiberti Lecture de traceur.def ! 06/20: D. Cugnet Nouveaux tracer.def et tracer_*.def + encapsulation (types tr et iso) ! ! Objet: ! ------ ! GCM LMD nouvelle grille ! !============================================================================================================================== ! ... modification de l'integration de q ( 26/04/94 ) .... !------------------------------------------------------------------------------------------------------------------------------ ! Declarations: ! INCLUDE "dimensions.h" !------------------------------------------------------------------------------------------------------------------------------ ! Local variables INTEGER, ALLOCATABLE :: hadv(:), hadv_inca(:), & !--- Horizontal/vertical transport scheme number vadv(:), vadv_inca(:) !--- + specific INCA versions CHARACTER(LEN=1) :: ph !--- Phase CHARACTER(LEN=2) :: suff(9) !--- Suffixes for schemes of order 3 or 4 (Prather) CHARACTER(LEN=3) :: descrq(30) !--- Advection scheme description CHARACTER(LEN=4) :: oldH2O(3) !--- Old water names CHARACTER(LEN=256) :: newH2O, iname, isoPhase !--- New water and isotope names, phases list CHARACTER(LEN=256) :: msg1, msg2 !--- Strings for messages CHARACTER(LEN=256), ALLOCATABLE, DIMENSION(:) :: & !--- Temporary storage isoName, isoZone, tra0, zon0, tag0, n, p, z, str INTEGER :: fType !--- Tracers description file type ; 0: none !--- 1: "traceur.def" 2: "tracer.def" 3: "tracer_*.def" INTEGER :: nqtrue !--- Tracers nb from tracer.def (no higher order moments) INTEGER :: iad !--- Advection scheme INTEGER :: iH2O !--- Index in "isotopes(:)" of H2O family INTEGER :: ic,ip,iq,jq, it,nt, im,nm, ix, iz, niso, nzone, ntiso !--- Indexes and temporary variables LOGICAL, ALLOCATABLE :: lisoGen2(:), & !--- Mask for second generation isotopes lisoName(:), & !--- Mask for water isotopes lisoZone(:), ll(:) !--- Mask for water isotopes tagging tracers LOGICAL :: lerr TYPE(tra), ALLOCATABLE, TARGET :: ttr(:) TYPE(tra), POINTER :: t1, t(:) TYPE(iso), POINTER :: s !------------------------------------------------------------------------------------------------------------------------------ ! Initialization : !------------------------------------------------------------------------------------------------------------------------------ modname = 'infotrac_init' type_trac='lmdz'!'lmdz,inca' suff = ['x ','y ','z ','xx','xy','xz','yy','yz','zz'] descrq( 1: 2) = ['LMV','BAK'] descrq(10:20) = ['VL1','VLP','FH1','FH2','VLH',' ','PPM','PPS','PPP',' ','SLP'] descrq(30) = 'PRA' oldH2O = ['H2Ov','H2Ol','H2Oi'] !--- MESSAGE ABOUT THE CHOSEN CONFIGURATION CALL msg('type_trac='//TRIM(type_trac)) IF(strParse(type_trac, ',', str, n=nt)) CALL abort_gcm(modname,'can''t parse "type_trac = '//TRIM(type_trac)//'"',1) DO it = 1, nt !--- nt>1 if "type_trac" is a coma-separated keywords list msg1 = 'For type_trac = "'//TRIM(str(it))//'":' SELECT CASE(str(it)) CASE('inca'); CALL msg(TRIM(msg1)//' coupling with INCA chemistry model, config_inca='//config_inca) CASE('repr'); CALL msg(TRIM(msg1)//' coupling with REPROBUS chemistry model') CASE('co2i'); CALL msg(TRIM(msg1)//' you have chosen to run with CO2 cycle') CASE('coag'); CALL msg(TRIM(msg1)//' tracers are treated for COAGULATION tests') CASE('lmdz'); CALL msg(TRIM(msg1)//' tracers are treated in LMDZ only') CASE DEFAULT CALL abort_gcm(modname,'type_trac='//TRIM(str(it))//' not possible yet.',1) END SELECT END DO !--- COHERENCE TEST BETWEEN "type_trac", "config_inca" AND PREPROCESSING KEYS DO it=1,nt SELECT CASE(type_trac) CASE('inca'); IF(ALL(['aero', 'aeNP', 'chem']/=config_inca)) & CALL abort_gcm(modname, 'Mismatch between type_trac and config_inca. Please modify "run.def"',1) #ifndef INCA CALL abort_gcm(modname, 'You must add cpp key INCA and compile with INCA code',1) #endif CASE('repr') #ifndef REPROBUS CALL abort_gcm(modname, 'You must add cpp key REPROBUS and compile with REPROBUS code',1) #endif CASE('coag') #ifndef CPP_StratAer CALL abort_gcm(modname, 'You must add cpp key StratAer and compile with StratAer code',1) #endif END SELECT END DO !--- Disable "config_inca" option for a run without INCA if it differs from "none" IF (ALL(str(:) /= 'inca') .AND. config_inca /= 'none') THEN CALL msg('setting config_inca="none" as you do not couple with INCA model') config_inca = 'none' END IF !------------------------------------------------------------------------------------------------------------------------------ ! 1) Get the numbers of: true tracers "nqtrue", water tracers "nqo" (vapor/liquid/solid) ! (here, "true" tracers means declared tracers, first order only) ! Deal with the advection scheme choice for water and tracers: ! iadv = 1 "LMDZ-specific humidity transport" (for H2O vapour) LMV ! iadv = 2 backward (for H2O liquid) BAK ! iadv = 14 Van-Leer + specific humidity, modified by Francis Codron VLH ! iadv = 10 Van-Leer (chosen for vapour and liquid water) VL1 ! iadv = 11 Van-Leer for hadv and PPM version (Monotonic) for vadv VLP ! iadv = 12 Frederic Hourdin I FH1 ! iadv = 13 Frederic Hourdin II FH2 ! iadv = 16 Monotonic PPM (Collela & Woodward 1984) PPM ! iadv = 17 Semi-monotonic PPM (overshoots allowed) PPS ! iadv = 18 Definite positive PPM (overshoots and undershoots allowed) PPP ! iadv = 20 Slopes SLP ! iadv = 30 Prather PRA ! ! In array q(ij,l,iq) : iq = 1 for vapour water ! iq = 2 for liquid water ! [iq = 3 for ice water] ! And optionaly: iq = 3[4],nqtot for other tracers !------------------------------------------------------------------------------------------------------------------------------ ! Get choice of advection scheme from file tracer.def or from INCA !------------------------------------------------------------------------------------------------------------------------------ IF(readTracersFiles(type_trac, fType, tracers)) CALL abort_gcm(modname,'problem with tracers file(s)',1) CALL msg(fType == 0, 'WARNING: USING DEFAULT VALUES !') !---------------------------------------------------------------------------------------------------------------------------- SELECT CASE(fType) !---------------------------------------------------------------------------------------------------------------------------- CASE(0) !=== NO READABLE TRACERS CONFIG FILE => DEFAULT !-------------------------------------------------------------------------------------------------------------------------- IF(planet_type=='earth') THEN !--- Default for Earth nqo = 2; nbtr = 2 tracers(:)%name = ['H2O-g','H2O-l','RN ','PB '] tracers(:)%prnt = [tran0 ,tran0 ,tran0 ,tran0 ] tracers(:)%igen = [1 ,1 ,1 ,1 ] hadv = [14 ,10 ,10 ,10 ] vadv = [14 ,10 ,10 ,10 ] ELSE !--- Default for other planets nqo = 0; nbtr = 1 tracers(:)%name = ['dummy'] tracers(:)%prnt = ['dummy'] tracers(:)%igen = [1 ] hadv = [10 ] vadv = [10 ] END IF nqtrue = nbtr + nqo !-------------------------------------------------------------------------------------------------------------------------- CASE(1) !-------------------------------------------------------------------------------------------------------------------------- IF(type_trac=='inca') THEN !=== OLD STYLE "traceur.def" FOR INCA FOUND !------------------------------------------------------------------------------------------------------------------------ nqo = SIZE(tracers(:), DIM=1) WRITE(msg1,'(a,i0)')'Only 2 or 3 water phases allowed ; found nqo=',nqo IF(nqo/=2 .AND. nqo/=3) CALL abort_gcm(modname,TRIM(msg1),1) #ifdef INCA CALL Init_chem_inca_trac(nbtr) !--- Get nbtr from INCA #endif ALLOCATE(hadv_inca(nbtr), vadv_inca(nbtr), conv_flg(nbtr), pbl_flg(nbtr), solsym(nbtr)) #ifdef INCA !--- Activation of: Convection, Boundary layer CALL init_transport(hadv_inca, vadv_inca, conv_flg, pbl_flg, solsym) #endif nqtrue = nbtr + nqo !--- Total number of tracers ALLOCATE(ttr(nqtrue)); ttr(1:nqo) = tracers(1:nqo) DO iq = nqo+1, nqtrue ttr(iq)%name = solsym(iq) ttr(iq)%prnt = tran0 ttr(iq)%igen = 1 hadv = hadv_inca(iq-nqo) vadv = vadv_inca(iq-nqo) END DO CALL MOVE_ALLOC(FROM=ttr, TO=tracers) !------------------------------------------------------------------------------------------------------------------------ ELSE !=== OLD STYLE "traceur.def" CONFIG FILE FOUND !------------------------------------------------------------------------------------------------------------------------ nqo = 0 DO ip = 1, SIZE(oldH2O) ix = strIdx(tracers(:)%name,oldH2O(ip)) !--- Old name of water in a specific phase (ix/=0) IF(ix == 0) CYCLE newH2O = 'H2O-'//known_phases(ip:ip) !--- Corresponding new name nqo = nqo+1; tracers(ix)%name = newH2O !--- One more water phase ; replace old name with one tracers(strFind(tracers(:)%nam1,oldH2O(ip)))%nam1 = newH2O tracers(strFind(tracers(:)%prnt,oldH2O(ip)))%prnt = newH2O END DO nqtrue = SIZE(tracers,DIM=1) nbtr = nqtrue - nqo END IF !-------------------------------------------------------------------------------------------------------------------------- CASE DEFAULT !=== FOUND NEW STYLE TRACERS CONFIG FILE(S) !-------------------------------------------------------------------------------------------------------------------------- nqo = 2; IF(ANY(tracers(:)%name == 'H2O-s')) nqo=3 nqtrue = SIZE(tracers, DIM=1) nbtr = nqtrue - nqo !---------------------------------------------------------------------------------------------------------------------------- END SELECT !---------------------------------------------------------------------------------------------------------------------------- CALL getKey_init(tracers) IF(.NOT.ALLOCATED(hadv)) lerr = getKey('hadv', hadv) IF(.NOT.ALLOCATED(vadv)) lerr = getKey('vadv', vadv) IF(.NOT.ALLOCATED(solsym)) ALLOCATE(solsym(nbtr)) IF(.NOT.ALLOCATED(conv_flg)) conv_flg = [(1, it=1, nbtr)] IF(.NOT.ALLOCATED( pbl_flg)) pbl_flg = [(1, it=1, nbtr)] #ifdef CPP_StratAer IF (type_trac == 'coag') THEN nbtr_bin=0 nbtr_sulgas=0 DO iq = 1, nqtrue IF(tracers(iq)%name(1:3)=='BIN') nbtr_bin = nbtr_bin +1 IF(tracers(iq)%name(1:3)=='GAS') nbtr_sulgas = nbtr_sulgas+1 SELECT CASE(tracers(iq)%name) CASE('BIN01'); id_BIN01_strat = iq - nqo; CALL msg('id_BIN01_strat=', id_BIN01_strat) CASE('GASOCS'); id_OCS_strat = iq - nqo; CALL msg('id_OCS_strat =', id_OCS_strat) CASE('GASSO2'); id_SO2_strat = iq - nqo; CALL msg('id_SO2_strat =', id_SO2_strat) CASE('GASH2SO4'); id_H2SO4_strat = iq - nqo; CALL msg('id_H2SO4_strat=', id_H2SO4_strat) CASE('GASTEST'); id_TEST_strat = iq - nqo; CALL msg('id_TEST_strat=' , id_TEST_strat) END SELECT END DO CALL msg('nbtr_bin =',nbtr_bin) CALL msg('nbtr_sulgas =',nbtr_sulgas) END IF #endif !--- Transfert number of tracers to Reprobus #ifdef REPROBUS IF(type_trac == 'repr') CALL Init_chem_rep_trac(nbtr,nqo,tracers(:)%name) #endif !------------------------------------------------------------------------------------------------------------------------------ ! 2) Verify if the advection scheme 20 or 30 have been chosen. ! Calculate total number of tracers needed: nqtot ! Allocate variables depending on total number of tracers !------------------------------------------------------------------------------------------------------------------------------ DO iq = 1, nqtrue t1 => tracers(iq) IF( hadv(iq)<20 .OR. (ANY(hadv(iq)==[20,30]) .AND. hadv(iq)==vadv(iq)) ) CYCLE WRITE(msg1,'(2(a,i0))')' is not available: hadv=',hadv(iq),', vadv=',vadv(iq) CALL msg('This choice of advection scheme for "'//TRIM(t1%name)//'"'//TRIM(msg1)) CALL abort_gcm(modname,'Bad choice of advection scheme',1) END DO nqtot = COUNT( hadv< 20 .AND. vadv< 20 ) & !--- No additional tracer + 4*COUNT( hadv==20 .AND. vadv==20 ) & !--- 3 additional tracers + 10*COUNT( hadv==30 .AND. vadv==30 ) !--- 9 additional tracers ! More tracers due to the choice of advection scheme => assign total number of tracers IF( nqtot /= nqtrue ) THEN CALL msg('The choice of advection scheme for one or more tracers makes it necessary to add tracers') CALL msg('The number of true tracers is '//TRIM(int2str(nqtrue))) CALL msg('The total number of tracers needed is '//TRIM(int2str(nqtot))) END IF ALLOCATE(ttr(nqtot)) !------------------------------------------------------------------------------------------------------------------------------ ! 3) Determine iadv, long and short name, generation number, phase and region !------------------------------------------------------------------------------------------------------------------------------ jq = 0; ttr(:)%iadv = -1 DO iq = 1, nqtrue jq = jq + 1 t1 => tracers(iq) !--- Verify choice of advection schema iad = -1 IF(hadv(iq) == vadv(iq) ) iad = hadv(iq) IF(hadv(iq)==10 .AND. vadv(iq)==16) iad = 11 CALL msg(iad == -1, 'This choice of advection scheme for "'//TRIM(t1%name)//'" '//'is not available: hadv = ' & //TRIM(int2str(hadv(iq)))//', vadv='//TRIM(int2str(vadv(iq))) ) IF(iad == -1) CALL abort_gcm(modname,'Bad choice of advection scheme - 2',1) t1%lnam = t1%name; IF(iad /= 0) t1%lnam=TRIM(t1%name)//descrq(iad) !--- Defining most fields of the tracer derived type ttr(jq)%name = t1%name ttr(jq)%nam1 = t1%nam1 ttr(jq)%prnt = t1%prnt ttr(jq)%lnam = t1%lnam ttr(jq)%type = t1%type ttr(jq)%phas = t1%phas ttr(jq)%iadv = iad ttr(jq)%igen = t1%igen IF(ALL([20,30] /= iad)) CYCLE !--- 1st order scheme: finished IF(iad == 20) nm = 3 !--- 2nd order scheme IF(iad == 30) nm = 9 !--- 3rd order scheme ttr(jq+1:jq+nm)%name = [ (TRIM(t1%name)//'-'//TRIM(suff(im)), im=1, nm) ] ttr(jq+1:jq+nm)%nam1 = [ (TRIM(t1%nam1)//'-'//TRIM(suff(im)), im=1, nm) ] ttr(jq+1:jq+nm)%lnam = [ (TRIM(t1%lnam)//'-'//TRIM(suff(im)), im=1, nm) ] ttr(jq+1:jq+nm)%prnt = t1%prnt ttr(jq+1:jq+nm)%type = t1%type ttr(jq+1:jq+nm)%phas = t1%phas ttr(jq+1:jq+nm)%iadv = -iad ttr(jq+1:jq+nm)%igen = t1%igen jq = jq + nm END DO DEALLOCATE(hadv, vadv) !--- Determine parent and childs indexes CALL indexUpdate(ttr) !=== TEST ADVECTION SCHEME DO iq=1,nqtot ; t1 => ttr(iq); iad = t1%iadv WRITE(msg1,'(a,i0)')'This LMDZ version has not been tested for option iadv=',iad WRITE(msg2,'(a,i2,a)')'iadv=',iad,' not implemented yet for' !--- ONLY TESTED VALUES FOR TRACERS FOR NOW: iadv = 14, 10 (and 0) IF(ALL( [10,14,0] /= iad) ) CALL abort_gcm(modname, TRIM(msg1)//' ; only iadv=10 and iadv=14 are tested !', 1) !--- ONLY TESTED VALUES FOR CHILDS FOR NOW: iadv = 10 (CHILDS: TRACERS OF GENERATION GREATER THAN 1) IF(fmsg(iad/=10.AND.t1%igen>1,'WARNING ! '//TRIM(msg2)//' childs. Setting iadv=10 for "'//TRIM(t1%name)//'".')) t1%iadv=10 !--- ONLY TESTED VALUES FOR PARENTS FOR NOW: iadv = 14, 10 (PARENTS: TRACERS OF GENERATION 1) IF(t1%igen==1 .AND. ALL([10,14]/=iad)) CALL abort_gcm(modname, TRIM(msg2)//' parents: schemes 10 or 14 only !', 1) !--- iadv = 14 IS ONLY VALID FOR WATER VAPOUR IF(fmsg(iad==14 .AND. t1%name(1:5)/='H2O-g', 'WARNING ! '//TRIM(msg1)//', found for "' & //TRIM(t1%name)//'" but only valid for water vapour ! Setting iadv=10 for "'//TRIM(t1%name)//'".')) t1%iadv=10 END DO !=== DISPLAY THE RESULTING LIST CALL msg('Information stored in infotrac :') IF(dispTable('isssiii', ['iq ','name ','long name','parent ','iadv ','ipar ','igen '], & cat(ttr(:)%name, ttr(:)%lnam, ttr(:)%prnt), cat([(iq, iq=1, nqtot)], ttr(:)%iadv, ttr(:)%iprnt, ttr(:)%igen))) & CALL abort_gcm(modname,"problem with the tracers table content",1) CALL MOVE_ALLOC(FROM=ttr, TO=tracers) t => tracers !=== VARIABLES RELATED TO GENERATIONS niadv = PACK( [(iq,iq=1,nqtot)], MASK=t(:)%iadv>=0) !--- Indexes of "true" tracers p = PACK(delPhase(t%prnt),MASK=t%type=='tracer'.AND.t%igen==2)!--- Parents of 2nd generation isotopes CALL strReduce(p, nbIso) ALLOCATE(isotopes(nbIso)) IF(nbIso==0) RETURN !=== NO ISOTOPES: FINISHED CALL msg('Isotopes families required: '//strStack(p)) !--- ISOTOPES RELATED VARIABLES ; NULL OR EMPTY IF NO ISOTOPES isotopes(:)%prnt = p DO ip = 1, SIZE(p) !--- Loop on isotopes categories s => isotopes(ip) iname = s%prnt !=== Geographic tagging tracers descending on tracer "iname": mask, names, number lisoZone = t(:)%type=='tag' .AND. delPhase(t(:)%nam1) == iname .AND. t(:)%igen == 3 s%zone = PACK(strTail(t(:)%name,'_'), MASK = lisoZone) !--- Tagging zones names for isotopes category "iname" CALL strReduce(s%zone) s%nzon = SIZE(s%zone) !--- Tagging zones number for isotopes category "iname" !=== Isotopes childs of tracer "iname": mask, names, number (same for each phase of "iname") lisoName = t(:)%type=='tracer' .AND. delPhase(t(:)%prnt) == iname .AND. t(:)%phas == 'g' ALLOCATE(s%keys(COUNT(lisoName))) s%keys(:)%name = PACK(delPhase(t(:)%name), MASK = lisoName) !--- Effectively found isotopes of "iname" s%niso = SIZE(s%keys) !--- Number of "effectively found isotopes of "iname" s%trac = [s%keys%name, ((TRIM(s%keys(it)%name)//'_'//TRIM(s%zone(iz)), it=1, s%niso), iz=1, s%nzon)] s%nitr = SIZE(s%trac) !--- " + their geographic tracers [ntraciso] !=== Phases for tracer "iname" s%phas = '' DO ix = 1, nphases; IF(strIdx(t%name,addPhase(iname, known_phases(ix:ix))) /= 0) s%phas = TRIM(s%phas)//ph; END DO s%npha = LEN_TRIM(s%phas) !--- Equal to "nqo" for water !=== Tables giving the index in a table of effectively found items for each dynamical tracer (1<=iq<=nqtot) DO iq = 1, nqtot t1 => tracers(iq) IF(t1%nam1 /= iname) CYCLE !--- Only deal with tracers descending on "iname" t1%iso_igr = ip !--- Index of isotopes family in list "isotopes(:)%prnt" t1%iso_num = strIdx(s%trac, delPhase(strHead(t1%name,'_')))!--- Index of current isotope in effective isotopes list t1%iso_zon = strIdx(s%zone, strTail(t1%name,'_') )!--- Index of current isotope zone in effective zones list t1%iso_pha = INDEX(s%phas,TRIM(t1%phas)) !--- Index of current isotope phase in effective phases list IF(t1%igen /= 3) t1%iso_zon = 0 !--- Skip possible generation 2 tagging tracers END DO !=== Table used to get iq (index in dyn array, size nqtot) from the isotope and phase indexes ; the full isotopes list ! (including tagging tracers) is sorted this way: iso1, iso2, ..., iso1_zone1, iso2_zone1, ..., iso1_zoneN, iso2_zoneN s%iTraPha = RESHAPE( [( (strIdx(t(:)%name, addPhase(s%trac(it),s%phas(ip:ip))), it=1, s%nitr), ip=1, s%npha)], & [s%nitr, s%npha] ) !=== Table used to get ix (index in tagging tracers isotopes list, size nitr) from the zone and isotope indexes s%iZonIso = RESHAPE( [( (strIdx(s%trac(:), TRIM(s%trac(it))//'_'//TRIM(s%zone(iz))), iz=1, s%nzon), it=1, s%niso)], & [s%nzon, s%niso] ) END DO !=== Indexes, in dynamical tracers list, of the tracers transmitted to phytrac (nqtottr non-vanishing elements) ll = delPhase(t%name)/='H2O' .AND. t%iso_num ==0 !--- Mask of tracers passed to the physics t(:)%itr = UNPACK([(iq,iq=1,COUNT(ll))], ll, [(0, iq=1, nqtot)]) itr_indice = PACK(t(:)%itr, MASK = t(:)%itr/=0) !--- Might be removed (t%itr should be enough) !=== READ PHYSICAL PARAMETERS FROM "isotopes_params.def" FILE ! DONE HERE, AND NOT ONLY IN "infotrac_phy", BECAUSE SOME PHYSICAL PARAMS ARE NEEDED FOR RESTARTS (tnat AND alpha_ideal) IF(readIsotopesFile('isotopes_params.def',isotopes)) CALL abort_gcm(modname,'Problem when reading isotopes parameters',1) print*,'coincoin' !=== Specific to water CALL getKey_init(tracers, isotopes) IF(isoSelect('H2O')) RETURN !--- Select water isotopes ; finished if no water isotopes. iH2O = ixIso !--- Keep track of water family index lerr = getKey('tnat' ,tnat, isoName) lerr = getKey('alpha',alpha_ideal, isoName) CALL msg('end') END SUBROUTINE infotrac_init !============================================================================================================================== !=== THE ROUTINE isoSelect IS USED TO SWITCH FROM AN ISOTOPE FAMILY TO ANOTHER: ISOTOPES DEPENDENT PARAMETERS ARE UPDATED ! Singe generic "isoSelect" routine, using the predefined parent index (fast version) or its name (first time). !============================================================================================================================== LOGICAL FUNCTION isoSelectByName(iName) RESULT(lerr) CHARACTER(LEN=*), INTENT(IN) :: iName INTEGER :: iIso iIso = strIdx(isotopes(:)%prnt, iName) IF(test(fmsg(iIso == 0,'no isotope family named "'//TRIM(iName)//'"'),lerr)) RETURN IF(isoSelectByIndex(iIso)) RETURN END FUNCTION isoSelectByName !============================================================================================================================== LOGICAL FUNCTION isoSelectByIndex(iIso) RESULT(lerr) INTEGER, INTENT(IN) :: iIso lerr = .FALSE. IF(iIso == ixIso) RETURN !--- Nothing to do if the index is already OK IF(test(fmsg(iIso<=0 .OR. iIso>=nbIso,'Inconsistent isotopes family index '//TRIM(int2str(iIso))),lerr)) RETURN ixIso = iIso !--- Update currently selected family index isotope => isotopes(ixIso) !--- Select corresponding component !--- VARIOUS ALIASES isoKeys => isotope%keys; niso = isotope%niso isoName => isotope%trac; nitr = isotope%nitr; isoCheck => isotope%check isoZone => isotope%zone; nzon = isotope%nzon; iZonIso => isotope%iZonIso isoPhas => isotope%phas; npha = isotope%npha; iTraPha => isotope%iTraPha END FUNCTION isoSelectByIndex !============================================================================================================================== END MODULE infotrac