! $Id: infotrac.F90 4057 2022-01-12 22:16:06Z dcugnet $ ! MODULE infotrac USE readTracFiles_mod, ONLY: trac_type, isot_type, maxlen, ancestor, delPhase ! nqtot : total number of tracers and higher order of moment, water vapor and liquid included INTEGER, SAVE :: nqtot !CR: on ajoute le nombre de traceurs de l eau INTEGER, SAVE :: nqo ! nbtr : number of tracers not including higher order of moment or water vapor or liquid ! number of tracers used in the physics INTEGER, SAVE :: nbtr ! Nombre de traceurs passes a phytrac INTEGER, SAVE :: nqtottr ! ThL: nb traceurs CO2 INTEGER, SAVE :: nqCO2 ! DC: derived types containing informations about tracers and isotopes TYPE(trac_type), TARGET, SAVE, ALLOCATABLE :: tracers(:) !=== TRACERS DESCRIPTORS VECTOR TYPE(isot_type), TARGET, SAVE, ALLOCATABLE :: isotopes(:) !=== ISOTOPES PARAMETERS VECTOR REAL :: qperemin,masseqmin,ratiomin ! MVals et CRisi PARAMETER (qperemin=1e-30,masseqmin=1e-18,ratiomin=1e-16) ! MVals ! conv_flg(it)=0 : convection desactivated for tracer number it INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: conv_flg ! pbl_flg(it)=0 : boundary layer diffusion desactivaded for tracer number it INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: pbl_flg CHARACTER(len=4),SAVE :: type_trac CHARACTER(len=8),DIMENSION(:),ALLOCATABLE, SAVE :: solsym ! CRisi: cas particulier des isotopes LOGICAL,SAVE :: ok_isotopes,ok_iso_verif,ok_isotrac,ok_init_iso INTEGER :: niso_possibles PARAMETER ( niso_possibles=5) REAL, DIMENSION (niso_possibles),SAVE :: tnat,alpha_ideal LOGICAL, DIMENSION(niso_possibles),SAVE :: use_iso INTEGER, ALLOCATABLE, DIMENSION(:,:), SAVE :: iqiso ! donne indice iq en fn de (ixt,phase) INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: iso_indnum ! donne numero iso entre 1 et niso effectif en fn de nqtot INTEGER, DIMENSION(niso_possibles), SAVE :: indnum_fn_num ! donne indice entre entre 1 et niso en fonction du numero d isotope entre 1 et niso_possibles INTEGER, ALLOCATABLE, DIMENSION(:,:), SAVE :: index_trac ! numero ixt en fn izone, indnum entre 1 et niso INTEGER,SAVE :: niso,ntraceurs_zone,ntraciso CONTAINS SUBROUTINE infotrac_init USE control_mod, ONLY: planet_type, config_inca #ifdef REPROBUS USE CHEM_REP, ONLY : Init_chem_rep_trac #endif IMPLICIT NONE !======================================================================= ! ! Auteur: P. Le Van /L. Fairhead/F.Hourdin ! ------- ! Modif special traceur F.Forget 05/94 ! Modif M-A Filiberti 02/02 lecture de traceur.def ! ! Objet: ! ------ ! GCM LMD nouvelle grille ! !======================================================================= ! ... modification de l'integration de q ( 26/04/94 ) .... !----------------------------------------------------------------------- ! Declarations INCLUDE "dimensions.h" INCLUDE "iniprint.h" ! Local variables INTEGER, ALLOCATABLE, DIMENSION(:) :: hadv ! index of horizontal trasport schema INTEGER, ALLOCATABLE, DIMENSION(:) :: vadv ! index of vertical trasport schema INTEGER, ALLOCATABLE, DIMENSION(:) :: hadv_inca ! index of horizontal trasport schema INTEGER, ALLOCATABLE, DIMENSION(:) :: vadv_inca ! index of vertical trasport schema INTEGER, ALLOCATABLE, DIMENSION(:) :: conv_flg_inca INTEGER, ALLOCATABLE, DIMENSION(:) :: pbl_flg_inca CHARACTER(len=8), ALLOCATABLE, DIMENSION(:) :: solsym_inca CHARACTER(len=maxlen), ALLOCATABLE, DIMENSION(:) :: tnom_0 ! tracer short name CHARACTER(len=maxlen), ALLOCATABLE, DIMENSION(:) :: tnom_transp ! transporting fluid short name: CRisi CHARACTER(len=3), DIMENSION(30) :: descrq CHARACTER(len=1), DIMENSION(3) :: txts CHARACTER(len=2), DIMENSION(9) :: txtp CHARACTER(len=maxlen) :: str1,str2 INTEGER :: nqtrue ! number of tracers read from tracer.def, without higer order of moment INTEGER :: iq, new_iq, iiq, jq, ierr,itr, iadv INTEGER :: ifils,ipere ! CRisi LOGICAL :: continu,nouveau_traceurdef INTEGER :: IOstatus ! gestion de la retrocompatibilite de traceur.def CHARACTER(len=maxlen) :: tchaine, msg1 INTEGER, ALLOCATABLE :: iqfils(:,:) INTEGER :: nqINCA character(len=*),parameter :: modname="infotrac_init" !----------------------------------------------------------------------- ! Initialization : ! txts=(/'x','y','z'/) txtp=(/'x ','y ','z ','xx','xy','xz','yy','yz','zz'/) descrq(14)='VLH' descrq(10)='VL1' descrq(11)='VLP' descrq(12)='FH1' descrq(13)='FH2' descrq(16)='PPM' descrq(17)='PPS' descrq(18)='PPP' descrq(20)='SLP' descrq(30)='PRA' !--- MESSAGE ABOUT THE CHOSEN CONFIGURATION WRITE(lunout,*)'type_trac='//TRIM(type_trac) msg1 = 'For type_trac = "'//TRIM(type_trac)//'":' SELECT CASE(type_trac) CASE('inca'); WRITE(lunout,*)TRIM(msg1)//' coupling with INCA chemistry model, config_inca='//config_inca CASE('inco'); WRITE(lunout,*)TRIM(msg1)//' coupling jointly with INCA and CO2 cycle' CASE('repr'); WRITE(lunout,*)TRIM(msg1)//' coupling with REPROBUS chemistry model' CASE('co2i'); WRITE(lunout,*)TRIM(msg1)//' you have chosen to run with CO2 cycle' CASE('coag'); WRITE(lunout,*)TRIM(msg1)//' tracers are treated for COAGULATION tests' CASE('lmdz'); WRITE(lunout,*)TRIM(msg1)//' tracers are treated in LMDZ only' CASE DEFAULT CALL abort_gcm(modname,'type_trac='//TRIM(type_trac)//' not possible yet.',1) END SELECT !--- COHERENCE TEST BETWEEN "type_trac", "config_inca" AND PREPROCESSING KEYS SELECT CASE(type_trac) CASE('inca','inco'); IF(ALL(['aero', 'aeNP', 'chem']/=config_inca)) & CALL abort_gcm(modname, 'Incoherence 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 !--- Disable "config_inca" option for a run without INCA if it differs from "none" IF (ALL(['inca', 'inco', 'none'] /= config_inca)) THEN WRITE(lunout,*)'setting config_inca="none" as you do not couple with INCA model' config_inca = 'none' END IF !----------------------------------------------------------------------- ! ! 1) Get the true number of tracers + water vapor/liquid ! Here true tracers (nqtrue) means declared tracers (only first order) ! !----------------------------------------------------------------------- OPEN(90,file='traceur.def',form='formatted',status='old', iostat=ierr) IF(ierr.EQ.0) THEN WRITE(lunout,*) trim(modname),': Open traceur.def : ok' ELSE WRITE(lunout,*) trim(modname),': Failed opening traceur.def' CALL abort_gcm(modname,"file traceur.def not found!",1) ENDIF nqCO2 = 0; IF(type_trac == 'inco') nqCO2 = 1 SELECT CASE(type_trac) CASE('lmdz','repr','coag','co2i'); READ(90,*) nqtrue CASE('inca','inco'); READ(90,*) nqo ! The traceur.def file is used to define the number "nqo" of water phases ! present in the simulation. Default : nqo = 2. IF (nqo == 4 .AND. type_trac=='inco') nqo = 3 IF(ALL([2,3] /= nqo)) THEN WRITE(lunout,*) trim(modname),': nqo=',nqo, ' is not allowed. Only 2 or 3 water phases allowed' CALL abort_gcm('infotrac_init','Bad number of water phases',1) END IF ! nbtr has been read from INCA by init_const_lmdz() in gcm.F #ifdef INCA CALL Init_chem_inca_trac(nqINCA) #else nqINCA=0 #endif nbtr=nqINCA+nqCO2 nqtrue=nbtr+nqo WRITE(lunout,*) trim(modname),': nqo = ',nqo WRITE(lunout,*) trim(modname),': nbtr = ',nbtr WRITE(lunout,*) trim(modname),': nqtrue = ',nqtrue WRITE(lunout,*) trim(modname),': nqCO2 = ',nqCO2 WRITE(lunout,*) trim(modname),': nqINCA = ',nqINCA ALLOCATE(hadv_inca(nqINCA), vadv_inca(nqINCA), conv_flg_inca(nqINCA), pbl_flg_inca(nqINCA), solsym_inca(nqINCA)) END SELECT !>jyg IF ((planet_type=="earth").and.(nqtrue < 2)) THEN WRITE(lunout,*) trim(modname),': nqtrue=',nqtrue, ' is not allowed. 2 tracers is the minimum' CALL abort_gcm('infotrac_init','Not enough tracers',1) ENDIF !jyg< ! ! Allocate variables depending on nqtrue ! ALLOCATE(tnom_0(nqtrue), hadv(nqtrue), vadv(nqtrue),tnom_transp(nqtrue)) !----------------------------------------------------------------------- ! 2) Choix des schemas d'advection pour l'eau et les traceurs ! ! iadv = 1 schema transport type "humidite specifique LMD" ! iadv = 2 schema amont ! iadv = 14 schema Van-leer + humidite specifique ! Modif F.Codron ! iadv = 10 schema Van-leer (retenu pour l'eau vapeur et liquide) ! iadv = 11 schema Van-Leer pour hadv et version PPM (Monotone) pour vadv ! iadv = 12 schema Frederic Hourdin I ! iadv = 13 schema Frederic Hourdin II ! iadv = 16 schema PPM Monotone(Collela & Woodward 1984) ! iadv = 17 schema PPM Semi Monotone (overshoots autorises) ! iadv = 18 schema PPM Positif Defini (overshoots undershoots autorises) ! iadv = 20 schema Slopes ! iadv = 30 schema Prather ! ! Dans le tableau q(ij,l,iq) : iq = 1 pour l'eau vapeur ! iq = 2 pour l'eau liquide ! Et eventuellement iq = 3,nqtot pour les autres traceurs ! ! iadv(1): choix pour l'eau vap. et iadv(2) : choix pour l'eau liq. !------------------------------------------------------------------------ ! ! Get choice of advection schema from file tracer.def or from INCA !--------------------------------------------------------------------- IF (ANY(['lmdz', 'repr', 'coag', 'co2i'] == type_trac)) THEN ! Continue to read tracer.def DO iq=1,nqtrue write(*,*) 'infotrac 237: iq=',iq ! CRisi: ajout du nom du fluide transporteur ! mais rester retro compatible READ(90,'(I2,X,I2,X,A)',IOSTAT=IOstatus) hadv(iq),vadv(iq),tchaine write(lunout,*) 'iq,hadv(iq),vadv(iq)=',iq,hadv(iq),vadv(iq) write(lunout,*) 'tchaine=',trim(tchaine) write(*,*) 'infotrac 238: IOstatus=',IOstatus if (IOstatus.ne.0) CALL abort_gcm('infotrac_init','Pb dans la lecture de traceur.def',1) ! Y-a-t-il 1 ou 2 noms de traceurs separes par un espace ? iiq = INDEX(tchaine(1:LEN_TRIM(tchaine)),' ') nouveau_traceurdef=iiq/=0 write(*,*) 'iiq,nouveau_traceurdef=',iiq,nouveau_traceurdef if (nouveau_traceurdef) then IF(iq==1) write(lunout,*) "Nouvelle version de traceur.def" tnom_0 (iq) = tchaine(1:iiq-1) tnom_transp(iq) = tchaine(iiq+1:) else IF(iq==1) write(lunout,*) "Nouvelle version de traceur.def: traceurs d'air uniquement" tnom_0 (iq) = tchaine tnom_transp(iq) = 'air' endif write(lunout,*) 'tnom_0(iq)=<',trim(tnom_0(iq)),'>' write(lunout,*) 'tnom_transp(iq)=<',trim(tnom_transp(iq)),'>' ENDDO!DO iq=1,nqtrue CLOSE(90) WRITE(lunout,*) trim(modname),': Valeur de traceur.def :' WRITE(lunout,*) trim(modname),': nombre total de traceurs ',nqtrue DO iq=1,nqtrue WRITE(lunout,*) hadv(iq),vadv(iq),' ',trim(tnom_0(iq)),' ',trim(tnom_transp(iq)) END DO IF ( planet_type=='earth') THEN !CR: nombre de traceurs de l eau nqo=2; IF (tnom_0(3) == 'H2Oi') nqo=3 ! For Earth, water vapour & liquid tracers are not in the physics nbtr=nqtrue-nqo ELSE ! Other planets (for now); we have the same number of tracers ! in the dynamics than in the physics nbtr=nqtrue ENDIF ENDIF !jyg< ! ! Transfert number of tracers to Reprobus #ifdef REPROBUS IF (type_trac == 'repr') CALL Init_chem_rep_trac(nbtr,nqo,tnom_0) #endif ! ! Allocate variables depending on nbtr ! ALLOCATE(conv_flg(nbtr), pbl_flg(nbtr), solsym(nbtr)) conv_flg(:) = 1 ! convection activated for all tracers pbl_flg(:) = 1 ! boundary layer activated for all tracers IF (type_trac == 'inca' .OR. type_trac == 'inco') THEN ! config_inca='aero' ou 'chem' !>jyg ! le module de chimie fournit les noms des traceurs et les schemas d'advection associes. ! excepte pour ceux lus dans traceur.def #ifdef INCA CALL init_transport(hadv_inca, vadv_inca, conv_flg_inca, pbl_flg_inca, solsym_inca) ! DC passive CO2 tracer is at index 1: H2O was removed ; nqCO2/=0 in "inco" case only conv_flg(1:nqCO2) = 1; conv_flg(1+nqCO2:nbtr) = conv_flg_inca pbl_flg(1:nqCO2) = 1; pbl_flg(1+nqCO2:nbtr) = pbl_flg_inca solsym(1:nqCO2) = 'CO2'; solsym(1+nqCO2:nbtr) = solsym_inca #endif itr = 0 DO iq = 1, nqtot IF(iq > nqo+nqCO2) THEN itr = itr+1 hadv (iq) = hadv_inca (itr) vadv (iq) = vadv_inca (itr) tnom_0(iq) = solsym_inca(itr) tnom_transp(iq) = 'air' CYCLE END IF write(*,*) 'infotrac 237: iq=',iq ! CRisi: ajout du nom du fluide transporteur en restant retro-compatible READ(90,'(I2,X,I2,X,A)',IOSTAT=IOstatus) hadv(iq),vadv(iq),tchaine write(lunout,*) 'iq,hadv(iq),vadv(iq)=',iq,hadv(iq),vadv(iq) write(lunout,*) 'tchaine=',trim(tchaine) write(*,*) 'infotrac 238: IOstatus=',IOstatus if (IOstatus.ne.0) CALL abort_gcm('infotrac_init','Pb dans la lecture de traceur.def',1) ! Y-a-t-il 1 ou 2 noms de traceurs separes par un espace ? iiq = INDEX(tchaine(1:LEN_TRIM(tchaine)),' ') nouveau_traceurdef=iiq/=0 write(*,*) 'iiq,nouveau_traceurdef=',iiq,nouveau_traceurdef if (nouveau_traceurdef) then IF(iq==1) write(lunout,*) "Nouvelle version de traceur.def" tnom_0 (iq) = tchaine(1:iiq-1) tnom_transp(iq) = tchaine(iiq+1:) else IF(iq==1) write(lunout,*) "Nouvelle version de traceur.def: traceurs d'air uniquement" tnom_0 (iq) = tchaine tnom_transp(iq) = 'air' endif write(lunout,*) 'tnom_0(iq)=<',trim(tnom_0(iq)),'>' write(lunout,*) 'tnom_transp(iq)=<',trim(tnom_transp(iq)),'>' END DO CLOSE(90) ENDIF ! (type_trac == 'inca' or 'inco') !----------------------------------------------------------------------- ! ! 3) Verify if advection schema 20 or 30 choosen ! Calculate total number of tracers needed: nqtot ! Allocate variables depending on total number of tracers !----------------------------------------------------------------------- new_iq=0 DO iq=1,nqtrue ! Add tracers for certain advection schema IF (hadv(iq)<20 .AND. vadv(iq)<20 ) THEN new_iq=new_iq+1 ! no tracers added ELSE IF (hadv(iq)==20 .AND. vadv(iq)==20 ) THEN new_iq=new_iq+4 ! 3 tracers added ELSE IF (hadv(iq)==30 .AND. vadv(iq)==30 ) THEN new_iq=new_iq+10 ! 9 tracers added ELSE WRITE(lunout,*) trim(modname),': This choice of advection schema is not available',iq,hadv(iq),vadv(iq) CALL abort_gcm('infotrac_init','Bad choice of advection schema - 1',1) ENDIF END DO IF (new_iq /= nqtrue) THEN ! The choice of advection schema imposes more tracers ! Assigne total number of tracers nqtot = new_iq WRITE(lunout,*) trim(modname),': The choice of advection schema for one or more tracers' WRITE(lunout,*) 'makes it necessary to add tracers' WRITE(lunout,*) trim(modname)//': ',nqtrue,' is the number of true tracers' WRITE(lunout,*) trim(modname)//': ',nqtot, ' is the total number of tracers needed' ELSE ! The true number of tracers is also the total number nqtot = nqtrue ENDIF ! ! Allocate variables with total number of tracers, nqtot ! ALLOCATE(tracers(nqtot)) !----------------------------------------------------------------------- ! ! 4) Determine iadv, long and short name ! !----------------------------------------------------------------------- new_iq=0 DO iq=1,nqtrue new_iq=new_iq+1 ! Verify choice of advection schema IF (hadv(iq)==vadv(iq)) THEN tracers(new_iq)%iadv=hadv(iq) ELSE IF (hadv(iq)==10 .AND. vadv(iq)==16) THEN tracers(new_iq)%iadv=11 ELSE WRITE(lunout,*)trim(modname),': This choice of advection schema is not available',iq,hadv(iq),vadv(iq) CALL abort_gcm('infotrac_init','Bad choice of advection schema - 2',1) ENDIF str1=tnom_0(iq) tracers(new_iq)%name = TRIM(tnom_0(iq)) tracers(new_iq)%parent = TRIM(tnom_transp(iq)) IF (tracers(new_iq)%iadv==0) THEN tracers(new_iq)%longName=trim(str1) ELSE tracers(new_iq)%longName=trim(tnom_0(iq))//descrq(tracers(new_iq)%iadv) ENDIF ! schemas tenant compte des moments d'ordre superieur str2=TRIM(tracers(new_iq)%longName) IF (tracers(new_iq)%iadv==20) THEN DO jq=1,3 new_iq=new_iq+1 tracers(new_iq)%iadv=-20 tracers(new_iq)%longName=trim(str2)//txts(jq) tracers(new_iq)%name=trim(str1)//txts(jq) END DO ELSE IF (tracers(new_iq)%iadv==30) THEN DO jq=1,9 new_iq=new_iq+1 tracers(new_iq)%iadv=-30 tracers(new_iq)%longName=trim(str2)//txtp(jq) tracers(new_iq)%name=trim(str1)//txtp(jq) END DO ENDIF END DO WRITE(lunout,*) trim(modname),': Information stored in infotrac :' WRITE(lunout,*) trim(modname),': iadv name long_name :' DO iq=1,nqtot WRITE(lunout,*) tracers(iq)%iadv,' ',trim(tracers(iq)%name),' ',trim(tracers(iq)%longName) END DO ! ! Test for advection schema. ! This version of LMDZ only garantees iadv=10 and iadv=14 (14 only for water vapour) . ! DO iq=1,nqtot iadv=tracers(iq)%iadv IF (ALL([10, 14, 0]/=iadv)) THEN WRITE(lunout,*)trim(modname),' STOP : The option iadv=',iadv,' is not tested in this version of LMDZ' CALL abort_gcm('infotrac_init','In this version only iadv=10 and iadv=14 is tested!',1) ELSE IF (iadv==14 .AND. iq/=1) THEN WRITE(lunout,*)trim(modname),'STOP : The option iadv=',iadv,' is not tested in this version of LMDZ' CALL abort_gcm('infotrac_init','In this version iadv=14 is only permitted for water vapour!',1) ENDIF END DO ! CRisi: quels sont les traceurs fils et les traceurs peres. ! initialiser tous les tableaux d'indices lies aux traceurs familiaux ! + verifier que tous les peres sont ecrits en premieres positions ALLOCATE(iqfils(nqtot,nqtot)) iqfils(:,:)=0 tracers(:)%iqParent=0 DO iq=1,nqtot if (tnom_transp(iq) == 'air') then ! ceci est un traceur pere WRITE(lunout,*) 'Le traceur',iq,', appele ',trim(tnom_0(iq)),', est un pere' tracers(iq)%iqParent=0 else !if (tnom_transp(iq) == 'air') then ! ceci est un fils. Qui est son pere? WRITE(lunout,*) 'Le traceur',iq,', appele ',trim(tnom_0(iq)),', est un fils' continu=.true. ipere=1 do while (continu) if (tnom_transp(iq) == tnom_0(ipere)) then ! Son pere est ipere WRITE(lunout,*) 'Le traceur',iq,'appele ', & & trim(tnom_0(iq)),' est le fils de ',ipere,'appele ',trim(tnom_0(ipere)) if (iq.eq.ipere) then CALL abort_gcm('infotrac_init','Un fils est son propre pere',1) endif tracers(ipere)%nqChilds = tracers(ipere)%nqChilds+1 iqfils(tracers(ipere)%nqChilds,ipere)=iq tracers(iq)%iqParent=ipere continu=.false. else !if (tnom_transp(iq) == tnom_0(ipere)) then ipere=ipere+1 if (ipere.gt.nqtot) then WRITE(lunout,*) 'Le traceur',iq,'appele ', & & trim(tnom_0(iq)),', est orphelin.' CALL abort_gcm('infotrac_init','Un traceur est orphelin',1) endif !if (ipere.gt.nqtot) then endif !if (tnom_transp(iq) == tnom_0(ipere)) then enddo !do while (continu) endif !if (tnom_transp(iq) == 'air') then enddo !DO iq=1,nqtot WRITE(lunout,*) 'infotrac: nqGen0=',COUNT(tracers(:)%parent == 'air') WRITE(lunout,*) 'nqChilds=',tracers(:)%nqChilds WRITE(lunout,*) 'iqParent=',tracers(:)%iqParent WRITE(lunout,*) 'iqfils=',iqfils ! Calculer le nombre de descendants a partir de iqfils et de nbfils DO iq=1,nqtot tracers(iq)%iGeneration=0 continu=.true. ifils=iq do while (continu) ipere=tracers(ifils)%iqParent if (ipere.gt.0) then tracers(ipere)%nqDescen = tracers(ipere)%nqDescen+1 iqfils(tracers(ipere)%nqDescen,ipere)=iq ifils=ipere tracers(iq)%iGeneration=tracers(iq)%iGeneration+1 else !if (ipere.gt.0) then continu=.false. endif !if (ipere.gt.0) then enddo !do while (continu) WRITE(lunout,*) 'Le traceur ',iq,', appele ',trim(tnom_0(iq)), & ' est un traceur de generation: ',tracers(iq)%iGeneration enddo !DO iq=1,nqtot DO iq=1,nqtot ALLOCATE(tracers(iq)%iqDescen(tracers(iq)%nqDescen)) tracers(iq)%iqDescen(:) = iqfils(1:tracers(iq)%nqDescen,iq) END DO WRITE(lunout,*) 'infotrac: nqDescen=',tracers(:)%nqDescen WRITE(lunout,*) 'iqfils=',iqfils WRITE(lunout,*) 'nqDescen_tot=',SUM(tracers(:)%nqDescen) ! Interdire autres schemas que 10 pour les traceurs fils, et autres schemas ! que 10 et 14 si des peres ont des fils do iq=1,nqtot if (tracers(iq)%iqParent > 0) then ! ce traceur a un pere qui n'est pas l'air ! Seul le schema 10 est autorise iadv=tracers(iq)%iadv if (iadv/=10) then WRITE(lunout,*)trim(modname),' STOP : The option iadv=',iadv,' is not implemented for sons' CALL abort_gcm('infotrac_init','Sons should be advected by scheme 10',1) endif ! Le traceur pere ne peut etre advecte que par schema 10 ou 14: IF (ALL([10,14]/=tracers(tracers(iq)%iqParent)%iadv)) THEN WRITE(lunout,*)trim(modname),' STOP : The option iadv=',iadv,' is not implemented for fathers' CALL abort_gcm('infotrac_init','Fathers should be advected by scheme 10 ou 14',1) endif endif enddo !do iq=1,nqtot tracers(:)%gen0Name = ancestor(tracers) !--- Name of the first generation ancestor tracers(:)%isAdvected = tracers(:)%iadv > 0 ! tracers(:)%isH2Ofamily = delPhase(tracers(:)%gen0Name) == 'H2O' tracers(:)%isH2Ofamily = [(tracers(iq)%gen0Name(1:3) == 'H2O', iq=1, nqtot)] ! detecter quels sont les traceurs isotopiques parmi des traceurs call infotrac_isoinit(tnom_0,nqtrue) ! if (ntraciso.gt.0) then ! le 18 sep 2020: on enleve la condition ntraciso.gt.0 car nqtottr doit etre ! connu meme si il n'y a pas d'isotopes! write(lunout,*) 'infotrac 702: nbtr,ntraciso=',nbtr,ntraciso ! retrancher les traceurs isotopiques de la liste des traceurs qui passent dans ! phytrac nbtr=nbtr-nqo*ntraciso ! faire un tableau d'indice des traceurs qui passeront dans phytrac nqtottr=nqtot-nqo*(1+ntraciso) write(lunout,*) 'infotrac 704: nqtottr,nqtot,nqo=',nqtottr,nqtot,nqo ! Rq: nqtottr n'est pas forcement egal a nbtr dans le cas ou new_iq /= nqtrue ! if (COUNT(tracers(:)%iso_iName == 0) /= nqtottr) & ! CALL abort_gcm('infotrac_init','pb dans le calcul de nqtottr',1) ! endif !if (ntraciso.gt.0) then !----------------------------------------------------------------------- ! Finalize : ! DEALLOCATE(tnom_0, hadv, vadv,tnom_transp) WRITE(lunout,*) 'infotrac init fin' END SUBROUTINE infotrac_init SUBROUTINE infotrac_isoinit(tnom_0,nqtrue) #ifdef CPP_IOIPSL use IOIPSL #else ! if not using IOIPSL, we still need to use (a local version of) getin use ioipsl_getincom #endif implicit none ! inputs INTEGER,INTENT(IN) :: nqtrue CHARACTER(len=*),INTENT(IN) :: tnom_0(nqtrue) ! locals CHARACTER(len=3), DIMENSION(niso_possibles) :: tnom_iso INTEGER, ALLOCATABLE,DIMENSION(:,:) :: nb_iso,nb_traciso INTEGER, ALLOCATABLE,DIMENSION(:) :: nb_isoind INTEGER :: ntraceurs_zone_prec,iq,phase,ixt,iiso,izone CHARACTER(len=maxlen) :: tnom_trac INCLUDE "iniprint.h" tnom_iso=(/'eau','HDO','O18','O17','HTO'/) ALLOCATE(nb_iso(niso_possibles,nqo)) ALLOCATE(nb_isoind(nqo)) ALLOCATE(nb_traciso(niso_possibles,nqo)) ALLOCATE(iso_indnum(nqtot)) iso_indnum(:)=0 indnum_fn_num(:)=0 use_iso(:)=.false. nb_iso(:,:)=0 nb_isoind(:)=0 nb_traciso(:,:)=0 niso=0 ntraceurs_zone=0 ntraceurs_zone_prec=0 ntraciso=0 do iq=nqo+1,nqtot ! write(lunout,*) 'infotrac 569: iq,tnom_0(iq)=',iq,tnom_0(iq) do phase=1,nqo do ixt= 1,niso_possibles tnom_trac=trim(tnom_0(phase))//'_' tnom_trac=trim(tnom_trac)//trim(tnom_iso(ixt)) ! write(*,*) 'phase,ixt,tnom_trac=',phase,ixt,tnom_trac IF (tnom_0(iq) == tnom_trac) then ! write(lunout,*) 'Ce traceur est un isotope' nb_iso(ixt,phase)=nb_iso(ixt,phase)+1 nb_isoind(phase)=nb_isoind(phase)+1 tracers(iq)%iso_iName=ixt iso_indnum(iq)=nb_isoind(phase) indnum_fn_num(ixt)=iso_indnum(iq) tracers(iq)%iso_iPhase=phase goto 20 else if ( tracers(iq)%iqParent> 0) then if (tnom_0(tracers(iq)%iqParent) == tnom_trac) then ! write(lunout,*) 'Ce traceur est le fils d''un isotope' ! c'est un traceur d'isotope nb_traciso(ixt,phase)=nb_traciso(ixt,phase)+1 tracers(iq)%iso_iName=ixt iso_indnum(iq)=indnum_fn_num(ixt) tracers(iq)%iso_iZone=nb_traciso(ixt,phase) tracers(iq)%iso_iPhase=phase goto 20 endif !if (tnom_0(tracers(iq)%iqParent) == trim(tnom_0(phase))//trim(tnom_iso(ixt))) then endif !IF (tnom_0(iq) == trim(tnom_0(phase))//trim(tnom_iso(ixt))) then enddo !do ixt= niso_possibles enddo !do phase=1,nqo 20 continue enddo !do iq=1,nqtot do ixt= 1,niso_possibles if (nb_iso(ixt,1).eq.1) then ! on verifie que toutes les phases ont le meme nombre de ! traceurs do phase=2,nqo if (nb_iso(ixt,phase).ne.nb_iso(ixt,1)) then ! write(lunout,*) 'ixt,phase,nb_iso=',ixt,phase,nb_iso(ixt,phase) CALL abort_gcm('infotrac_init','Phases must have same number of isotopes',1) endif enddo !do phase=2,nqo niso=niso+1 use_iso(ixt)=.true. ntraceurs_zone=nb_traciso(ixt,1) ! on verifie que toutes les phases ont le meme nombre de ! traceurs do phase=2,nqo if (nb_traciso(ixt,phase).ne.ntraceurs_zone) then write(lunout,*) 'ixt,phase,nb_traciso=',ixt,phase,nb_traciso(ixt,phase) write(lunout,*) 'ntraceurs_zone=',ntraceurs_zone CALL abort_gcm('infotrac_init','Phases must have same number of tracers',1) endif enddo !do phase=2,nqo ! on verifie que tous les isotopes ont le meme nombre de ! traceurs if (ntraceurs_zone_prec.gt.0) then if (ntraceurs_zone.eq.ntraceurs_zone_prec) then ntraceurs_zone_prec=ntraceurs_zone else !if (ntraceurs_zone.eq.ntraceurs_zone_prec) then write(*,*) 'ntraceurs_zone_prec,ntraceurs_zone=',ntraceurs_zone_prec,ntraceurs_zone CALL abort_gcm('infotrac_init', & &'Isotope tracers are not well defined in traceur.def',1) endif !if (ntraceurs_zone.eq.ntraceurs_zone_prec) then endif !if (ntraceurs_zone_prec.gt.0) then else if (nb_iso(ixt,1).ne.0) then WRITE(lunout,*) 'nqo,ixt=',nqo,ixt WRITE(lunout,*) 'nb_iso(ixt,1)=',nb_iso(ixt,1) CALL abort_gcm('infotrac_init','Isotopes are not well defined in traceur.def',1) endif !if (nb_iso(ixt,1).eq.1) then enddo ! do ixt= niso_possibles ! dimensions isotopique: ntraciso=niso*(ntraceurs_zone+1) ! WRITE(lunout,*) 'niso=',niso ! WRITE(lunout,*) 'ntraceurs_zone,ntraciso=',ntraceurs_zone,ntraciso ! flags isotopiques: ok_isotopes = niso > 0 ! WRITE(lunout,*) 'ok_isotopes=',ok_isotopes if (ok_isotopes) then ok_iso_verif=.false. call getin('ok_iso_verif',ok_iso_verif) ok_init_iso=.false. call getin('ok_init_iso',ok_init_iso) tnat=(/1.0,155.76e-6,2005.2e-6,0.004/100.,0.0/) alpha_ideal=(/1.0,1.01,1.006,1.003,1.0/) endif !if (ok_isotopes) then ! WRITE(lunout,*) 'ok_iso_verif=',ok_iso_verif ! WRITE(lunout,*) 'ok_init_iso=',ok_init_iso if (ntraceurs_zone.gt.0) then ok_isotrac=.true. else ok_isotrac=.false. endif ! WRITE(lunout,*) 'ok_isotrac=',ok_isotrac ! remplissage du tableau iqiso(ntraciso,phase) ALLOCATE(iqiso(ntraciso,nqo)) iqiso(:,:)=0 do iq=1,nqtot if (tracers(iq)%iso_iName > 0) then ixt=iso_indnum(iq)+tracers(iq)%iso_iZone*niso iqiso(ixt,tracers(iq)%iso_iPhase)=iq endif enddo ! WRITE(lunout,*) 'iqiso=',iqiso ! replissage du tableau index_trac(ntraceurs_zone,niso) ALLOCATE(index_trac(ntraceurs_zone,niso)) if (ok_isotrac) then do iiso=1,niso do izone=1,ntraceurs_zone index_trac(izone,iiso)=iiso+izone*niso enddo enddo else !if (ok_isotrac) then index_trac(:,:)=0.0 endif !if (ok_isotrac) then ! write(lunout,*) 'index_trac=',index_trac ! Finalize : DEALLOCATE(nb_iso) END SUBROUTINE infotrac_isoinit END MODULE infotrac