Ignore:
Timestamp:
Jun 15, 2024, 6:26:24 PM (2 weeks ago)
Author:
crisi
Message:

plenty of files that I forgot to commit last time.

Location:
LMDZ6/trunk/libf/phylmd
Files:
3 edited

Legend:

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

    r4638 r4984  
    55   USE       strings_mod, ONLY: msg, fmsg, maxlen, cat, dispTable, int2str, bool2str, strStack, strParse, strIdx
    66   USE readTracFiles_mod, ONLY: trac_type, readTracersFiles, tracers, setGeneration, itZonIso, nzone, tran0, isoZone, &
    7         delPhase, niso, getKey, isot_type, readIsotopesFile, isotope, maxTableWidth, iqIsoPha, nphas, ixIso, isoPhas, &
    8         addPhase, iH2O, addKey, isoSelect, testTracersFiles, isoKeys, indexUpdate,   isoCheck, nbIso, ntiso, isoName
     7        delPhase, niso, getKey, isot_type, readIsotopesFile, isotope, maxTableWidth, iqIsoPha, iqWIsoPha, nphas, ixIso, &
     8        isoPhas, addPhase, iH2O, addKey, isoSelect, testTracersFiles, isoKeys, indexUpdate,   isoCheck, nbIso, ntiso, isoName
    99   IMPLICIT NONE
    1010
     
    2020   PUBLIC :: id_OCS_strat, id_SO2_strat, id_H2SO4_strat, id_BIN01_strat, id_TEST_strat
    2121#endif
    22 #ifdef REPROBUS
    23    PUBLIC :: nbtr_bin, nbtr_sulgas
    24    PUBLIC :: id_OCS_strat, id_SO2_strat, id_H2SO4_strat, id_BIN01_strat, &
    25              id_TEST_strat
    26 #endif
    27 
     22
     23   !=== FOR WATER
     24   PUBLIC :: ivap, iliq, isol
    2825   !=== FOR ISOTOPES: General
    2926   PUBLIC :: isot_type, nbIso                              !--- Derived type, full isotopes families database + nb of families
     
    3734   PUBLIC :: itZonIso                                      !--- idx "it" (in "isoName(1:niso)") = function(tagging idx, isotope idx)
    3835   PUBLIC :: iqIsoPha                                      !--- idx "iq" (in "qx") = function(isotope idx, phase idx) + aliases
     36   PUBLIC :: iqWIsoPha                                      !--- Same as iqIsoPha but with normal water phases
     37
    3938   PUBLIC :: isoCheck                                      !--- Run isotopes checking routines
    4039   !=== FOR BOTH TRACERS AND ISOTOPES
     
    7372!  | longName    | Long name (with adv. scheme suffix) for outputs      | ttext       |                        |
    7473!  | type        | Type (so far: tracer or tag)                         | /           | tracer,tag             |
    75 !  | phase       | Phases list ("g"as / "l"iquid / "s"olid / "b"lowing) | /           | [g][l][s][b]           |
     74!  | phase       | Phases list ("g"as / "l"iquid / "s"olid)             | /           | [g][l][s]              |
    7675!  | component   | Name(s) of the merged/cumulated section(s)           | /           | coma-separated names   |
    7776!  | iGeneration | Generation (>=1)                                     | /           |                        |
     
    9897!  | trac   | ntiso  | Isotopes + tagging tracers list + number         | / | ntraciso       |                 |
    9998!  | zone   | nzone  | Geographic tagging zones   list + number         | / | ntraceurs_zone |                 |
    100 !  | phase  | nphas  | Phases                     list + number         |                    |[g][l][s][b] 1:4 |
     99!  | phase  | nphas  | Phases                     list + number         |                    | [g][l][s], 1:3 |
    101100!  | iqIsoPha        | Index in "qx"           = f(name(1:ntiso)),phas) | iqiso              | 1:nqtot         |
     101!  | iqWIsoPha       | Index in "qx"           = f(name(1:ntiso)),phas) | iqiso              | 1:nqtot         |
    102102!  | itZonIso        | Index in "trac(1:ntiso)"= f(zone, name(1:niso))  | index_trac         | 1:ntiso         |
    103103!  +-----------------+--------------------------------------------------+--------------------+-----------------+
     
    112112!$OMP THREADPRIVATE(nqtot, nbtr, nqo, nqtottr, nqCO2, type_trac)
    113113
     114   !=== INDICES OF WATER
     115   INTEGER,               SAVE :: ivap,iliq,isol ! Indices for vap, liq and ice
     116!$OMP THREADPRIVATE(ivap,iliq,isol)
     117
    114118   !=== VARIABLES FOR INCA
    115119   INTEGER,               SAVE, ALLOCATABLE :: conv_flg(:), &   !--- Convection     activation ; needed for INCA        (nbtr)
     
    123127  INTEGER, SAVE ::  id_OCS_strat, id_SO2_strat, id_H2SO4_strat, id_BIN01_strat, id_TEST_strat
    124128!$OMP THREADPRIVATE(id_OCS_strat, id_SO2_strat, id_H2SO4_strat, id_BIN01_strat, id_TEST_strat)
    125 #endif
    126 #ifdef REPROBUS
    127   INTEGER, SAVE ::  nbtr_bin, nbtr_sulgas
    128 !$OMP THREADPRIVATE(nbtr_bin, nbtr_sulgas)
    129   INTEGER, SAVE ::  id_OCS_strat, id_SO2_strat, id_H2SO4_strat, id_BIN01_strat,&
    130                     id_TEST_strat
    131 !$OMP THREADPRIVATE(id_OCS_strat, id_SO2_strat, id_H2SO4_strat, id_BIN01_strat)
    132 !$OMP THREADPRIVATE(id_TEST_strat)
    133129#endif
    134130
  • LMDZ6/trunk/libf/phylmd/phys_output_write_mod.F90

    r4887 r4984  
    12941294
    12951295       ENDDO
    1296        
    1297                
     1296
     1297
    12981298        IF (iflag_pbl > 1) THEN
    12991299          zx_tmp_fi3d=0.
     
    27842784
    27852785#ifdef ISO
     2786    !write(*,*) 'tmp phys_output_write: ntiso=',ntiso
    27862787    do ixt=1,ntiso
    2787 !        write(*,*) 'ixt'
     2788        !write(*,*) 'ixt,o_xtovap(ixt)=',ixt,o_xtovap(ixt)
    27882789        IF (vars_defined) zx_tmp_fi2d(:) = xtrain_fall(ixt,:) + xtsnow_fall(ixt,:)
    27892790        CALL histwrite_phy(o_xtprecip(ixt), zx_tmp_fi2d)
  • LMDZ6/trunk/libf/phylmd/phys_state_var_mod.F90

    r4976 r4984  
    8787!$OMP THREADPRIVATE(prw_ancien, prlw_ancien, prsw_ancien, prbsw_ancien)
    8888#ifdef ISO
    89       REAL, ALLOCATABLE, SAVE :: xt_ancien(:,:,:),xtl_ancien(:,:,:),xts_ancien(:,:,:)
    90 !$OMP THREADPRIVATE(xt_ancien,xtl_ancien,xts_ancien)
     89      REAL, ALLOCATABLE, SAVE :: xt_ancien(:,:,:),xtl_ancien(:,:,:),xts_ancien(:,:,:), &
     90              xtbs_ancien(:,:,:)
     91!$OMP THREADPRIVATE(xt_ancien,xtl_ancien,xts_ancien,xtbs_ancien)
    9192#endif
    9293      REAL, ALLOCATABLE, SAVE :: u_ancien(:,:), v_ancien(:,:)
     
    760761      ALLOCATE(xtl_ancien(ntraciso,klon,klev))
    761762      ALLOCATE(xts_ancien(ntraciso,klon,klev))
     763      ALLOCATE(xtbs_ancien(ntraciso,klon,klev))
    762764      ALLOCATE(xtrain_fall(ntraciso,klon))
    763765      ALLOCATE(xtsnow_fall(ntraciso,klon))
     
    949951#ifdef ISO   
    950952      DEALLOCATE(xtsol,fxtevap) 
    951       DEALLOCATE(xt_ancien,xtl_ancien,xts_ancien, fxtd, wake_deltaxt)
     953      DEALLOCATE(xt_ancien,xtl_ancien,xts_ancien,xtbs_ancien, fxtd, wake_deltaxt)
    952954      DEALLOCATE(xtrain_fall, xtsnow_fall, xtrain_con, xtsnow_con)
    953955#ifdef ISOTRAC
Note: See TracChangeset for help on using the changeset viewer.