Changeset 3991 for LMDZ6/branches


Ignore:
Timestamp:
Oct 13, 2021, 4:51:21 PM (3 years ago)
Author:
dcugnet
Message:
  • fixed a bug in dynetat0[_loc].F90 for old style tracers description files having more water tracers than the initial state file.
  • changes (mainly cosmetic) to make dynetat0 and dynetat0_loc more similar.
  • fix a bug in readTracFiles_mod for tagging tracers.
Location:
LMDZ6/branches/LMDZ-tracers/libf
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/LMDZ-tracers/libf/dyn3d/dynetat0.F90

    r3957 r3991  
    66! Purpose: Initial state reading.
    77!-------------------------------------------------------------------------------
    8   USE readTracFiles_mod, ONLY: known_phases, old_phases, nphases, phases_sep
    98  USE infotrac,    ONLY: nqtot, niso, tracers, iTraPha, tnat, alpha_ideal, tra
    109  USE netcdf,      ONLY: NF90_OPEN,  NF90_NOWRITE, NF90_INQ_VARID, NF90_NoErr, &
    1110                         NF90_CLOSE, NF90_GET_VAR
    12   USE strings_mod, ONLY: strIdx
    1311  USE control_mod, ONLY: planet_type
    1412  USE assert_eq_m, ONLY: assert_eq
     
    1917  USE temps_mod, ONLY: annee_ref, day_ini, day_ref, itau_dyn, start_time
    2018  USE ener_mod,  ONLY: etot0, ptot0, ztot0, stot0, ang0
     19  USE strings_mod, ONLY: strIdx
     20  USE readTracFiles_mod, ONLY: known_phases, old_phases, nphases, phases_sep
    2121
    2222  IMPLICIT NONE
     
    120120  END IF
    121121  CALL err(NF90_GET_VAR(fID,vID,time),"get",var)
    122   CALL get_var2("phisinit", phis)
     122  CALL get_var3("vcov",     vcov)
    123123  CALL get_var3("ucov",     ucov)
    124   CALL get_var3("vcov",     vcov)
    125124  CALL get_var3("teta",     teta)
    126125  CALL get_var3("masse",   masse)
     126  CALL get_var2("phisinit", phis)
    127127  CALL get_var2("ps",         ps)
    128128
     
    132132    var = tr%name
    133133    ix = strIdx([('H2O'//phases_sep//known_phases(ip:ip), ip=1, nphases)], var)
    134     IF(NF90_INQ_VARID(fID, var, vID) == NF90_NoErr) THEN
     134    oldH2O = '***'; IF(ix/=0) oldH2O = 'H2O'//old_phases(ix:ix)
     135    !------------------------------------------------------------------------------------------------------------------
     136    IF(NF90_INQ_VARID(fID, var, vID) == NF90_NoErr) THEN                                 !=== REGULAR CASE
    135137      CALL get_var3(var, q(:,:,:,iq))
     138    !------------------------------------------------------------------------------------------------------------------
    136139#ifdef INCA
    137     ELSE IF(NF90_INQ_VARID(fID, 'OX', vID) == NF90_NoErr .AND. var == 'O3') THEN
     140    ELSE IF(NF90_INQ_VARID(fID, 'OX',   vID) == NF90_NoErr .AND. var == 'O3') THEN       !=== INCA: OX INSTEAD OF O3
    138141      WRITE(lunout,*)TRIM(modname)//': Tracer <O3> is missing => initialized to OX'
    139142      CALL get_var3('OX', q(:,:,:,iq))
    140143#endif
    141     ELSE IF(ix /= 0) THEN              !--- Old file, water: H2Ov/l/i instead of H2O_g/_l/_s
    142       oldH2O = 'H2O'//old_phases(ix:ix)
    143       IF(NF90_INQ_VARID(fID, oldH2O, vID) == NF90_NoErr) THEN
    144         WRITE(lunout,*)TRIM(modname)//': Tracer <'//TRIM(var)//'> is missing => initialized to '//TRIM(oldH2O)
    145         CALL get_var3(oldH2O, q(:,:,:,iq))
     144    !------------------------------------------------------------------------------------------------------------------
     145    ELSE IF(NF90_INQ_VARID(fID, oldH2O, vID) == NF90_NoErr .AND. ix  /= 0   ) THEN       !=== OLD WATER PHASES
     146      WRITE(lunout,*)TRIM(modname)//': Tracer <'//TRIM(var)//'> is missing => initialized to '//TRIM(oldH2O)
     147      CALL get_var3(oldH2O, q(:,:,:,iq))
     148    !------------------------------------------------------------------------------------------------------------------
     149    ELSE IF(niso > 0 .AND. tr%iso_num > 0) THEN                                          !=== ISOTOPES, CRisi
     150      IF(tr%iso_zon == 0) THEN
     151        WRITE(lunout,*)TRIM(modname)//': Isotope <'//TRIM(var)//'> is missing => initialized with a' &
     152          //' simplified Rayleigh distillation law'
     153        q(:,:,:,iq) = q(:,:,:,tr%iprnt)         *        tnat(tr%iso_num) &
     154                  *(q(:,:,:,tr%iprnt)/30.e-3)**(alpha_ideal(tr%iso_num)-1)
     155      ELSE
     156        WRITE(lunout,*)TRIM(modname)//': Isotope geographical tracer <'//TRIM(var)//'> is missing '  &
     157          //'=> initialized its parent isotope concentration'
     158        q(:,:,:,iq) = q(:,:,:,iTraPha(tr%iso_num,tr%iso_pha))
    146159      END IF
    147     ELSE
     160    !------------------------------------------------------------------------------------------------------------------
     161    ELSE                                                                                 !=== MISSING: SET TO 0
    148162      WRITE(lunout,*)TRIM(modname)//': Tracer <'//TRIM(var)//'> is missing => initialized to zero'
    149163      q(:,:,:,iq)=0.
    150       !--- CRisi: for isotopes, theoretical initialization using very simplified Rayleigh distillation law
    151       IF(niso > 0 .AND. tr%iso_num > 0) THEN
    152         IF(tr%iso_zon == 0) q(:,:,:,iq) = q(:,:,:,tr%iprnt)         *        tnat(tr%iso_num)  &
    153                                         *(q(:,:,:,tr%iprnt)/30.e-3)**(alpha_ideal(tr%iso_num)-1)
    154         IF(tr%iso_zon == 1) q(:,:,:,iq) = q(:,:,:,iTraPha(tr%iso_num,tr%iso_pha))
    155       END IF
    156164    END IF
     165    !------------------------------------------------------------------------------------------------------------------
    157166  END DO
    158167  CALL err(NF90_CLOSE(fID),"close",fichnom)
  • LMDZ6/branches/LMDZ-tracers/libf/dyn3dmem/dynetat0_loc.F90

    r3985 r3991  
    1414  USE assert_eq_m, ONLY: assert_eq
    1515  USE comvert_mod, ONLY: pa,preff
    16   USE comconst_mod, ONLY: cpp, daysec, dtvr, g, im, jm, kappa, lllm, &
    17                           omeg, rad
     16  USE comconst_mod, ONLY: cpp, daysec, dtvr, g, im, jm, kappa, lllm, omeg, rad
    1817  USE logic_mod, ONLY: fxyhypb, ysinus
    1918  USE serre_mod, ONLY: clon, clat, grossismx, grossismy
    20   USE temps_mod, ONLY: annee_ref,day_ref,itau_dyn, &
    21                        start_time,day_ini
    22   USE ener_mod, ONLY: etot0,ptot0,ztot0,stot0,ang0
     19  USE temps_mod, ONLY: annee_ref, day_ini, day_ref, itau_dyn, start_time
     20  USE ener_mod,  ONLY: etot0, ptot0, ztot0, stot0, ang0
    2321  USE strings_mod, ONLY: strIdx
    2422  USE readTracFiles_mod, ONLY: known_phases, old_phases, nphases, phases_sep
     
    139137    var = tr%name
    140138    ix = strIdx([('H2O'//phases_sep//known_phases(ip:ip), ip=1, nphases)], var)
    141     IF(NF90_INQ_VARID(fID, var, vID) == NF90_NoErr) THEN
     139    oldH2O = '***'; IF(ix/=0) oldH2O = 'H2O'//old_phases(ix:ix)
     140    !------------------------------------------------------------------------------------------------------------------
     141    IF(NF90_INQ_VARID(fID, var, vID) == NF90_NoErr) THEN                                 !=== REGULAR CASE
    142142      CALL get_var2(var, q(ib:ie,:,iq), ib, ie, nglo)
     143    !------------------------------------------------------------------------------------------------------------------
    143144#ifdef INCA
    144     ELSE IF(NF90_INQ_VARID(fID, 'OX', vID) == NF90_NoErr .AND. var == 'O3') THEN
     145    ELSE IF(NF90_INQ_VARID(fID, 'OX',   vID) == NF90_NoErr .AND. var == 'O3') THEN       !=== INCA: OX INSTEAD OF O3
    145146      WRITE(lunout,*)TRIM(modname)//': Tracer <O3> is missing => initialized to OX'
    146147      CALL get_var2('OX', q(ib:ie,:,iq), ib, ie, nglo)
    147148#endif
    148     ELSE IF(ix /= 0) THEN              !--- Old file, water: H2Ov/l/i instead of H2O-g/-l/-s
    149       oldH2O = 'H2O'//old_phases(ix:ix)
    150       IF(NF90_INQ_VARID(fID, oldH2O, vID) == NF90_NoErr) THEN
    151         WRITE(lunout,*)TRIM(modname)//': Tracer <'//TRIM(var)//'> is missing => initialized to '//TRIM(oldH2O)
    152         CALL get_var2(oldH2O, q(ib:ie,:,iq), ib, ie, nglo)
     149    !------------------------------------------------------------------------------------------------------------------
     150    ELSE IF(NF90_INQ_VARID(fID, oldH2O, vID) == NF90_NoErr .AND. ix  /= 0   ) THEN       !=== OLD WATER PHASES
     151      WRITE(lunout,*)TRIM(modname)//': Tracer <'//TRIM(var)//'> is missing => initialized to '//TRIM(oldH2O)
     152      CALL get_var2(oldH2O, q(ib:ie,:,iq), ib, ie, nglo)
     153    !------------------------------------------------------------------------------------------------------------------
     154    ELSE IF(niso > 0 .AND. tr%iso_num > 0) THEN                                          !=== ISOTOPES, CRisi
     155      IF(tr%iso_zon == 0) THEN
     156        WRITE(lunout,*)TRIM(modname)//': Isotope <'//TRIM(var)//'> is missing => initialized with a' &
     157          //' simplified Rayleigh distillation law'
     158        q(:,:,iq) = q(:,:,tr%iprnt)         *        tnat(tr%iso_num) &
     159                  *(q(:,:,tr%iprnt)/30.e-3)**(alpha_ideal(tr%iso_num)-1)
     160      ELSE
     161        WRITE(lunout,*)TRIM(modname)//': Isotope geographical tracer <'//TRIM(var)//'> is missing '  &
     162          //'=> initialized its parent isotope concentration'
     163        q(:,:,iq) = q(:,:,iTraPha(tr%iso_num,tr%iso_pha))
    153164      END IF
    154     ELSE
     165    !------------------------------------------------------------------------------------------------------------------
     166    ELSE                                                                                 !=== MISSING: SET TO 0
    155167      WRITE(lunout,*)TRIM(modname)//': Tracer <'//TRIM(var)//'> is missing => initialized to zero'
    156168      q(ib:ie,:,iq)=0.
    157       !--- CRisi: for isotopes, theoretical initialization using very simplified Rayleigh distillation law
    158       IF(niso > 0 .AND. tr%iso_num > 0) THEN
    159         IF(tr%iso_zon == 0) q(:,:,iq) = q(:,:,tr%iprnt)         *        tnat(tr%iso_num) &
    160                                       *(q(:,:,tr%iprnt)/30.e-3)**(alpha_ideal(tr%iso_num)-1)
    161         IF(tr%iso_zon == 1) q(:,:,iq) = q(:,:,iTraPha(tr%iso_num,tr%iso_pha))
    162       END IF
    163169    END IF
     170    !------------------------------------------------------------------------------------------------------------------
    164171  END DO
    165172  CALL err(NF90_CLOSE(fID),"close",fichnom)
  • LMDZ6/branches/LMDZ-tracers/libf/misc/readTracFiles_mod.f90

    r3985 r3991  
    927927    !=== Geographic tagging tracers descending on tracer "iname": mask, names, number
    928928    ll = t(:)%type=='tag'    .AND. delPhase(t(:)%nam1) == iname .AND. t(:)%igen == 3
    929     s%zone = PACK(strTail(t(:)%name,'_'), MASK = ll)                 !--- Tagging zones names  for isotopes category "iname"
     929    s%zone = PACK(strTail(t(:)%name,'_',lFirst=.TRUE.), MASK = ll)   !--- Tagging zones names  for isotopes category "iname"
    930930    CALL strReduce(s%zone)
    931931    s%nzon = SIZE(s%zone)                                            !--- Tagging zones number for isotopes category "iname"
Note: See TracChangeset for help on using the changeset viewer.