Changeset 4984


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

plenty of files that I forgot to commit last time.

Location:
LMDZ6/trunk/libf
Files:
11 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/dyn3d/check_isotopes.F90

    r4399 r4984  
    2323                             iso_O17, iso_HTO
    2424   LOGICAL, SAVE :: first=.TRUE.
     25   LOGICAL, PARAMETER :: tnat1=.TRUE.
    2526
    2627   modname='check_isotopes'
     
    3435      iso_O17 = strIdx(isoName,'H217O')
    3536      iso_HTO = strIdx(isoName,'HTO')
    36       IF(getKey('tnat', tnat)) CALL abort_gcm(modname, 'missing isotopic parameter', 1)
     37      if (tnat1) then
     38              tnat(:)=1.0
     39      else
     40         IF(getKey('tnat', tnat)) CALL abort_gcm(modname, 'missing isotopic parameter', 1)
     41      endif
    3742      first = .FALSE.
    3843   END IF
  • LMDZ6/trunk/libf/dyn3d/dynetat0.F90

    r4492 r4984  
    4343  REAL    :: time, tnat, alpha_ideal, tab_cntrl(length)    !--- RUN PARAMS TABLE
    4444  LOGICAL :: lSkip, ll
     45  LOGICAL,PARAMETER :: tnat1=.TRUE.
    4546!-------------------------------------------------------------------------------
    4647  modname="dynetat0"
     
    155156      iqParent = tracers(iq)%iqParent
    156157      IF(tracers(iq)%iso_iZone == 0) THEN
    157          IF(getKey('tnat', tnat, isoName(iName)) .OR. getKey('alpha', alpha_ideal, isoName(iName))) &
     158         if (tnat1) then
     159                 tnat=1.0
     160                 alpha_ideal=1.0
     161                 write(*,*) 'attention dans dynetat0: les alpha_ideal sont a 1'
     162         else
     163          IF(getKey('tnat', tnat, isoName(iName)) .OR. getKey('alpha', alpha_ideal, isoName(iName))) &
    158164            CALL abort_gcm(TRIM(modname), 'missing isotopic parameters', 1)
     165         endif
    159166         CALL msg('Tracer <'//TRIM(var)//'> is missing => initialized with a simplified Rayleigh distillation law.', modname)
    160167         q(:,:,:,iq) = q(:,:,:,iqParent)*tnat*(q(:,:,:,iqParent)/30.e-3)**(alpha_ideal-1.)
  • LMDZ6/trunk/libf/dyn3d/iniacademic.F90

    r4419 r4984  
    8080
    8181  REAL zdtvr, tnat, alpha_ideal
     82  LOGICAL,PARAMETER :: tnat1=.true.
    8283 
    8384  character(len=*),parameter :: modname="iniacademic"
     
    321322              iqParent = tracers(iq)%iqParent
    322323              IF(tracers(iq)%iso_iZone == 0) THEN
    323                  IF(getKey('tnat', tnat, isoName(iName)) .OR. getKey('alpha', alpha_ideal, isoName(iName))) &
     324                 if (tnat1) then
     325                         tnat=1.0
     326                         alpha_ideal=1.0
     327                         write(*,*) 'Attention dans iniacademic: alpha_ideal=1'
     328                 else
     329                    IF(getKey('tnat', tnat, isoName(iName)) .OR. getKey('alpha', alpha_ideal, isoName(iName))) &
    324330                    CALL abort_gcm(TRIM(modname), 'missing isotopic parameters', 1)
     331                 endif
    325332                 q(:,:,iq) = q(:,:,iqParent)*tnat*(q(:,:,iqParent)/30.e-3)**(alpha_ideal-1.)
    326               ELSE
    327                  q(:,:,iq) = q(:,:,iqIsoPha(iName,iPhase))
    328               END IF
     333              ELSE !IF(tracers(iq)%iso_iZone == 0) THEN
     334                 IF(tracers(iq)%iso_iZone == 1) THEN
     335                    ! correction le 14 mai 2024 pour que tous les traceurs soient de la couleur 1.
     336                    ! Sinon, on va avoir des porblèmes de conservation de masse de traceurs.
     337                    q(:,:,iq) = q(:,:,iqIsoPha(iName,iPhase))
     338                 else !IF(tracers(iq)%iso_iZone == 1) THEN
     339                    q(:,:,iq) = 0.
     340                 endif !IF(tracers(iq)%iso_iZone == 1) THEN
     341              END IF !IF(tracers(iq)%iso_iZone == 0) THEN
    329342           enddo
    330343        else
  • LMDZ6/trunk/libf/dyn3d_common/infotrac.F90

    r4638 r4984  
    3636!  |--------------------+-----------------------+-----------------+---------------+----------------------------|
    3737!  | water in different |    water tagging      |  water isotopes | other tracers | additional tracers moments |
    38 !  | phases: H2O_[glsb] |      isotopes         |                 |               |  for higher order schemes  |
     38!  | phases: H2O_[gls] |      isotopes         |                 |               |  for higher order schemes  |
    3939!  |--------------------+-----------------------+-----------------+---------------+----------------------------|
    4040!  |                    |                       |                 |               |                            |
     
    6565!  | longName    | Long name (with adv. scheme suffix) for outputs      | ttext       |                        |
    6666!  | type        | Type (so far: tracer or tag)                         | /           | tracer,tag             |
    67 !  | phase       | Phases list ("g"as / "l"iquid / "s"olid / "b"lowing) | /           | [g][l][s][b]           |
     67!  | phase       | Phases list ("g"as / "l"iquid / "s"olid)             | /           | [g][l][s]              |
    6868!  | component   | Name(s) of the merged/cumulated section(s)           | /           | coma-separated names   |
    6969!  | iGeneration | Generation (>=1)                                     | /           |                        |
     
    9191!  | trac   | ntiso  | Isotopes + tagging tracers list + number         | / | ntraciso       |                 |
    9292!  | zone   | nzone  | Geographic tagging zones   list + number         | / | ntraceurs_zone |                 |
    93 !  | phase  | nphas  | Phases                     list + number         |                    |[g][l][s][b],1:4 |
     93!  | phase  | nphas  | Phases                     list + number         |                    | [g][l][s], 1:3 |
    9494!  | iqIsoPha        | Index in "qx"           = f(name(1:ntiso)),phas) | iqiso              | 1:nqtot         |
    9595!  | itZonIso        | Index in "trac(1:ntiso)"= f(zone, name(1:niso))  | index_trac         | 1:ntiso         |
     
    236236      nbtr = nqINCA + nqCO2                                          !--- Number of tracers passed to phytrac
    237237      nqtrue = nbtr + nqo                                            !--- Total number of "true" tracers
    238       IF(ALL([2,3,4,5] /= nqo)) CALL abort_gcm(modname, 'Only 2, 3, 4 , 5 water phases allowed ; found nqo='//TRIM(int2str(nqo)), 1)
     238      IF(ALL([2,3] /= nqo)) CALL abort_gcm(modname, 'Only 2 or 3 water phases allowed ; found nqo='//TRIM(int2str(nqo)), 1)
    239239      ALLOCATE(hadv(nqtrue), hadv_inca(nqINCA), conv_flg_inca(nqINCA), solsym_inca(nqINCA))
    240240      ALLOCATE(vadv(nqtrue), vadv_inca(nqINCA),  pbl_flg_inca(nqINCA))
  • LMDZ6/trunk/libf/dyn3dmem/check_isotopes_loc.F90

    r4399 r4984  
    2424                             iso_O17, iso_HTO
    2525   LOGICAL, SAVE :: first=.TRUE.
     26   LOGICAL, PARAMETER :: tnat1=.TRUE.
    2627!$OMP THREADPRIVATE(first)
    2728
     
    3738      iso_O17 = strIdx(isoName,'H217O')
    3839      iso_HTO = strIdx(isoName,'HTO')
    39       IF(getKey('tnat', tnat)) CALL abort_gcm(modname, 'missing isotopic parameter', 1)
     40      if (tnat1) then
     41              tnat(:)=1.0
     42      else
     43         IF(getKey('tnat', tnat)) CALL abort_gcm(modname, 'missing isotopic parameter', 1)
     44      endif
    4045!$OMP END MASTER
    4146!$OMP BARRIER
  • LMDZ6/trunk/libf/dyn3dmem/dynetat0_loc.F90

    r4490 r4984  
    4242  INTEGER, PARAMETER :: length=100
    4343  INTEGER :: iq, fID, vID, idecal, ierr, iqParent, iName, iZone, iPhase, ix
    44   REAL    :: time, tnat, alpha_ideal, tab_cntrl(length)    !--- RUN PARAMS TABLE
     44  REAL    :: time,tab_cntrl(length)    !--- RUN PARAMS TABLE
     45  REAL    :: tnat, alpha_ideal
    4546  REAL,             ALLOCATABLE :: vcov_glo(:,:),masse_glo(:,:),   ps_glo(:)
    4647  REAL,             ALLOCATABLE :: ucov_glo(:,:),    q_glo(:,:), phis_glo(:)
    4748  REAL,             ALLOCATABLE :: teta_glo(:,:)
    4849  LOGICAL :: lSkip, ll
     50  LOGICAL,PARAMETER :: tnat1=.TRUE.
    4951!-------------------------------------------------------------------------------
    5052  modname="dynetat0_loc"
     
    179181      iqParent = tracers(iq)%iqParent
    180182      IF(tracers(iq)%iso_iZone == 0) THEN
    181          IF(getKey('tnat', tnat, isoName(iName)) .OR. getKey('alpha', alpha_ideal, isoName(iName))) &
     183         if (tnat1) then
     184                 tnat=1.0
     185                 alpha_ideal=1.0
     186                 write(*,*) 'attention dans dynetat0: les alpha_ideal sont a 1'
     187         else
     188          IF(getKey('tnat', tnat, isoName(iName)) .OR. getKey('alpha', alpha_ideal, isoName(iName))) &
    182189            CALL abort_gcm(TRIM(modname), 'missing isotopic parameters', 1)
     190         endif
    183191         CALL msg('Tracer <'//TRIM(var)//'> is missing => initialized with a simplified Rayleigh distillation law.', modname)
    184192         q(ijb_u:ije_u,:,iq) = q(ijb_u:ije_u,:,iqParent)*tnat*(q(ijb_u:ije_u,:,iqParent)/30.e-3)**(alpha_ideal-1.)
     
    193201         ! remplacant 1 par izone_init dans la ligne qui suit.
    194202         IF(tracers(iq)%iso_iZone == 1) THEN
    195           q(ijb_u:ije_u,:,iq) = q(ijb_u:ije_u,:,iqIsoPha(iName,iPhase))
     203           q(ijb_u:ije_u,:,iq) = q(ijb_u:ije_u,:,iqIsoPha(iName,iPhase))
    196204         ELSE
    197205           q(ijb_u:ije_u,:,iq) =  0.
  • LMDZ6/trunk/libf/dyn3dmem/iniacademic_loc.F90

    r4419 r4984  
    8585
    8686  REAL zdtvr, tnat, alpha_ideal
     87  LOGICAL,PARAMETER :: tnat1=.true.
    8788 
    8889  character(len=*),parameter :: modname="iniacademic"
     
    323324              iqParent = tracers(iq)%iqParent
    324325              IF(tracers(iq)%iso_iZone == 0) THEN
    325                  IF(getKey('tnat', tnat, isoName(iName)) .OR. getKey('alpha', alpha_ideal, isoName(iName))) &
     326                 if (tnat1) then
     327                         tnat=1.0
     328                         alpha_ideal=1.0
     329                         write(*,*) 'Attention dans iniacademic: alpha_ideal=1'
     330                 else
     331                    IF(getKey('tnat', tnat, isoName(iName)) .OR. getKey('alpha', alpha_ideal, isoName(iName))) &
    326332                    CALL abort_gcm(TRIM(modname), 'missing isotopic parameters', 1)
     333                 endif
    327334                 q(ijb_u:ije_u,:,iq) = q(ijb_u:ije_u,:,iqParent)*tnat*(q(ijb_u:ije_u,:,iqParent)/30.e-3)**(alpha_ideal-1.)
    328               ELSE
    329                  q(ijb_u:ije_u,:,iq) = q(ijb_u:ije_u,:,iqIsoPha(iName,iPhase))
    330               END IF
     335              ELSE !IF(tracers(iq)%iso_iZone == 0) THEN
     336                 IF(tracers(iq)%iso_iZone == 1) THEN ! a verifier.
     337                    ! correction le 14 mai 2024 pour que tous les traceurs soient de la couleur 1.
     338                    ! Sinon, on va avoir des porblèmes de conservation de masse de traceurs.
     339                    q(ijb_u:ije_u,:,iq) = q(ijb_u:ije_u,:,iqIsoPha(iName,iPhase))
     340                 else !IF(tracers(iq)%iso_iZone == 1) THEN
     341                    q(ijb_u:ije_u,:,iq) = 0.0
     342                 endif !IF(tracers(iq)%iso_iZone == 1) THEN
     343              END IF !IF(tracers(iq)%iso_iZone == 0) THEN
    331344           enddo
    332345        else
  • LMDZ6/trunk/libf/misc/readTracFiles_mod.f90

    r4523 r4984  
    3636  PUBLIC :: itZonIso                                            !--- Idx IN isoName(1:niso) = f(tagging idx, isotope idx)
    3737  PUBLIC :: iqIsoPha                                            !--- Idx IN qx(1:nqtot)     = f(isotope idx,   phase idx)
     38  PUBLIC :: iqWIsoPha                                           !--- Idx IN qx(1:nqtot)     = f(isotope idx,   phase idx) but with normal water first
    3839  PUBLIC :: isoCheck                                            !--- FLAG TO RUN ISOTOPES CHECKING ROUTINES
    3940
     
    8283    INTEGER,               ALLOCATABLE :: iqIsoPha(:,:)    !--- Idx in "tracers(1:nqtot)" = f(name(1:ntiso)),phas)
    8384                                                           !---        "iqIsoPha" former name: "iqiso"
     85    INTEGER,               ALLOCATABLE :: iqWIsoPha(:,:)   !--- Idx in "tracers(1:nqtot)" = f(name(1:ntiso)),phas)
     86                                                           !---        "iqIsoPha" former name: "iqiso"
    8487    INTEGER,               ALLOCATABLE :: itZonIso(:,:)    !--- Idx in "trac(1:ntiso)" = f(zone, name(1:niso))
    8588                                                           !---        "itZonIso" former name: "index_trac"
     
    148151                                            nphas, ntiso        !--- NUMBER OF PHASES AND ISOTOPES + ISOTOPIC TAGGING TRACERS
    149152  INTEGER,                 SAVE, POINTER ::itZonIso(:,:), &     !--- INDEX IN "isoTrac" AS f(tagging zone idx,  isotope idx)
    150                                            iqIsoPha(:,:)        !--- INDEX IN "qx"      AS f(isotopic tracer idx, phase idx)
     153                                           iqIsoPha(:,:), &        !--- INDEX IN "qx"      AS f(isotopic tracer idx, phase idx)
     154                                           iqWIsoPha(:,:)       !--- INDEX IN "qx"      AS f(isotopic tracer idx, phase idx)
    151155
    152156  INTEGER,    PARAMETER :: maxTableWidth = 192                  !--- Maximum width of a table displayed with "dispTable"
     
    12051209    i%iqIsoPha = RESHAPE( [( (strIdx(t%name,  addPhase(i%trac(it),i%phase(ip:ip))),       it=1, i%ntiso), ip=1, i%nphas)], &
    12061210                         [i%ntiso, i%nphas] )
     1211    !=== Table used to get iq (index in dyn array, size nqtot) from the water and isotope and phase indexes ; the full isotopes list
     1212    !    (including tagging tracers) is sorted this way:  iso1, iso2, ..., iso1_zone1, iso2_zone1, ..., iso1_zoneN, iso2_zoneN
     1213    i%iqWIsoPha = RESHAPE( [( [strIdx(t%name,   addPhase('H2O',i%phase(ip:ip))), i%iqIsoPha(:,ip)], ip=1,i%nphas)], &
     1214                         [1+i%ntiso, i%nphas] )
    12071215    !=== Table used to get ix (index in tagging tracers isotopes list, size ntiso) from the zone and isotope indexes
    12081216    i%itZonIso = RESHAPE( [( (strIdx(i%trac(:), TRIM(i%trac(it))//'_'//TRIM(i%zone(iz))), iz=1, i%nzone), it=1, i%niso )], &
     
    12111219
    12121220  !=== READ PHYSICAL PARAMETERS FROM isoFile FILE
    1213   IF(test(readIsotopesFile_prv(isoFile, isotopes), lerr)) RETURN
     1221!  IF(test(readIsotopesFile_prv(isoFile, isotopes), lerr)) RETURN! on commente pour ne pas chercher isotopes_params.def
    12141222
    12151223  !=== CHECK CONSISTENCY
     
    12871295   itZonIso => isotope%itZonIso; isoCheck = isotope%check
    12881296   iqIsoPha => isotope%iqIsoPha
     1297   iqWIsoPha => isotope%iqWIsoPha
    12891298END FUNCTION isoSelectByIndex
    12901299!==============================================================================================================================
  • 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.