Ignore:
Timestamp:
Dec 15, 2021, 11:18:49 PM (3 years ago)
Author:
dcugnet
Message:

First commit for new tracers.

  • parser routines readTracFiles, strings_mod and tracer_types added in misc using revision 4 of https://svn.lmd.jussieu.fr/tracers-parser
  • tested in sequential and parallel mode using ioipsl.
  • for now, only two fields of "tracers(:)" derived type vector are used: "name" and "longName".
Location:
LMDZ6/trunk/libf/phylmdiso
Files:
5 edited

Legend:

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

    r4026 r4046  
    77! the dynamics (could be further cleaned) and is initialized using values
    88! provided by the dynamics
     9
     10  USE readTracFiles_mod, ONLY: trac_type, maxlen, delPhase
    911
    1012! nqtot : total number of tracers and higher order of moment, water vapor and liquid included
     
    4143!$OMP THREADPRIVATE(nqperes)
    4244
    43 ! Name variables
    44   INTEGER,PARAMETER :: tname_lenmax=128
    45   CHARACTER(len=tname_lenmax), ALLOCATABLE, DIMENSION(:), SAVE :: tname ! tracer short name for restart and diagnostics
    46   CHARACTER(len=tname_lenmax+3), ALLOCATABLE, DIMENSION(:), SAVE :: ttext ! tracer long name for diagnostics
    47 !$OMP THREADPRIVATE(tname,ttext)
    48 
    49 !! iadv  : index of trasport schema for each tracer
    50 !  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE    :: iadv
     45! Tracers parameters
     46  TYPE(trac_type), TARGET, ALLOCATABLE, SAVE :: tracers(:)
     47!$OMP THREADPRIVATE(tracers)
    5148
    5249! niadv : vector keeping the coorspondance between all tracers(nqtot) treated in the
     
    107104CONTAINS
    108105
    109   SUBROUTINE init_infotrac_phy(nqtot_,nqo_,nbtr_,nqtottr_,nqCO2_,tname_,ttext_,type_trac_,&
     106  SUBROUTINE init_infotrac_phy(nqtot_,nqo_,nbtr_,nqtottr_,nqCO2_,tracers_,type_trac_,&
    110107                               niadv_,conv_flg_,pbl_flg_,solsym_,&
    111108                               nqfils_,nqdesc_,nqdesc_tot_,iqfils_,iqpere_,&
     
    139136    INTEGER,INTENT(IN) :: id_BIN01_strat_
    140137#endif
    141     CHARACTER(len=*),INTENT(IN) :: tname_(nqtot_) ! tracer short name for restart and diagnostics
    142     CHARACTER(len=*),INTENT(IN) :: ttext_(nqtot_) ! tracer long name for diagnostics
     138    CHARACTER(len=*),INTENT(IN) :: tracers_(nqtot_) ! tracers descriptors
    143139    CHARACTER(len=*),INTENT(IN) :: type_trac_
    144140    INTEGER,INTENT(IN) :: niadv_ (nqtot_) ! equivalent dyn / physique
     
    179175    nqCO2=nqCO2_
    180176    nqtottr=nqtottr_
     177    ALLOCATE(tracers(nqtot)); tracers(:) = tracers_(:)
    181178#ifdef CPP_StratAer
    182179    nbtr_bin=nbtr_bin_
     
    187184    id_BIN01_strat=id_BIN01_strat_
    188185#endif
    189     ALLOCATE(tname(nqtot))
    190     tname(:) = tname_(:)
    191     ALLOCATE(ttext(nqtot))
    192     ttext(:) = ttext_(:)
    193186    type_trac = type_trac_
    194187    ALLOCATE(niadv(nqtot))
  • LMDZ6/trunk/libf/phylmdiso/phyetat0.F90

    r4040 r4046  
    3131  USE geometry_mod, ONLY : longitude_deg, latitude_deg
    3232  USE iostart, ONLY : close_startphy, get_field, get_var, open_startphy
    33   USE infotrac_phy, only: nbtr, nqo, type_trac, tname, niadv, &
     33  USE infotrac_phy, only: nbtr, nqo, type_trac, tracers, niadv, &
    3434        itr_indice ! C Risi
    3535  USE traclmdz_mod,    ONLY : traclmdz_from_restart
     
    476476        iq=itr_indice(it)                                                   
    477477        iiq=niadv(iq)                                                        ! jyg
    478         found=phyetat0_get(1,trs(:,it),"trs_"//tname(iiq), &
    479               "Surf trac"//tname(iiq),0.)
     478        found=phyetat0_get(1,trs(:,it),"trs_"//TRIM(tracers(iiq)%name), &
     479                                  "Surf trac"//TRIM(tracers(iiq)%name),0.)
    480480     ENDDO
    481481     CALL traclmdz_from_restart(trs)
     
    489489        found=phyetat0_get(1,co2_send,"co2_send","co2 send",co2_ppm)
    490490     ENDIF
    491   ENDIF !IF (type_trac == 'lmdz') THEN
     491  ENDIF
    492492
    493493#ifdef ISO
  • LMDZ6/trunk/libf/phylmdiso/phyredem.F90

    r3940 r4046  
    3838  USE iostart, ONLY: open_restartphy, close_restartphy, enddef_restartphy, put_field, put_var
    3939  USE traclmdz_mod, ONLY : traclmdz_to_restart
    40   USE infotrac_phy, ONLY: type_trac, niadv, tname, nbtr, nqo,itr_indice
     40  USE infotrac_phy, ONLY: type_trac, niadv, tracers, nbtr, nqo,itr_indice
    4141#ifdef ISO
    4242  USE infotrac_phy, ONLY: itr_indice,niso,ntraciso
     
    350350          iq=itr_indice(it)                                                           ! jyg
    351351          iiq=niadv(iq)                                                           ! jyg
    352           CALL put_field(pass,"trs_"//tname(iiq), "", trs(:, it))
     352          CALL put_field(pass,"trs_"//tracers(iiq)%name, "", trs(:, it))
    353353       END DO
    354354       IF (carbon_cycle_cpl) THEN
     
    407407    IF (pass==2) CALL close_restartphy
    408408  ENDDO ! DO pass=1,2   ! pass=1 netcdf definition ; pass=2 netcdf write
    409  
    410 
    411409 
    412410  !$OMP BARRIER
  • LMDZ6/trunk/libf/phylmdiso/phys_output_mod.F90

    r3940 r4046  
    3535    USE iophy
    3636    USE dimphy
    37     USE infotrac_phy, ONLY: nqtot, nqo, niadv, tname, ttext, type_trac, &
     37    USE infotrac_phy, ONLY: nqtot, nqo, niadv, tracers, type_trac, &
    3838        nqtottr,itr_indice ! C Risi
     39    USE strings_mod,  ONLY: maxlen
    3940    USE ioipsl
    4041    USE phys_cal_mod, only : hour, calend
     
    124125
    125126#ifdef ISO
    126       INTEGER  :: ixt,iiso,izone
    127       CHARACTER*50 :: striso_sortie
    128       integer :: lnblnk
    129 #endif
     127    INTEGER  :: ixt,iiso,izone
     128    CHARACTER(LEN=50) :: outiso
     129    CHARACTER(LEN=20) :: unit
     130#endif
     131    CHARACTER(LEN=maxlen) :: tnam, lnam, dn
     132    INTEGER :: flag(nfiles)
    130133
    131134!!!!!!!!!! stockage dans une region limitee pour chaque fichier !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    534537        write(lunout,*) 'itr_indice=',itr_indice
    535538!       IF (nqtot>=nqo+1) THEN
    536         IF (nqtottr>=1) THEN
     539         IF (nqtottr>=1) THEN
    537540!
    538541            !DO iq=nqo+1,nqtot
    539542            ! C Risi: on modifie la boucle
    540             do itr=1,nqtottr ! C Risi
     543          DO itr=1,nqtottr ! C Risi
    541544            iq=itr_indice(itr)  ! C Risi
    542545            write(*,*) 'phys_output_mid 503: itr=',itr
    543546 
    544547            iiq=niadv(iq)
    545             o_trac(itr) = ctrl_out((/ 1, 5, 5, 5, 10, 10, 11, 11, 11, 11 /), &
    546                            tname(iiq),'Tracer '//ttext(iiq), "-",  &
    547                            (/ '', '', '', '', '', '', '', '', '', '' /))
    548             o_dtr_vdf(itr) = ctrl_out((/ 4, 7, 7, 7, 10, 10, 11, 11, 11, 11 /), &
    549                               'd'//trim(tname(iq))//'_vdf',  &
    550                               'Tendance tracer '//ttext(iiq), "-" , &
    551                               (/ '', '', '', '', '', '', '', '', '', '' /))
    552 
    553             o_dtr_the(itr) = ctrl_out((/ 5, 7, 7, 7, 10, 10, 11, 11, 11, 11 /), &
    554                               'd'//trim(tname(iq))//'_the', &
    555                               'Tendance tracer '//ttext(iiq), "-", &
    556                               (/ '', '', '', '', '', '', '', '', '', '' /))
    557 
    558             o_dtr_con(itr) = ctrl_out((/ 5, 7, 7, 7, 10, 10, 11, 11, 11, 11 /), &
    559                               'd'//trim(tname(iq))//'_con', &
    560                               'Tendance tracer '//ttext(iiq), "-", &
    561                               (/ '', '', '', '', '', '', '', '', '', '' /))
    562 
    563             o_dtr_lessi_impa(itr) = ctrl_out((/ 7, 7, 7, 7, 10, 10, 11, 11, 11, 11 /), &
    564                                      'd'//trim(tname(iq))//'_lessi_impa', &
    565                                      'Tendance tracer '//ttext(iiq), "-", &
    566                                      (/ '', '', '', '', '', '', '', '', '', '' /))
    567 
    568             o_dtr_lessi_nucl(itr) = ctrl_out((/ 7, 7, 7, 7, 10, 10, 11, 11, 11, 11 /), &
    569                                      'd'//trim(tname(iq))//'_lessi_nucl', &
    570                                      'Tendance tracer '//ttext(iiq), "-", &
    571                                      (/ '', '', '', '', '', '', '', '', '', '' /))
    572 
    573             o_dtr_insc(itr) = ctrl_out((/ 7, 7, 7, 7, 10, 10, 11, 11, 11, 11 /), &
    574                                'd'//trim(tname(iq))//'_insc', &
    575                                'Tendance tracer '//ttext(iiq), "-", &
    576                                (/ '', '', '', '', '', '', '', '', '', '' /))
    577 
    578             o_dtr_bcscav(itr) = ctrl_out((/ 7, 7, 7, 7, 10, 10, 11, 11, 11, 11 /), &
    579                                  'd'//trim(tname(iq))//'_bcscav', &
    580                                  'Tendance tracer '//ttext(iiq), "-", &
    581                                  (/ '', '', '', '', '', '', '', '', '', '' /))
    582 
    583             o_dtr_evapls(itr) = ctrl_out((/ 7, 7, 7, 7, 10, 10, 11, 11, 11, 11 /), &
    584                                  'd'//trim(tname(iq))//'_evapls', &
    585                                  'Tendance tracer '//ttext(iiq), "-", &
    586                                  (/ '', '', '', '', '', '', '', '', '', '' /))
    587 
    588             o_dtr_ls(itr) = ctrl_out((/ 7, 7, 7, 7, 10, 10, 11, 11, 11, 11 /), &
    589                              'd'//trim(tname(iq))//'_ls', &
    590                              'Tendance tracer '//ttext(iiq), "-", &
    591                              (/ '', '', '', '', '', '', '', '', '', '' /))
    592 
    593             o_dtr_trsp(itr) = ctrl_out((/ 7, 7, 7, 7, 10, 10, 11, 11, 11, 11 /), &
    594                                'd'//trim(tname(iq))//'_trsp', &
    595                                'Tendance tracer '//ttext(iiq), "-", &
    596                                (/ '', '', '', '', '', '', '', '', '', '' /))
    597 
    598             o_dtr_sscav(itr) = ctrl_out((/ 7, 7, 7, 7, 10, 10, 11, 11, 11, 11 /), &
    599                                 'd'//trim(tname(iq))//'_sscav', &
    600                                 'Tendance tracer '//ttext(iiq), "-", &
    601                                 (/ '', '', '', '', '', '', '', '', '', '' /))
    602 
    603             o_dtr_sat(itr) = ctrl_out((/ 7, 7, 7, 7, 10, 10, 11, 11, 11, 11 /), &
    604                                'd'//trim(tname(iq))//'_sat', &
    605                                'Tendance tracer '//ttext(iiq), "-", &
    606                                (/ '', '', '', '', '', '', '', '', '', '' /))
    607 
    608             o_dtr_uscav(itr) = ctrl_out((/ 7, 7, 7, 7, 10, 10, 11, 11, 11, 11 /), &
    609                                 'd'//trim(tname(iq))//'_uscav', &
    610                                 'Tendance tracer '//ttext(iiq), "-", &
    611                                  (/ '', '', '', '', '', '', '', '', '', '' /))
    612 
    613             o_dtr_dry(itr) = ctrl_out((/ 7, 7, 7, 7, 10, 10, 11, 11, 11, 11 /), &
    614                               'cum'//'d'//trim(tname(iq))//'_dry', &
    615                               'tracer tendency dry deposition'//ttext(iiq), "-", &
    616                               (/ '', '', '', '', '', '', '', '', '', '' /))
    617 
    618             o_trac_cum(itr) = ctrl_out((/ 1, 4, 10, 10, 10, 10, 11, 11, 11, 11 /), &
    619                                'cum'//tname(iiq),&
    620                                'Cumulated tracer '//ttext(iiq), "-", &
    621                                (/ '', '', '', '', '', '', '', '', '', '' /))
    622             ENDDO
    623       ENDIF
     548            dn = 'd'//TRIM(tracers(iiq)%name)//'_'
     549
     550            flag = [1, 5, 5, 5, 10, 10, 11, 11, 11, 11]
     551            lnam = 'Tracer '//TRIM(tracers(iiq)%longName)
     552            tnam = TRIM(tracers(iiq)%name); o_trac          (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
     553
     554            flag = [4, 7, 7, 7, 10, 10, 11, 11, 11, 11]
     555            lnam = 'Tendance tracer '//TRIM(tracers(iiq)%longName)
     556            tnam = TRIM(dn)//'vdf';         o_dtr_vdf       (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
     557
     558            flag = [5, 7, 7, 7, 10, 10, 11, 11, 11, 11]
     559            tnam = TRIM(dn)//'the';         o_dtr_the       (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
     560            tnam = TRIM(dn)//'con';         o_dtr_con       (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
     561
     562            flag = [7, 7, 7, 7, 10, 10, 11, 11, 11, 11]
     563            tnam = TRIM(dn)//'lessi_impa';  o_dtr_lessi_impa(itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
     564            tnam = TRIM(dn)//'lessi_nucl';  o_dtr_lessi_nucl(itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
     565            tnam = TRIM(dn)//'insc';        o_dtr_insc      (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
     566            tnam = TRIM(dn)//'bcscav';      o_dtr_bcscav    (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
     567            tnam = TRIM(dn)//'evapls';      o_dtr_evapls    (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
     568            tnam = TRIM(dn)//'ls';          o_dtr_ls        (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
     569            tnam = TRIM(dn)//'trsp';        o_dtr_trsp      (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
     570            tnam = TRIM(dn)//'sscav';       o_dtr_sscav     (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
     571            tnam = TRIM(dn)//'sat';         o_dtr_sat       (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
     572            tnam = TRIM(dn)//'uscav';       o_dtr_uscav     (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
     573
     574            lnam = 'tracer tendency dry deposition'//TRIM(tracers(iiq)%longName)
     575            tnam = 'cum'//TRIM(dn)//'dry';  o_dtr_dry       (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
     576
     577            flag = [1, 4, 10, 10, 10, 10, 11, 11, 11, 11]
     578            lnam = 'Cumulated tracer '//TRIM(tracers(iiq)%longName)
     579            tnam = 'cum'//TRIM(tracers(iiq)%name); o_trac_cum(itr)= ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
     580          ENDDO
     581       ENDIF
    624582
    625583   ENDDO !  iff
     
    627585        write(*,*) 'phys_output_mid 589'
    628586#ifdef ISO
    629   do ixt=1,ntraciso
    630      if (ixt.le.niso) then
     587    do ixt=1,ntraciso
     588      if (ixt.le.niso) then
    631589        striso_sortie=striso(ixt)
    632      else
     590      else
    633591#ifdef ISOTRAC
    634592        iiso=index_iso(ixt)
     
    639597        stop
    640598#endif
    641      endif
    642 
    643    o_xtprecip(ixt)=ctrl_out((/ 1, 1, 1, 10, 5, 10, 11, 11, 11, 11/), &
    644     'precip'//striso_sortie(1:lnblnk(striso_sortie)),  &
    645     'Precip Totale liq+sol', 'kg/(s*m2)', (/ ('', i=1, 10) /))   
    646    o_xtplul(ixt) = ctrl_out((/ 1, 1, 1, 10, 10, 10, 11, 11, 11, 11/), &
    647     'plul'//striso_sortie(1:lnblnk(striso_sortie)),  &
    648     'Large-scale Precip.', 'kg/(s*m2)', (/ ('', i=1, 10) /))
    649    o_xtpluc(ixt) = ctrl_out((/ 1, 1, 1, 10, 5, 10, 11, 11, 11, 11/), &
    650     'pluc'//striso_sortie(1:lnblnk(striso_sortie)),  &
    651     'Convective Precip.', 'kg/(s*m2)', (/ ('', i=1, 10) /))
    652    o_xtevap(ixt) = ctrl_out((/ 1, 1, 10, 10, 10, 10, 11, 11, 11, 11/), &
    653     'evap'//striso_sortie(1:lnblnk(striso_sortie)),  &
    654     'Evaporat', 'kg/(s*m2)', (/ ('', i=1, 10) /))
    655    o_xtovap(ixt) = ctrl_out((/ 2, 3, 4, 10, 10, 10, 11, 11, 11, 11/), &
    656     'ovap'//striso_sortie(1:lnblnk(striso_sortie)),  &
    657     'Specific humidity', 'kg/kg', (/ ('', i=1, 10) /))
    658    o_xtoliq(ixt) = ctrl_out((/ 2, 3, 4, 10, 10, 10, 11, 11, 11, 11/), &
    659     'oliq'//striso_sortie(1:lnblnk(striso_sortie)),  &
    660     'Liquid water', 'kg/kg', (/ ('', i=1, 10) /))
    661    o_xtcond(ixt) = ctrl_out((/ 2, 3, 4, 10, 10, 10, 11, 11, 11, 11/), &
    662     'ocond'//striso_sortie(1:lnblnk(striso_sortie)),  &
    663     'Condensed water', 'kg/kg', (/ ('', i=1, 10) /))     
    664    o_dxtdyn(ixt) = ctrl_out((/ 4, 10, 10, 10, 10, 10, 11, 11, 11, 11/), &
    665     'dqdyn'//striso_sortie(1:lnblnk(striso_sortie)),  &
    666     'Dynamics dQ', '(kg/kg)/s', (/ ('', i=1, 10) /))
    667    o_dxtldyn(ixt) = ctrl_out((/ 4, 10, 10, 10, 10, 10, 11, 11, 11, 11/), &
    668     'dqldyn'//striso_sortie(1:lnblnk(striso_sortie)),  &
    669     'Dynamics dQL', '(kg/kg)/s', (/ ('', i=1, 10) /))
    670    o_dxtcon(ixt) = ctrl_out((/ 4, 10, 10, 10, 10, 10, 11, 11, 11, 11/), &
    671     'dqcon'//striso_sortie(1:lnblnk(striso_sortie)),  &
    672     'Convection dQ', '(kg/kg)/s', (/ ('', i=1, 10) /))
    673    o_dxteva(ixt) = ctrl_out((/ 4, 10, 10, 10, 10, 10, 11, 11, 11, 11/), &
    674     'dqeva'//striso_sortie(1:lnblnk(striso_sortie)),  &
    675     'Reevaporation dQ', '(kg/kg)/s', (/ ('', i=1, 10) /))
    676    o_dxtlsc(ixt) = ctrl_out((/ 4, 10, 10, 10, 10, 10, 11, 11, 11, 11/), &
    677     'dqlsc'//striso_sortie(1:lnblnk(striso_sortie)),  &
    678     'Condensation dQ', '(kg/kg)/s', (/ ('', i=1, 10) /))
    679    o_dxtajs(ixt) = ctrl_out((/ 4, 10, 10, 10, 10, 10, 11, 11, 11, 11/), &
    680     'dqajs'//striso_sortie(1:lnblnk(striso_sortie)),  &
    681     'Dry adjust. dQ', '(kg/kg)/s', (/ ('', i=1, 10) /))
    682    o_dxtvdf(ixt) = ctrl_out((/ 4, 10, 10, 10, 10, 10, 11, 11, 11, 11/), &
    683     'dqvdf'//striso_sortie(1:lnblnk(striso_sortie)),  &
    684     'Boundary-layer dQ', '(kg/kg)/s', (/ ('', i=1, 10) /))
    685    o_dxtthe(ixt) = ctrl_out((/ 4, 10, 10, 10, 10, 10, 11, 11, 11, 11/), &
    686     'dqthe'//striso_sortie(1:lnblnk(striso_sortie)),  &
    687     'Thermal dQ', '(kg/kg)/s', (/ ('', i=1, 10) /))
    688 
    689    IF (ok_qch4) then
    690      o_dxtch4(ixt) = ctrl_out((/ 4, 10, 10, 10, 10, 10, 11, 11, 11, 11/), &
    691         'dqch4'//striso_sortie(1:lnblnk(striso_sortie)),  &
    692     'H2O due to CH4 oxidation & photolysis', '(kg/kg)/s', (/ ('', i=1, 10) /))
    693    endif ! IF (ok_qch4) then
    694 
    695    if (ixt.eq.iso_HTO) then
    696       o_dxtprod_nucl(ixt) = ctrl_out((/ 4, 10, 10, 10, 10, 10, 11, 11, 11, 11/), &
    697         'dqprodnucl'//striso_sortie(1:lnblnk(striso_sortie)),  &
    698         'dHTO/dt due to nuclear production', '(kg/kg)/s', (/ ('', i=1, 10) /))
    699       o_dxtcosmo(ixt) = ctrl_out((/ 4, 10, 10, 10, 10, 10, 11, 11, 11, 11/), &
    700         'dqcosmo'//striso_sortie(1:lnblnk(striso_sortie)),  &
    701         'dHTO/dt due to cosmogenic production', '(kg/kg)/s', (/ ('', i=1, 10) /))
    702       o_dxtdecroiss(ixt) = ctrl_out((/ 4, 10, 10, 10, 10, 10, 11, 11, 11, 11/), &
    703         'dqdecroiss'//striso_sortie(1:lnblnk(striso_sortie)),  &
    704         'dHTO/dt due to radiative destruction', '(kg/kg)/s', (/ ('', i=1, 10) /))
    705    endif !if (ixt.eq.iso_HTO) then
    706   enddo !do ixt=1,niso
     599      endif
     600
     601      flag = [1,  1,  1, 10,  5, 10, 11, 11, 11, 11]; unit = 'kg/(s*m2)'
     602      o_xtprecip(ixt)=ctrl_out(flag, 'precip'//TRIM(outiso), 'Precip Totale liq+sol', unit, [('',i=1,nfiles)])
     603      o_xtpluc  (ixt)=ctrl_out(flag,   'pluc'//TRIM(outiso),    'Convective Precip.', unit, [('',i=1,nfiles)])
     604
     605      flag = [1,  1,  1, 10, 10, 10, 11, 11, 11, 11]
     606      o_xtplul  (ixt)=ctrl_out(flag,   'plul'//TRIM(outiso),   'Large-scale Precip.', unit, [('',i=1,nfiles)])
     607      o_xtevap  (ixt)=ctrl_out(flag,   'evap'//TRIM(outiso),             'Evaporat.', unit, [('',i=1,nfiles)])
     608
     609      flag = [2,  3,  4, 10, 10, 10, 11, 11, 11, 11]; unit = 'kg/kg'
     610      o_xtovap  (ixt)=ctrl_out(flag,   'ovap'//TRIM(outiso),     'Specific humidity', unit, [('',i=1,nfiles)])
     611      o_xtoliq  (ixt)=ctrl_out(flag,   'oliq'//TRIM(outiso),          'Liquid water', unit, [('',i=1,nfiles)])
     612      o_xtcond  (ixt)=ctrl_out(flag,  'ocond'//TRIM(outiso),       'Condensed water', unit, [('',i=1,nfiles)])
     613
     614      flag = [4, 10, 10, 10, 10, 10, 11, 11, 11, 11]; unit = '(kg/kg)/s'
     615      o_dxtdyn  (ixt)=ctrl_out(flag,  'dqdyn'//TRIM(outiso),           'Dynamics dQ', unit, [('',i=1,nfiles)])
     616      o_dxtldyn (ixt)=ctrl_out(flag, 'dqldyn'//TRIM(outiso),          'Dynamics dQL', unit, [('',i=1,nfiles)])
     617      o_dxtcon  (ixt)=ctrl_out(flag,  'dqcon'//TRIM(outiso),         'Convection dQ', unit, [('',i=1,nfiles)])
     618      o_dxteva  (ixt)=ctrl_out(flag,  'dqeva'//TRIM(outiso),      'Reevaporation dQ', unit, [('',i=1,nfiles)])
     619      o_dxtlsc  (ixt)=ctrl_out(flag,  'dqlsc'//TRIM(outiso),       'Condensation dQ', unit, [('',i=1,nfiles)])
     620      o_dxtajs  (ixt)=ctrl_out(flag,  'dqajs'//TRIM(outiso),        'Dry adjust. dQ', unit, [('',i=1,nfiles)])
     621      o_dxtvdf  (ixt)=ctrl_out(flag,  'dqvdf'//TRIM(outiso),     'Boundary-layer dQ', unit, [('',i=1,nfiles)])
     622      o_dxtthe  (ixt)=ctrl_out(flag,  'dqthe'//TRIM(outiso),            'Thermal dQ', unit, [('',i=1,nfiles)])
     623
     624      IF(ok_qch4) o_dxtch4(ixt)=ctrl_out(flag, 'dqch4'//TRIM(outiso), 'H2O due to CH4 oxidation & photolysis', &
     625                                                                                      unit, [('',i=1,nfiles)])
     626      IF(ixt == iso_HTO) THEN
     627      o_dxtprod_nucl(ixt)=ctrl_out(flag, 'dqprodnucl'//TRIM(outiso), 'dHTO/dt due to nuclear production',      &
     628                                                                                      unit, [('',i=1,nfiles)])
     629      o_dxtcosmo    (ixt)=ctrl_out(flag,    'dqcosmo'//TRIM(outiso), 'dHTO/dt due to cosmogenic production',   &
     630                                                                                      unit, [('',i=1,nfiles)])
     631      o_dxtdecroiss (ixt)=ctrl_out(flag, 'dqdecroiss'//TRIM(outiso), 'dHTO/dt due to radiative destruction',   &
     632      END IF
     633    enddo !do ixt=1,niso
    707634#endif
    708635        write(*,*) 'phys_output_mid 596'
  • LMDZ6/trunk/libf/phylmdiso/phys_output_write_mod.F90

    r4040 r4046  
    2525
    2626    USE dimphy, ONLY: klon, klev, klevp1
    27     USE infotrac_phy, ONLY: nbtr
     27    USE infotrac_phy, ONLY: nbtr, nqtot, nqo, type_trac, tracers, niadv, &
     28        nqtottr,itr_indice
     29    USE strings_mod,  ONLY: maxlen
    2830    USE mod_phys_lmdz_para, ONLY: is_north_pole_phy,is_south_pole_phy
    2931    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
     
    383385    USE pbl_surface_mod, ONLY: snow
    384386    USE indice_sol_mod, ONLY: nbsrf
    385     USE infotrac_phy, ONLY: nqtot, nqo, type_trac, tname, niadv, &
    386         nqtottr,itr_indice ! C Risi: ajout nqtottr
    387387#ifdef ISO
    388388    USE infotrac_phy, only: ntraciso,niso,nqtottr
     
    467467    INTEGER ISW
    468468    CHARACTER*1 ch1
    469     CHARACTER*20 varname
     469    CHARACTER(LEN=maxlen) :: varname, dn
    470470
    471471#ifdef CPP_XIOS
     
    538538          DO iq=nqo+1, nqtot
    539539            iiq=niadv(iq)
    540             varname=trim(tname(iiq))
    541             WRITE (lunout,*) 'XIOS var=', nqo, iq, nqtot, varname
     540            dn = 'd'//TRIM(tracers(iiq)%name)//'_'
     541            WRITE (lunout,*) 'XIOS var=', nqo, iq, nqtot, tracers(iiq)%name
     542
     543            unt = "kg kg-1"
     544            varname=trim(tracers(iiq)%name)
    542545            CALL xios_add_child(group_handle, child, varname)
    543             CALL xios_set_attr(child, name=varname, unit="kg kg-1")
    544             varname='d'//trim(tname(iiq))//'_vdf'
     546            CALL xios_set_attr(child, name=varname, unit=unt)
     547
     548            unt = "kg kg-1 s-1"
     549            varname=TRIM(dn)//'vdf'
    545550            CALL xios_add_child(group_handle, child, varname)
    546             CALL xios_set_attr(child, name=varname, unit="kg kg-1 s-1")
    547             varname='d'//trim(tname(iiq))//'_the'
     551            CALL xios_set_attr(child, name=varname, unit=unt)
     552            varname=TRIM(dn)//'the'
    548553            CALL xios_add_child(group_handle, child, varname)
    549             CALL xios_set_attr(child, name=varname, unit="kg kg-1 s-1")
    550             varname='d'//trim(tname(iiq))//'_con'
     554            CALL xios_set_attr(child, name=varname, unit=unt)
     555            varname=TRIM(dn)//'con'
    551556            CALL xios_add_child(group_handle, child, varname)
    552             CALL xios_set_attr(child, name=varname, unit="kg kg-1 s-1")
    553             varname='d'//trim(tname(iiq))//'_lessi_impa'
     557            CALL xios_set_attr(child, name=varname, unit=unt)
     558            varname=TRIM(dn)//'lessi_impa'
    554559            CALL xios_add_child(group_handle, child, varname)
    555             CALL xios_set_attr(child, name=varname, unit="kg kg-1 s-1")
    556             varname='d'//trim(tname(iiq))//'_lessi_nucl'
     560            CALL xios_set_attr(child, name=varname, unit=unt)
     561            varname=TRIM(dn)//'lessi_nucl'
    557562            CALL xios_add_child(group_handle, child, varname)
    558             CALL xios_set_attr(child, name=varname, unit="kg kg-1 s-1")
    559             varname='d'//trim(tname(iiq))//'_insc'
     563            CALL xios_set_attr(child, name=varname, unit=unt)
     564            varname=TRIM(dn)//'insc'
    560565            CALL xios_add_child(group_handle, child, varname)
    561             CALL xios_set_attr(child, name=varname, unit="kg kg-1 s-1")
    562             varname='d'//trim(tname(iiq))//'_bcscav'
     566            CALL xios_set_attr(child, name=varname, unit=unt)
     567            varname=TRIM(dn)//'bcscav'
    563568            CALL xios_add_child(group_handle, child, varname)
    564             CALL xios_set_attr(child, name=varname, unit="kg kg-1 s-1")
    565             varname='d'//trim(tname(iiq))//'_evapls'
     569            CALL xios_set_attr(child, name=varname, unit=unt)
     570            varname=TRIM(dn)//'evapls'
    566571            CALL xios_add_child(group_handle, child, varname)
    567             CALL xios_set_attr(child, name=varname, unit="kg kg-1 s-1")
    568             varname='d'//trim(tname(iiq))//'_ls'
     572            CALL xios_set_attr(child, name=varname, unit=unt)
     573            varname=TRIM(dn)//'ls'
    569574            CALL xios_add_child(group_handle, child, varname)
    570             CALL xios_set_attr(child, name=varname, unit="kg kg-1 s-1")
    571             varname='d'//trim(tname(iiq))//'_trsp'
     575            CALL xios_set_attr(child, name=varname, unit=unt)
     576            varname=TRIM(dn)//'trsp'
    572577            CALL xios_add_child(group_handle, child, varname)
    573             CALL xios_set_attr(child, name=varname, unit="kg kg-1 s-1")
    574             varname='d'//trim(tname(iiq))//'_sscav'
     578            CALL xios_set_attr(child, name=varname, unit=unt)
     579            varname=TRIM(dn)//'sscav'
    575580            CALL xios_add_child(group_handle, child, varname)
    576             CALL xios_set_attr(child, name=varname, unit="kg kg-1 s-1")
    577             varname='d'//trim(tname(iiq))//'_sat'
     581            CALL xios_set_attr(child, name=varname, unit=unt)
     582            varname=TRIM(dn)//'sat'
    578583            CALL xios_add_child(group_handle, child, varname)
    579             CALL xios_set_attr(child, name=varname, unit="kg kg-1 s-1")
    580             varname='d'//trim(tname(iiq))//'_uscav'
     584            CALL xios_set_attr(child, name=varname, unit=unt)
     585            varname=TRIM(dn)//'uscav'
    581586            CALL xios_add_child(group_handle, child, varname)
    582             CALL xios_set_attr(child, name=varname, unit="kg kg-1 s-1")
     587            CALL xios_set_attr(child, name=varname, unit=unt)
    583588          ENDDO
    584589          !On ajoute les variables 2D traceurs par l interface fortran
     
    587592          DO iq=nqo+1, nqtot
    588593            iiq=niadv(iq)
    589             varname='cum'//trim(tname(iiq))
     594
     595            unt = "kg m-2"
     596            varname='cum'//trim(tracers(iiq)%name)
    590597            WRITE (lunout,*) 'XIOS var=', iq, nqtot, varname
    591598            CALL xios_add_child(group_handle, child, varname)
    592             CALL xios_set_attr(child, name=varname, unit="kg m-2")
    593             varname='cumd'//trim(tname(iiq))//'_dry'
     599            CALL xios_set_attr(child, name=varname, unit=unt)
     600
     601            unt = "kg m-2 s-1"
     602            varname='cumd'//trim(tracers(iiq)%name)//'_dry'
    594603            CALL xios_add_child(group_handle, child, varname)
    595             CALL xios_set_attr(child, name=varname, unit="kg m-2 s-1")
     604            CALL xios_set_attr(child, name=varname, unit=unt)
    596605          ENDDO
    597606    ENDIF
Note: See TracChangeset for help on using the changeset viewer.