Ignore:
Timestamp:
Dec 6, 2022, 12:01:16 AM (22 months ago)
Author:
lguez
Message:

Sync latest trunk changes to Ocean_skin

Location:
LMDZ6/branches/Ocean_skin
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Ocean_skin

  • LMDZ6/branches/Ocean_skin/libf/phylmdiso/phys_output_mod.F90

    r3940 r4368  
    3535    USE iophy
    3636    USE dimphy
    37     USE infotrac_phy, ONLY: nqtot, nqo, niadv, tname, ttext, type_trac, &
    38         nqtottr,itr_indice ! C Risi
     37    USE infotrac_phy, ONLY: nqtot, tracers, niso, ntraciso=>ntiso
     38    USE strings_mod,  ONLY: maxlen
    3939    USE ioipsl
    4040    USE phys_cal_mod, only : hour, calend
     
    5252#endif
    5353#ifdef ISO
    54     USE infotrac_phy,ONLY: niso, ntraciso
    55     USE isotopes_mod, ONLY: striso,iso_HTO
     54    USE isotopes_mod, ONLY: isoName,iso_HTO
    5655#ifdef ISOTRAC
    5756    use isotrac_mod, only: index_zone,index_iso,strtrac
     
    6160    IMPLICIT NONE
    6261    include "clesphys.h"
    63     include "thermcell.h"
     62    include "alpale.h"
    6463    include "YOMCST.h"
    6564
     
    103102    CHARACTER(LEN=4), DIMENSION(nlevSTD)  :: clevSTD
    104103    REAL, DIMENSION(nlevSTD)              :: rlevSTD
    105     INTEGER                               :: nsrf, k, iq, iiq, iff, i, j, ilev
    106     INTEGER                               :: itr ! C Risi
     104    INTEGER                               :: nsrf, k, iq, iff, i, j, ilev, itr, ixt, iiso, izone
    107105    INTEGER                               :: naero
    108106    LOGICAL                               :: ok_veget
     
    124122
    125123#ifdef ISO
    126       INTEGER  :: ixt,iiso,izone
    127       CHARACTER*50 :: striso_sortie
    128       integer :: lnblnk
    129 #endif
     124    CHARACTER(LEN=maxlen) :: outiso
     125    CHARACTER(LEN=20) :: unit
     126#endif
     127    CHARACTER(LEN=maxlen) :: tnam, lnam, dn
     128    INTEGER :: flag(nfiles)
    130129
    131130!!!!!!!!!! stockage dans une region limitee pour chaque fichier !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    132131    !                 entre [phys_out_lonmin,phys_out_lonmax] et [phys_out_latmin,phys_out_latmax]
    133 
    134     LOGICAL, DIMENSION(nfiles), SAVE  :: phys_out_regfkey       = (/ .FALSE., .FALSE., .FALSE., .FALSE., .FALSE., &
    135                                                                      .FALSE., .FALSE., .FALSE., .FALSE., .FALSE. /)
    136     REAL, DIMENSION(nfiles), SAVE     :: phys_out_lonmin        = (/ -180., -180., -180., -180., -180., &
    137                                                                      -180., -180., -180., -180., -180. /)
    138     REAL, DIMENSION(nfiles), SAVE     :: phys_out_lonmax        = (/  180.,  180.,  180.,  180.,  180., &
    139                                                                       180.,  180.,  180.,  180.,  180. /)
    140     REAL, DIMENSION(nfiles), SAVE     :: phys_out_latmin        = (/  -90.,  -90.,  -90.,  -90.,  -90., &
    141                                                                       -90.,  -90.,  -90.,  -90.,  -90. /)
    142     REAL, DIMENSION(nfiles), SAVE     :: phys_out_latmax        = (/   90.,   90.,   90.,   90.,   90., &
    143                                                                        90.,   90.,   90.,   90.,   90. /)
     132    LOGICAL, DIMENSION(nfiles), SAVE :: &
     133      phys_out_regfkey = [.FALSE., .FALSE., .FALSE., .FALSE., .FALSE., .FALSE., .FALSE., .FALSE., .FALSE., .FALSE.]
     134    REAL,    DIMENSION(nfiles), SAVE :: &
     135      phys_out_lonmin  = [  -180.,   -180.,   -180.,   -180.,   -180.,   -180.,   -180.,   -180.,   -180.,   -180.], &
     136      phys_out_lonmax  = [   180.,    180.,    180.,    180.,    180.,    180.,    180.,    180.,    180.,    180.], &
     137      phys_out_latmin  = [   -90.,    -90.,    -90.,    -90.,    -90.,    -90.,    -90.,    -90.,    -90.,    -90.], &
     138      phys_out_latmax  = [    90.,     90.,     90.,     90.,     90.,     90.,     90.,     90.,     90.,     90.]
    144139    REAL, DIMENSION(klev,2) :: Ahyb_bounds, Bhyb_bounds
    145140    REAL, DIMENSION(klev+1)   :: lev_index
     
    399394    CALL wxios_add_vaxis("bnds", 2, (/1.,2./))
    400395
    401      CALL wxios_add_vaxis("Alt", &
     396    CALL wxios_add_vaxis("Alt", &
    402397            levmax(iff) - levmin(iff) + 1, pseudoalt)
    403398
    404     IF (NSW.EQ.6) THEN
    405 !
    406 !wl1_sun: minimum bound of wavelength (in um)
    407 !
    408       wl1_sun(1)=0.180
    409       wl1_sun(2)=0.250
    410       wl1_sun(3)=0.440
    411       wl1_sun(4)=0.690
    412       wl1_sun(5)=1.190
    413       wl1_sun(6)=2.380
    414 !
    415 !wl2_sun: maximum bound of wavelength (in um)
    416 !
    417       wl2_sun(1)=0.250
    418       wl2_sun(2)=0.440
    419       wl2_sun(3)=0.690
    420       wl2_sun(4)=1.190
    421       wl2_sun(5)=2.380
    422       wl2_sun(6)=4.000
    423 !
    424     ELSE IF(NSW.EQ.2) THEN
    425 !
    426 !wl1_sun: minimum bound of wavelength (in um)
    427 !
    428       wl1_sun(1)=0.250
    429       wl1_sun(2)=0.690
    430 !
    431 !wl2_sun: maximum bound of wavelength (in um)
    432 !
    433       wl2_sun(1)=0.690
    434       wl2_sun(2)=4.000
    435     ENDIF
     399    ! wl1_sun/wl2_sun: minimum/maximum bound of wavelength (in um)
     400    SELECT CASE(NSW)
     401      CASE(6)
     402        wl1_sun(1:6) = [0.180, 0.250, 0.440, 0.690, 1.190, 2.380]
     403        wl2_sun(1:6) = [0.250, 0.440, 0.690, 1.190, 2.380, 4.000]
     404      CASE(2)
     405        wl1_sun(1:2) = [0.250, 0.690]
     406        wl2_sun(1:2) = [0.690, 4.000]
     407    END SELECT
    436408
    437409    DO ISW=1, NSW
     
    531503     ENDIF ! clef_files
    532504
    533         write(lunout,*) 'phys_output_mid 496: nqtottr=',nqtottr
    534         write(lunout,*) 'itr_indice=',itr_indice
    535 !       IF (nqtot>=nqo+1) THEN
    536         IF (nqtottr>=1) THEN
    537 !
    538             !DO iq=nqo+1,nqtot
    539             ! C Risi: on modifie la boucle
    540             do itr=1,nqtottr ! C Risi
    541             iq=itr_indice(itr)  ! C Risi
    542             write(*,*) 'phys_output_mid 503: itr=',itr
    543  
    544             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
     505          itr = 0
     506          DO iq = 1, nqtot
     507            IF(.NOT.(tracers(iq)%isAdvected .AND. tracers(iq)%isInPhysics)) CYCLE
     508            itr = itr + 1
     509            dn = 'd'//TRIM(tracers(iq)%name)//'_'
     510
     511            flag = [1, 5, 5, 5, 10, 10, 11, 11, 11, 11]
     512            lnam = 'Tracer '//TRIM(tracers(iq)%longName)
     513            tnam = TRIM(tracers(iq)%name);  o_trac          (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
     514
     515            flag = [4, 7, 7, 7, 10, 10, 11, 11, 11, 11]
     516            lnam = 'Tendance tracer '//TRIM(tracers(iq)%longName)
     517            tnam = TRIM(dn)//'vdf';         o_dtr_vdf       (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
     518
     519            flag = [5, 7, 7, 7, 10, 10, 11, 11, 11, 11]
     520            tnam = TRIM(dn)//'the';         o_dtr_the       (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
     521            tnam = TRIM(dn)//'con';         o_dtr_con       (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
     522
     523            flag = [7, 7, 7, 7, 10, 10, 11, 11, 11, 11]
     524            tnam = TRIM(dn)//'lessi_impa';  o_dtr_lessi_impa(itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
     525            tnam = TRIM(dn)//'lessi_nucl';  o_dtr_lessi_nucl(itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
     526            tnam = TRIM(dn)//'insc';        o_dtr_insc      (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
     527            tnam = TRIM(dn)//'bcscav';      o_dtr_bcscav    (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
     528            tnam = TRIM(dn)//'evapls';      o_dtr_evapls    (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
     529            tnam = TRIM(dn)//'ls';          o_dtr_ls        (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
     530            tnam = TRIM(dn)//'trsp';        o_dtr_trsp      (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
     531            tnam = TRIM(dn)//'sscav';       o_dtr_sscav     (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
     532            tnam = TRIM(dn)//'sat';         o_dtr_sat       (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
     533            tnam = TRIM(dn)//'uscav';       o_dtr_uscav     (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
     534
     535            lnam = 'tracer tendency dry deposition'//TRIM(tracers(iq)%longName)
     536            tnam = 'cum'//TRIM(dn)//'dry';  o_dtr_dry       (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
     537
     538            flag = [1, 4, 10, 10, 10, 10, 11, 11, 11, 11]
     539            lnam = 'Cumulated tracer '//TRIM(tracers(iq)%longName)
     540            tnam = 'cum'//TRIM(tracers(iq)%name); o_trac_cum(itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
     541          ENDDO
    624542
    625543   ENDDO !  iff
    626544
    627         write(*,*) 'phys_output_mid 589'
    628545#ifdef ISO
    629   do ixt=1,ntraciso
    630      if (ixt.le.niso) then
    631         striso_sortie=striso(ixt)
    632      else
    633 #ifdef ISOTRAC
    634         iiso=index_iso(ixt)
    635         izone=index_zone(ixt)       
    636         striso_sortie=striso(iiso)//strtrac(izone)
    637 #else
    638         write(*,*) 'phys_output_mod 546: ixt,ntraciso=', ixt,ntraciso
    639         stop
    640 #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
    707 #endif
    708         write(*,*) 'phys_output_mid 596'
     546    write(*,*) 'phys_output_mid 589'
     547    do ixt=1,ntraciso
     548      outiso = TRIM(isoName(ixt))
     549      i = INDEX(outiso, '_', .TRUE.)
     550      outiso = outiso(1:i-1)//outiso(i+1:LEN_TRIM(outiso))
     551
     552      flag = [1,  1,  1, 10,  5, 10, 11, 11, 11, 11]; unit = 'kg/(s*m2)'
     553      o_xtprecip(ixt)=ctrl_out(flag, 'precip'//TRIM(outiso), 'Precip Totale liq+sol', unit, [('',i=1,nfiles)])
     554      o_xtpluc  (ixt)=ctrl_out(flag,   'pluc'//TRIM(outiso),    'Convective Precip.', unit, [('',i=1,nfiles)])
     555
     556      flag = [1,  1,  1, 10, 10, 10, 11, 11, 11, 11]
     557      o_xtplul  (ixt)=ctrl_out(flag,   'plul'//TRIM(outiso),   'Large-scale Precip.', unit, [('',i=1,nfiles)])
     558      o_xtevap  (ixt)=ctrl_out(flag,   'evap'//TRIM(outiso),             'Evaporat.', unit, [('',i=1,nfiles)])
     559
     560      flag = [2,  3,  4, 10, 10, 10, 11, 11, 11, 11]; unit = 'kg/kg'
     561      o_xtovap  (ixt)=ctrl_out(flag,   'ovap'//TRIM(outiso),     'Specific humidity', unit, [('',i=1,nfiles)])
     562      o_xtoliq  (ixt)=ctrl_out(flag,   'oliq'//TRIM(outiso),          'Liquid water', unit, [('',i=1,nfiles)])
     563      o_xtcond  (ixt)=ctrl_out(flag,  'ocond'//TRIM(outiso),       'Condensed water', unit, [('',i=1,nfiles)])
     564
     565      flag = [4, 10, 10, 10, 10, 10, 11, 11, 11, 11]; unit = '(kg/kg)/s'
     566      o_dxtdyn  (ixt)=ctrl_out(flag,  'dqdyn'//TRIM(outiso),           'Dynamics dQ', unit, [('',i=1,nfiles)])
     567      o_dxtldyn (ixt)=ctrl_out(flag, 'dqldyn'//TRIM(outiso),          'Dynamics dQL', unit, [('',i=1,nfiles)])
     568      o_dxtcon  (ixt)=ctrl_out(flag,  'dqcon'//TRIM(outiso),         'Convection dQ', unit, [('',i=1,nfiles)])
     569      o_dxteva  (ixt)=ctrl_out(flag,  'dqeva'//TRIM(outiso),      'Reevaporation dQ', unit, [('',i=1,nfiles)])
     570      o_dxtlsc  (ixt)=ctrl_out(flag,  'dqlsc'//TRIM(outiso),       'Condensation dQ', unit, [('',i=1,nfiles)])
     571      o_dxtajs  (ixt)=ctrl_out(flag,  'dqajs'//TRIM(outiso),        'Dry adjust. dQ', unit, [('',i=1,nfiles)])
     572      o_dxtvdf  (ixt)=ctrl_out(flag,  'dqvdf'//TRIM(outiso),     'Boundary-layer dQ', unit, [('',i=1,nfiles)])
     573      o_dxtthe  (ixt)=ctrl_out(flag,  'dqthe'//TRIM(outiso),            'Thermal dQ', unit, [('',i=1,nfiles)])
     574
     575      IF(ok_qch4) o_dxtch4(ixt)=ctrl_out(flag, 'dqch4'//TRIM(outiso), 'H2O due to CH4 oxidation & photolysis', &
     576                                                                                      unit, [('',i=1,nfiles)])
     577      IF(ixt == iso_HTO) THEN
     578      o_dxtprod_nucl(ixt)=ctrl_out(flag, 'dqprodnucl'//TRIM(outiso), 'dHTO/dt due to nuclear production',      &
     579                                                                                      unit, [('',i=1,nfiles)])
     580      o_dxtcosmo    (ixt)=ctrl_out(flag,    'dqcosmo'//TRIM(outiso), 'dHTO/dt due to cosmogenic production',   &
     581                                                                                      unit, [('',i=1,nfiles)])
     582      o_dxtdecroiss (ixt)=ctrl_out(flag, 'dqdecroiss'//TRIM(outiso), 'dHTO/dt due to radiative destruction',   &
     583                                                                                      unit, [('',i=1,nfiles)])
     584      END IF
     585    enddo !do ixt=1,niso
     586    write(*,*) 'phys_output_mid 596'
     587#endif
    709588
    710589
Note: See TracChangeset for help on using the changeset viewer.