Changeset 4149


Ignore:
Timestamp:
May 14, 2022, 8:13:22 PM (2 years ago)
Author:
dcugnet
Message:
  • remove striso (use isoName instead)
  • few fixes for the lOldCode=.FALSE. code
  • add the « isotopes_params.def » file, used in the lOldCode=.FALSE. part of the isotopes_mod module.


Location:
LMDZ6/trunk
Files:
1 added
5 edited

Legend:

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

    r4143 r4149  
    33
    44MODULE isotopes_mod
    5    USE strings_mod, ONLY: msg, real2str, int2str, bool2str, maxlen, strIdx, strStack
     5   USE strings_mod,  ONLY: msg, real2str, int2str, bool2str, maxlen, strIdx, strStack
     6   USE infotrac_phy, ONLY: isoName
    67   IMPLICIT NONE
    78   INTERFACE get_in; MODULE PROCEDURE getinp_s, getinp_i, getinp_r, getinp_l;  END INTERFACE get_in
     
    1011  !--- Contains all isotopic variables + their initialization
    1112  !--- Isotopes-specific routines are in isotopes_routines_mod to avoid circular dependencies with isotopes_verif_mod.
     13
     14  LOGICAL, PARAMETER :: lOldCode=.TRUE.
    1215
    1316   !--- Isotopes indices (in [1,niso] ; non-existing => 0 index)
     
    105108                    alpha_liq_sol, Rdefault, Rmethox
    106109!$OMP THREADPRIVATE(alpha_liq_sol, Rdefault, Rmethox)
    107 character*3, ALLOCATABLE, DIMENSION(:), save :: striso
    108 !$OMP THREADPRIVATE(striso)
    109110   REAL, SAVE ::    fac_coeff_eq17_liq, fac_coeff_eq17_ice
    110111!$OMP THREADPRIVATE(fac_coeff_eq17_liq, fac_coeff_eq17_ice)
     
    136137SUBROUTINE iso_init()
    137138   USE ioipsl_getin_p_mod, ONLY: getin_p
    138    USE infotrac_phy,       ONLY: ntiso, niso, isoName
     139   USE infotrac_phy,       ONLY: ntiso, niso, getKey
     140    USE strings_mod,       ONLY: maxlen
    139141   IMPLICIT NONE
    140142
     
    149151   !--- For H2[17]O
    150152   REAL    :: fac_kcin, pente_MWL
    151    INTEGER :: ierr
    152153     
    153154   !--- Sensitivity tests
     
    160161
    161162   CHARACTER(LEN=maxlen) :: modname, sxt
     163   REAL, ALLOCATABLE :: tmp(:)
    162164
    163165   modname = 'iso_init'
     
    165167
    166168   !--- Memory allocations
     169   IF(lOldCode) THEN
    167170   ALLOCATE(talph1(niso), tkcin0(niso),  talps1(niso),  tnat(niso))
    168171   ALLOCATE(talph2(niso), tkcin1(niso),  talps2(niso),  toce(niso))
    169172   ALLOCATE(talph3(niso), tkcin2(niso), tdifrel(niso), tcorr(niso))
    170173   ALLOCATE(alpha_liq_sol(niso),   Rdefault(niso),   Rmethox(niso))
    171    ALLOCATE(striso(niso))
     174   END IF
    172175
    173176
     
    184187
    185188   !--- Type of water isotopes:
    186    iso_eau = strIdx(isoName, 'H2[16]O'); CALL msg('59: iso_eau='//int2str(iso_eau), modname)
    187    iso_O17 = strIdx(isoName, 'H2[17]O'); CALL msg('iso_HDO='//int2str(iso_HDO), modname)
     189   iso_eau = strIdx(isoName, 'H2[16]O'); CALL msg('iso_eau='//int2str(iso_eau), modname)
     190   iso_HDO = strIdx(isoName, 'H[2]HO'); CALL msg('iso_HDO='//int2str(iso_HDO), modname)
    188191   iso_O18 = strIdx(isoName, 'H2[18]O'); CALL msg('iso_O18='//int2str(iso_O18), modname)
    189    iso_HDO = strIdx(isoName, 'H[2]HO'); CALL msg('iso_O17='//int2str(iso_O17), modname)
     192   iso_O17 = strIdx(isoName, 'H2[17]O'); CALL msg('iso_O17='//int2str(iso_O17), modname)
    190193   iso_HTO = strIdx(isoName, 'H[3]HO');  CALL msg('iso_HTO='//int2str(iso_HTO), modname)
    191194
     
    229232      CALL get_in('lat_max_albedo', lat_max_albedo,  100.)
    230233   END IF
     234   IF(lOldCode) &
    231235   CALL get_in('deltaO18_oce',        deltaO18_oce,   0.0)
    232 
     236   deltaO18_oce=0.0
    233237   CALL get_in('deltaP_BL',           deltaP_BL,     10.0)
    234238   CALL get_in('ruissellement_pluie', ruissellement_pluie, 0)
     
    298302    T_cste_surf_cond = 288.0
    299303   
     304   CALL msg('iso_O18, iso_HDO, iso_eau = '//TRIM(strStack(int2str([iso_O18, iso_HDO, iso_eau]))), modname)
     305
    300306   !--------------------------------------------------------------
    301307   ! Parameters that depend on the nature of water isotopes:
    302308   !--------------------------------------------------------------
     309
     310   !===========================================================================================================================
     311   IF(lOldCode) THEN
     312   !===========================================================================================================================
     313
    303314   ! Local constants
    304315   fac_enrichoce18 = 0.0005            ! Then: tcorO18 = 1 + fac_enrichoce18
     
    317328   fac_coeff_eq17_ice = 0.529
    318329
    319    CALL msg('iso_O18, iso_HDO, iso_eau = '//TRIM(strStack(int2str([iso_O18, iso_HDO, iso_eau]))), modname)
    320 
    321330   !--- Kinetic factor for surface evaporation:
    322331   ! (cf: kcin = tkcin0                  if |V|<tv0cin
     
    326335   DO ixt = 1, niso
    327336      sxt=int2str(ixt)
    328       WRITE(*,*) 'iso_init 80: ixt=',ixt
     337      CALL msg('80: ixt='//TRIM(int2str(ixt)),modname)
    329338
    330339      Rdefault(ixt) = 0.0
     
    343352         alpha_liq_sol(ixt) = 1.
    344353         Rmethox(ixt) = 0.0
    345          striso (ixt) = 'HTO'
    346354      ELSE IF(ixt == iso_O17) THEN     !=== H2[17]O
    347355         tdifrel(ixt)=1./0.98555       ! Used in 1D and in LdG's model
     
    361369         IF(Rdefault_smow) Rdefault(ixt) = tnat(ixt)*(-3.15/1000.0+1.0)
    362370         Rmethox(ixt) = (230./1000.+1.)*tnat(ixt)     ! Zahn et al 2006
    363          striso (ixt) = 'O17'
    364371      ELSE IF(ixt == iso_O18) THEN     !=== H2[18]O
    365372         tdifrel(ixt) = tdifrel_O18
     
    375382         IF(Rdefault_smow) Rdefault(ixt) = tnat(ixt)*(-6.0/1000.0+1.0)
    376383         Rmethox(ixt) = (130./1000.+1.)*tnat(ixt) ! Zahn et al 2006   
    377          striso (ixt) = 'O18'
    378          CALL msg('519: ixt, striso(ixt) = '//TRIM(sxt)//', '//TRIM(striso(ixt)), modname)
    379384      ELSE IF(ixt == iso_HDO) THEN     !=== H[2]HO
    380385         tdifrel(ixt) = 1./0.9755
     
    395400         IF(Rdefault_smow) Rdefault(ixt) = tnat(ixt)*((-6.0*pente_MWL+10.0)/1000.0+1.0)
    396401         Rmethox(ixt) = tnat(ixt)*(-25.0/1000.+1.) ! Zahn et al 2006
    397          striso (ixt) = 'HDO'
    398          CALL msg('548: ixt,striso(ixt) = '//TRIM(sxt)//', '//striso(ixt), modname)
    399402      ELSE IF(ixt  == iso_eau) THEN    !=== H2O[16]
    400403         tkcin0(ixt) = 0.0
     
    406409         tdifrel(ixt) = 1.
    407410         talph1(ixt) = 0. ; talph2(ixt) = 0. ; talph3(ixt) = 0.
    408          talps1(ixt) = 0. ; talph3(ixt) = 0.
     411         talps1(ixt) = 0. ; talps2(ixt) = 0.
    409412         alpha_liq_sol(ixt)=1.
    410413         IF(Rdefault_smow) Rdefault(ixt) = tnat(ixt)*1.0
    411414         Rmethox(ixt) = 1.0
    412          striso(ixt) = 'eau'
    413415      END IF
    414416   END DO
     417   !===========================================================================================================================
     418   ELSE
     419   !===========================================================================================================================
     420
     421   IF(getKey('tnat',    tnat,    isoName)) CALL abort_physic(modname, 'can''t get tnat',    1)
     422   IF(getKey('toce',    toce,    isoName)) CALL abort_physic(modname, 'can''t get toce',    1)
     423   IF(getKey('tcorr',   tcorr,   isoName)) CALL abort_physic(modname, 'can''t get tcorr',   1)
     424   IF(getKey('talph1',  talph1,  isoName)) CALL abort_physic(modname, 'can''t get talph1',  1)
     425   IF(getKey('talph2',  talph2,  isoName)) CALL abort_physic(modname, 'can''t get talph2',  1)
     426   IF(getKey('talph3',  talph3,  isoName)) CALL abort_physic(modname, 'can''t get talph3',  1)
     427   IF(getKey('talps1',  talps1,  isoName)) CALL abort_physic(modname, 'can''t get talps1',  1)
     428   IF(getKey('talps2',  talps2,  isoName)) CALL abort_physic(modname, 'can''t get talps2',  1)
     429   IF(getKey('tkcin0',  tkcin0,  isoName)) CALL abort_physic(modname, 'can''t get tkcin0',  1)
     430   IF(getKey('tkcin1',  tkcin1,  isoName)) CALL abort_physic(modname, 'can''t get tkcin1',  1)
     431   IF(getKey('tkcin2',  tkcin2,  isoName)) CALL abort_physic(modname, 'can''t get tkcin2',  1)
     432   IF(getKey('tdifrel', tdifrel, isoName)) CALL abort_physic(modname, 'can''t get tdifrel', 1)
     433   DO ixt = 1, niso
     434      IF     (ixt == iso_HTO) THEN; tdifrel(ixt) = 1./0.968
     435      ELSE IF(ixt == iso_HDO) THEN; tdifrel(ixt) = 1./0.9755
     436      ELSE IF(ixt == iso_O17) THEN; tdifrel(ixt) = 1./0.98555
     437      ELSE IF(ixt == iso_O18) THEN; tdifrel(ixt) = 1./0.9723
     438      ELSE IF(ixt == iso_eau) THEN; tdifrel(ixt) = 1.; END IF
     439   END DO
     440   IF(getKey('alpha_liq_sol', alpha_liq_sol, isoName)) CALL abort_physic(modname, 'can''t get alpha_liq_sol',  1)
     441   IF(getKey('Rdefault',Rdefault,isoName)) CALL abort_physic(modname, 'can''t get Rdefault',1)
     442   IF(getKey('Rmethox', Rmethox, isoName)) CALL abort_physic(modname, 'can''t get Rmethox', 1)
     443   IF(.NOT.Rdefault_smow) Rdefault(:) = 0.0
     444
     445   !===========================================================================================================================
     446   END IF
     447   !===========================================================================================================================
    415448
    416449   !--- Sensitivity test: no kinetic effect in sfc evaporation
     
    423456   CALL msg('285: verif initialisation:', modname)
    424457   DO ixt=1,niso
    425       CALL msg(' * striso('//TRIM(sxt)//') = <'//TRIM(striso(ixt))//'>',   modname)
    426       CALL msg(  '   tnat('//TRIM(sxt)//') = '//TRIM(real2str(tnat(ixt))), modname)
    427 !     CALL msg('   alpha_liq_sol('//TRIM(sxt)//') = '//TRIM(real2str(alpha_liq_sol(ixt))), modname)
    428 !     CALL msg(       '   tkcin0('//TRIM(sxt)//') = '//TRIM(real2str(tkcin0(ixt))),        modname)
    429 !     CALL msg(      '   tdifrel('//TRIM(sxt)//') = '//TRIM(real2str(tdifrel(ixt))),       modname)
     458      sxt=int2str(ixt)
     459      CALL msg(' * isoName('//TRIM(sxt)//') = <'//TRIM(isoName(ixt))//'>',  modname)
     460      CALL msg(  '    tnat('//TRIM(sxt)//') = '//TRIM(real2str(tnat(ixt))), modname)
     461!     CALL msg('    alpha_liq_sol('//TRIM(sxt)//') = '//TRIM(real2str(alpha_liq_sol(ixt))), modname)
     462!     CALL msg(        '   tkcin0('//TRIM(sxt)//') = '//TRIM(real2str(tkcin0(ixt))),        modname)
     463!     CALL msg(       '   tdifrel('//TRIM(sxt)//') = '//TRIM(real2str(tdifrel(ixt))),       modname)
    430464   END DO
    431465   CALL msg('69:     lambda = '//TRIM(real2str(lambda_sursat)), modname)
  • LMDZ6/trunk/libf/phylmdiso/isotopes_routines_mod.F90

    r4143 r4149  
    1652516525      !USE write_field_phy
    1652616526      USE indice_sol_mod, only: nbsrf 
    16527   USE isotopes_mod, ONLY: striso,iso_HDO,iso_eau
     16527  USE isotopes_mod, ONLY: isoName,iso_HDO,iso_eau
    1652816528#ifdef ISOVERIF
    1652916529  USE isotopes_verif_mod
     
    1656316563        CHARACTER*5 str5
    1656416564        real xmin,xmax   
    16565         CHARACTER*50 striso_sortie 
     16565        CHARACTER*50 outiso 
    1656616566        integer lnblnk
    1656716567        LOGICAL :: found,phyetat0_get,phyetat0_srf
     
    1658116581   write(*,*) 'phyiso_etat0_fichier 3'
    1658216582   write(*,*) 'niso=',niso
    16583    write(*,*) 'striso(1)=',striso(1)
     16583   write(*,*) 'isoName(1)='//TRIM(isoName(1))
    1658416584
    1658516585   do ixt=1,ntraciso
    1658616586
    16587      if (ixt.le.niso) then
    16588         striso_sortie=striso(ixt)
    16589      else
    16590 #ifdef ISOTRAC
    16591         iiso=index_iso(ixt)
    16592         izone=index_zone(ixt)       
    16593         striso_sortie=striso(iiso)//strtrac(izone)
    16594 #else
    16595         write(*,*) 'phyredem 546: ixt,ntraciso=', ixt,ntraciso
    16596         stop
    16597 #endif
    16598      endif !if (ixt.le.niso) then
    16599      write(*,*) 'phyiso_etat0_fichier 16621: ixt,striso_sortie=',ixt,striso_sortie(1:lnblnk(striso_sortie))
     16587      outiso=TRIM(isoName(ixt))
     16588      i = INDEX(outiso, '_', .TRUE.)
     16589      outiso = outiso(1:i-1)//outiso(i+1:LEN_TRIM(outiso))
     16590      write(*,*) 'phyiso_etat0_fichier 16621: ixt,outiso=',ixt,TRIM(outiso)
    1660016591
    1660116592           
     
    1660616597#endif
    1660716598
    16608       found=phyetat0_srf(1,iso_tmp_lonsrf,"XTSNOW"//striso_sortie(1:lnblnk(striso_sortie)), &
    16609      &     "Surface snow",0.)
    16610       if (.NOT.found) then
    16611         CALL abort_physic('isotopes_routines_mod', &
    16612                 'phyiso_etat0_fichier 16581: variable isotopique not found',1)
    16613       endif
     16599      found=phyetat0_srf(1,iso_tmp_lonsrf,"XTSNOW"//TRIM(outiso),"Surface snow",0.)
     16600      if (.NOT.found) CALL abort_physic('isotopes_routines_mod', &
     16601                            'phyiso_etat0_fichier 16581: variable isotopique not found',1)
    1661416602      xtsnow(ixt,:,:)=iso_tmp_lonsrf(:,:)
    1661516603     
    16616       found=phyetat0_srf(1,iso_tmp_lonsrf,"XTEVAP"//striso_sortie &
    16617      &   (1:lnblnk(striso_sortie)),"evaporation",0.)
     16604      found=phyetat0_srf(1,iso_tmp_lonsrf,"XTEVAP"//TRIM(outiso),"evaporation",0.)
    1661816605      fxtevap(ixt,:,:)=iso_tmp_lonsrf(:,:)
    1661916606
    16620       found=phyetat0_get(1,iso_tmp,"xtrain_f"//striso_sortie &
    16621      &   (1:lnblnk(striso_sortie)),"xrain fall",0.)
     16607      found=phyetat0_get(1,iso_tmp,"xtrain_f"//TRIM(outiso),"xrain fall",0.)
    1662216608      xtrain_fall(ixt,:)=iso_tmp(:)
    1662316609
    16624       found=phyetat0_get(1,iso_tmp,"xtsnow_f"//striso_sortie &
    16625      &   (1:lnblnk(striso_sortie)),"snow fall",0.)
     16610      found=phyetat0_get(1,iso_tmp,"xtsnow_f"//TRIM(outiso),"snow fall",0.)
    1662616611      xtsnow_fall(ixt,:)=iso_tmp(:)
    1662716612
    16628       found=phyetat0_get(klev,iso_tmp_lonlev,"XTANCIEN"//striso_sortie &
    16629      &       (1:lnblnk(striso_sortie)),"QANCIEN",0.)
     16613      found=phyetat0_get(klev,iso_tmp_lonlev,"XTANCIEN"//TRIM(outiso),"QANCIEN",0.)
    1663016614      xt_ancien(ixt,:,:)=iso_tmp_lonlev(:,:)
    1663116615
    16632       found=phyetat0_get(klev,iso_tmp_lonlev,"XTLANCIEN"//striso_sortie &
    16633      &       (1:lnblnk(striso_sortie)),"QLANCIEN",0.)
     16616      found=phyetat0_get(klev,iso_tmp_lonlev,"XTLANCIEN"//TRIM(outiso),"QLANCIEN",0.)
    1663416617      xtl_ancien(ixt,:,:)=iso_tmp_lonlev(:,:)
    1663516618
    16636       found=phyetat0_get(klev,iso_tmp_lonlev,"XTSANCIEN"//striso_sortie &
    16637      &       (1:lnblnk(striso_sortie)),"QSANCIEN",0.)
     16619      found=phyetat0_get(klev,iso_tmp_lonlev,"XTSANCIEN"//TRIM(outiso),"QSANCIEN",0.)
    1663816620      xts_ancien(ixt,:,:)=iso_tmp_lonlev(:,:)
    1663916621
    16640 
    16641       found=phyetat0_get(1,iso_tmp,"XTRUNOFFLIC0"//striso_sortie(1:lnblnk(striso_sortie)), &
    16642      &          "RUNOFFLIC0",0.) 
     16622      found=phyetat0_get(1,iso_tmp,"XTRUNOFFLIC0"//TRIM(outiso),"RUNOFFLIC0",0.) 
    1664316623      xtrun_off_lic_0(ixt,:)=iso_tmp(:)
    1664416624
    16645 
    16646       found=phyetat0_get(klev,iso_tmp_lonlev,"WAKE_DELTAXT"//striso_sortie &
    16647      &   (1:lnblnk(striso_sortie)),"Delta hum. wake/env",0.) 
     16625      found=phyetat0_get(klev,iso_tmp_lonlev,"WAKE_DELTAXT"//TRIM(outiso),"Delta hum. wake/env",0.) 
    1664816626      wake_deltaxt(ixt,:,:)=iso_tmp_lonlev(:,:)
    1664916627
     
    1668716665       ! ces variables n'ont pas de traceurs:
    1668816666       if (ixt.le.niso) then
    16689         found=phyetat0_get(1,iso_tmp,"XTSOL"//striso_sortie(1:lnblnk(striso_sortie)), &
    16690      &     "Surface hmidity / bucket",0.) 
     16667        found=phyetat0_get(1,iso_tmp,"XTSOL"//TRIM(outiso),"Surface hmidity / bucket",0.) 
    1669116668        xtsol(ixt,:)=iso_tmp(:)
    1669216669
    16693         found=phyetat0_get(1,iso_tmp,"Rland_ice"//striso_sortie &
    16694      &     (1:lnblnk(striso_sortie)),"R land ice",0.)
     16670        found=phyetat0_get(1,iso_tmp,"Rland_ice"//TRIM(outiso),"R land ice",0.)
    1669516671        Rland_ice(ixt,:)=iso_tmp(:)
    1669616672
  • LMDZ6/trunk/libf/phylmdiso/isotopes_verif_mod.F90

    r4143 r4149  
    19391939
    19401940        function iso_verif_tracpos_choix_nostop(x,err_msg,seuil)
    1941         use isotrac_mod, only: index_iso,strtrac,index_zone
    1942         use isotopes_mod, only: striso
     1941        use isotopes_mod, only: isoName
    19431942        implicit none
    19441943
     
    19591958
    19601959       do ixt=niso+1,ntraciso
    1961           iiso=index_iso(ixt)
    19621960          if (iso_verif_positif_choix_nostop(x(ixt),seuil,err_msg// &
    1963      &           ', verif positif, iso'//striso(iiso) &
    1964      &           //strtrac(index_zone(ixt))).eq.1) then
     1961     &           ', verif positif, iso'//TRIM(isoName(ixt))).eq.1) then
    19651962            iso_verif_tracpos_choix_nostop=1
    19661963          endif
     
    19711968
    19721969        function iso_verif_traceur_noNaN_nostop(x,err_msg)
    1973         use isotrac_mod, only: index_iso
    1974         use isotopes_mod, only: striso
     1970        use isotopes_mod, only: isoName
    19751971        implicit none
    19761972
     
    19911987
    19921988        do ixt=niso+1,ntraciso
    1993           iiso=index_iso(ixt)
    19941989!          write(*,*) 'iso_verif_traceurs 154: iiso,ixt=',iiso,ixt
    19951990          if (iso_verif_noNaN_nostop(x(ixt),err_msg// &
    1996      &           ', verif trac no NaN, iso'//striso(iiso)) &
     1991     &           ', verif trac no NaN, iso'//TRIM(isoName(ixt))) &
    19971992     &           .eq.1) then
    19981993            iso_verif_traceur_noNaN_nostop=1
     
    20052000     &           errmaxin,errmaxrelin)
    20062001
    2007         use isotopes_mod, ONLY: ridicule,striso
     2002        use isotopes_mod, ONLY: ridicule,isoName
    20082003        ! on vérifie juste bilan de masse
    20092004        implicit none
     
    20332028
    20342029          if (iso_verif_egalite_choix_nostop(xtractot,x(iiso), &
    2035      &        err_msg//', verif trac egalite, iso '//striso(iiso), &
     2030     &        err_msg//', verif trac egalite, iso '// &
     2031     &        TRIM(isoName(iiso)), &
    20362032     &        errmaxin,errmaxrelin).eq.1) then
    20372033            write(*,*) 'iso_verif_traceur 202: x=',x
     
    20442040     &           (abs(x(iiso)).gt.ridicule)) then
    20452041            write(*,*) err_msg,', verif masse traceurs, iso ', &
    2046      &          striso(iiso)
     2042     &          TRIM(isoName(iiso))
    20472043            write(*,*) 'iso_verif_traceur 209: x=',x
    20482044!            iso_verif_tracm_choix_nostop=1
     
    23712367        subroutine iso_verif_trac_masse_vect(x,n,m,err_msg, &
    23722368     &            errmax,errmaxrel)
    2373         use isotopes_mod, only: striso
     2369        use isotopes_mod, only: isoName
    23742370        implicit none
    23752371       
     
    24022398        call iso_verif_egalite_std_vect( &
    24032399     &           xtractot,xiiso, &
    2404      &           err_msg//', verif trac egalite, iso '//striso(iiso), &
     2400     &           err_msg//', verif trac egalite, iso ' &
     2401     &           //TRIM(isoName(iiso)), &
    24052402     &           n,m,errmax,errmaxrel)
    24062403        enddo !do iiso=1,niso
  • LMDZ6/trunk/libf/phylmdiso/phyredem.F90

    r4143 r4149  
    489489      USE indice_sol_mod, ONLY: nbsrf
    490490      USE iostart, ONLY: put_field
    491       USE isotopes_mod, ONLY: striso,iso_eau
     491      USE isotopes_mod, ONLY: isoName,iso_eau
    492492#ifdef ISOVERIF
    493493      USE isotopes_verif_mod
     
    568568   do ixt=1,ntiso
    569569
    570      if (ixt.le.niso) then
    571         outiso=striso(ixt)
    572      else
    573 #ifdef ISOTRAC
    574         iiso=index_iso(ixt)
    575         izone=index_zone(ixt)       
    576         outiso=striso(iiso)//strtrac(izone)
    577 #else
    578         write(*,*) 'phyredem 546: ixt,ntiso=', ixt,ntiso
    579         stop
    580 #endif
    581      endif !if (ixt.le.niso) then
     570      outiso = TRIM(isoName(ixt))
     571      i = INDEX(outiso, '_', .TRUE.)
     572      outiso = outiso(1:i-1)//outiso(i+1:LEN_TRIM(outiso))
    582573      write(*,*) 'phyredem 550: ixt,outiso=',ixt,TRIM(outiso)
    583574     
  • LMDZ6/trunk/libf/phylmdiso/phys_output_mod.F90

    r4143 r4149  
    5252#endif
    5353#ifdef ISO
    54     USE isotopes_mod, ONLY: striso,iso_HTO
     54    USE isotopes_mod, ONLY: isoName,iso_HTO
    5555#ifdef ISOTRAC
    5656    use isotrac_mod, only: index_zone,index_iso,strtrac
     
    122122
    123123#ifdef ISO
    124     CHARACTER(LEN=LEN(striso)) :: outiso
     124    CHARACTER(LEN=maxlen) :: outiso
    125125    CHARACTER(LEN=20) :: unit
    126126#endif
     
    546546    write(*,*) 'phys_output_mid 589'
    547547    do ixt=1,ntraciso
    548       if (ixt <= niso) then
    549         outiso=striso(ixt)
    550       else
    551 #ifdef ISOTRAC
    552         iiso=index_iso(ixt)
    553         izone=index_zone(ixt)       
    554         outiso=striso(iiso)//strtrac(izone)
    555 #else
    556         write(*,*) 'phys_output_mod 546: ixt,ntraciso=', ixt,ntraciso
    557         stop
    558 #endif
    559       endif
     548      outiso = TRIM(isoName(ixt))
     549      i = INDEX(outiso, '_', .TRUE.)
     550      outiso = outiso(1:i-1)//outiso(i+1:LEN_TRIM(outiso))
    560551
    561552      flag = [1,  1,  1, 10,  5, 10, 11, 11, 11, 11]; unit = 'kg/(s*m2)'
Note: See TracChangeset for help on using the changeset viewer.