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

plenty of files that I forgot to commit last time.

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

Legend:

Unmodified
Added
Removed
  • 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
Note: See TracChangeset for help on using the changeset viewer.