Changeset 4325 for LMDZ6/trunk/libf/dyn3d
- Timestamp:
- Nov 7, 2022, 3:09:43 AM (2 years ago)
- Location:
- LMDZ6/trunk/libf/dyn3d
- Files:
-
- 6 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ6/trunk/libf/dyn3d/check_isotopes.F90
r4143 r4325 2 2 USE strings_mod, ONLY: maxlen, msg, strIdx, strStack, int2str, real2str 3 3 USE infotrac, ONLY: nqtot, niso, nphas, isotope, isoCheck, iqIsoPha, isoSelect, & 4 ntiso, iH2O, nzone, tracers, isoName, itZonIso, tnat4 ntiso, iH2O, nzone, tracers, isoName, itZonIso, getKey 5 5 IMPLICIT NONE 6 6 include "dimensions.h" … … 10 10 CHARACTER(LEN=maxlen) :: modname, msg1, nm(2) 11 11 INTEGER :: ixt, ipha, k, i, iq, iiso, izon, ieau, iqeau, iqpar 12 INTEGER, ALLOCATABLE :: ix(:) 12 INTEGER, ALLOCATABLE :: ix(:) 13 REAL, ALLOCATABLE :: tnat(:) 13 14 REAL :: xtractot, xiiso, deltaD, q1, q2 14 15 REAL, PARAMETER :: borne = 1e19, & … … 33 34 iso_O17 = strIdx(isoName,'H2[17]O') 34 35 iso_HTO = strIdx(isoName,'H[3]HO') 36 IF(getKey('tnat', tnat)) CALL abort_gcm(modname, 'missing isotopic parameter', 1) 35 37 first = .FALSE. 36 38 END IF -
LMDZ6/trunk/libf/dyn3d/dynetat0.F90
r4301 r4325 6 6 ! Purpose: Initial state reading. 7 7 !------------------------------------------------------------------------------- 8 USE infotrac, ONLY: nqtot, tracers, niso, iqIsoPha, tnat, alpha_ideal, iH2O8 USE infotrac, ONLY: nqtot, tracers, niso, iqIsoPha, iH2O, isoName 9 9 USE strings_mod, ONLY: maxlen, msg, strStack, real2str, int2str 10 10 USE netcdf, ONLY: NF90_OPEN, NF90_NOWRITE, NF90_INQ_VARID, & 11 11 NF90_CLOSE, NF90_GET_VAR, NF90_NoErr 12 USE readTracFiles_mod, ONLY: new2oldH2O, newHNO3, oldHNO3 12 USE readTracFiles_mod, ONLY: new2oldH2O, newHNO3, oldHNO3, getKey 13 13 USE control_mod, ONLY: planet_type 14 14 USE assert_eq_m, ONLY: assert_eq … … 41 41 INTEGER, PARAMETER :: length=100 42 42 INTEGER :: iq, fID, vID, idecal, iqParent, iName, iZone, iPhase 43 REAL :: time, t ab_cntrl(length)!--- RUN PARAMS TABLE43 REAL :: time, tnat, alpha_ideal, tab_cntrl(length) !--- RUN PARAMS TABLE 44 44 LOGICAL :: lSkip, ll 45 45 !------------------------------------------------------------------------------- … … 155 155 iqParent = tracers(iq)%iqParent 156 156 IF(tracers(iq)%iso_iZone == 0) THEN 157 IF(getKey('tnat', tnat, isoName(iName)) .OR. getKey('alpha', alpha_ideal, isoName(iName))) & 158 CALL abort_gcm(TRIM(modname), 'missing isotopic parameters', 1) 157 159 CALL msg('Tracer <'//TRIM(var)//'> is missing => initialized with a simplified Rayleigh distillation law.', modname) 158 q(:,:,:,iq) = q(:,:,:,iqParent)*tnat (iName)*(q(:,:,:,iqParent)/30.e-3)**(alpha_ideal(iName)-1.)160 q(:,:,:,iq) = q(:,:,:,iqParent)*tnat*(q(:,:,:,iqParent)/30.e-3)**(alpha_ideal-1.) 159 161 ELSE 160 162 CALL msg('Tracer <'//TRIM(var)//'> is missing => initialized to its parent isotope concentration.', modname) -
LMDZ6/trunk/libf/dyn3d/gcm.F90
r3579 r4325 20 20 21 21 USE filtreg_mod 22 USE infotrac 22 USE infotrac, ONLY: nqtot, init_infotrac 23 23 USE control_mod 24 24 USE mod_const_mpi, ONLY: COMM_LMDZ … … 205 205 ! Choix du nombre de traceurs et du schema pour l'advection 206 206 ! dans fichier traceur.def, par default ou via INCA 207 call in fotrac_init207 call init_infotrac 208 208 209 209 ! Allocation de la tableau q : champs advectes -
LMDZ6/trunk/libf/dyn3d/iniacademic.F90
r4143 r4325 5 5 6 6 USE filtreg_mod, ONLY: inifilr 7 USE infotrac, ONLY: nqtot, niso, tnat, alpha_ideal, iqIsoPha, tracers7 USE infotrac, ONLY: nqtot, niso, iqIsoPha, tracers, getKey, isoName 8 8 USE control_mod, ONLY: day_step,planet_type 9 9 use exner_hyb_m, only: exner_hyb … … 73 73 integer idum 74 74 75 REAL zdtvr 75 REAL zdtvr, tnat, alpha_ideal 76 76 77 77 character(len=*),parameter :: modname="iniacademic" … … 286 286 iqParent = tracers(iq)%iqParent 287 287 IF(tracers(iq)%iso_iZone == 0) THEN 288 q(:,:,iq) = q(:,:,iqParent)*tnat(iName)*(q(:,:,iqParent)/30.e-3)**(alpha_ideal(iName)-1.) 288 IF(getKey('tnat', tnat, isoName(iName)) .OR. getKey('alpha', alpha_ideal, isoName(iName))) & 289 CALL abort_gcm(TRIM(modname), 'missing isotopic parameters', 1) 290 q(:,:,iq) = q(:,:,iqParent)*tnat*(q(:,:,iqParent)/30.e-3)**(alpha_ideal-1.) 289 291 ELSE 290 292 q(:,:,iq) = q(:,:,iqIsoPha(iName,iPhase)) -
LMDZ6/trunk/libf/dyn3d/vlsplt.F
r4143 r4325 437 437 enddo 438 438 enddo 439 do ifils=1,tracers(iq)%nqChild s439 do ifils=1,tracers(iq)%nqChildren 440 440 iq2=tracers(iq)%iqDescen(ifils) 441 441 call vlx(Ratio,pente_max,masseq,u_mq,iq2) … … 969 969 ! CRisi: appel récursif de l'advection sur les fils. 970 970 ! Il faut faire ça avant d'avoir mis à jour q et masse 971 !write(*,*) 'vlsplt 942: iq,nqChild s(iq)=',iq,nqChilds(iq)971 !write(*,*) 'vlsplt 942: iq,nqChildren(iq)=',iq,nqChildren(iq) 972 972 do ifils=1,tracers(iq)%nqDescen 973 973 iq2=tracers(iq)%iqDescen(ifils) … … 987 987 enddo 988 988 989 do ifils=1,tracers(iq)%nqChild s989 do ifils=1,tracers(iq)%nqChildren 990 990 iq2=tracers(iq)%iqDescen(ifils) 991 991 call vlz(Ratio,pente_max,masseq,wq,iq2) -
LMDZ6/trunk/libf/dyn3d/vlspltqs.F
r4052 r4325 479 479 ! CRisi: appel récursif de l'advection sur les fils. 480 480 ! Il faut faire ça avant d'avoir mis à jour q et masse 481 !write(*,*) 'vlspltqs 326: iq,nqChilds(iq)=',iq,tracers(iq)%nqChilds 481 !write(*,*) 'vlspltqs 326: iq,nqChildren(iq)=',iq, 482 ! & tracers(iq)%nqChildren 482 483 483 484 do ifils=1,tracers(iq)%nqDescen … … 491 492 enddo 492 493 enddo 493 do ifils=1,tracers(iq)%nqChild s494 do ifils=1,tracers(iq)%nqChildren 494 495 iq2=tracers(iq)%iqDescen(ifils) 495 496 call vlx(Ratio,pente_max,masseq,u_mq,iq2) … … 786 787 ! CRisi: appel récursif de l'advection sur les fils. 787 788 ! Il faut faire ça avant d'avoir mis à jour q et masse 788 !write(*,*) 'vlyqs 689: iq,nqChilds(iq)=',iq,tracers(iq)%nqChilds 789 !write(*,*) 'vlyqs 689: iq,nqChildren(iq)=',iq, 790 ! & tracers(iq)%nqChildren 789 791 790 792 do ifils=1,tracers(iq)%nqDescen … … 797 799 enddo 798 800 enddo 799 do ifils=1,tracers(iq)%nqChild s801 do ifils=1,tracers(iq)%nqChildren 800 802 iq2=tracers(iq)%iqDescen(ifils) 801 803 !write(*,*) 'vlyqs 783: appel rec de vly, iq2=',iq2
Note: See TracChangeset
for help on using the changeset viewer.