Changeset 5618 for LMDZ6/branches/contrails/libf/phylmd/Dust
- Timestamp:
- Apr 15, 2025, 11:56:45 AM (3 months ago)
- Location:
- LMDZ6/branches/contrails
- Files:
-
- 4 deleted
- 8 edited
- 5 copied
Legend:
- Unmodified
- Added
- Removed
-
LMDZ6/branches/contrails
- Property svn:mergeinfo changed
/LMDZ6/trunk merged: 5451,5458,5460,5463,5468-5487,5490-5496,5499-5520,5524-5526,5528,5531,5544,5554-5557,5559-5562,5569-5572,5578,5582-5585,5597
- Property svn:mergeinfo changed
-
LMDZ6/branches/contrails/libf/phylmd/Dust/checknanqfi.f90
r5354 r5618 1 1 SUBROUTINE checknanqfi(zq,qmin,qmax,comment) 2 2 USE dimphy 3 USE, intrinsic :: ieee_arithmetic4 3 IMPLICIT NONE 5 4 … … 17 16 DO i = 1, klon 18 17 ! IF (zq(i,k).GT.qmax .OR. zq(i,k).LT.qmin) THEN 19 IF (i eee_is_nan(zq(i,k))) THEN18 IF (isnan(zq(i,k))) THEN 20 19 jbad = jbad + 1 21 20 jadrs(jbad) = i -
LMDZ6/branches/contrails/libf/phylmd/Dust/chem_spla_mod_h.f90
r5292 r5618 1 1 MODULE chem_spla_mod_h 2 2 IMPLICIT NONE; PRIVATE 3 PUBLIC ss_bins , masse_ammsulfate3 PUBLIC ss_bins 4 4 5 5 INTEGER, PARAMETER :: ss_bins = 2 6 REAL, PARAMETER :: masse_ammsulfate = 132.0 !--g mol-17 6 END MODULE chem_spla_mod_h 8 7 -
LMDZ6/branches/contrails/libf/phylmd/Dust/phytracr_spl_mod.F90
r5337 r5618 4 4 MODULE phytracr_spl_mod 5 5 6 USE lmdz_spla_gastoparticle, ONLY : spla_gastoparticle 7 6 8 ! Recuperation des morceaux de la physique de Jeronimo specifiques 7 9 ! du modele d'aerosols d'Olivier n'co. 8 USE chem_mod_h10 USE lmdz_spla_ini, ONLY: masse_s !au lieu de USE chem_mod_h 9 11 USE chem_spla_mod_h 10 12 … … 2748 2750 ENDIF 2749 2751 2750 CALL gastoparticle(pdtphys,zdz,zrho,rlat, &2752 CALL spla_gastoparticle(klon,klev,nbtr,pdtphys,zdz,zrho,rlat, & 2751 2753 pplay,t_seri,id_prec,id_fine, & 2752 2754 tr_seri,his_g2pgas ,his_g2paer) -
LMDZ6/branches/contrails/libf/phylmd/Dust/precuremission.f90
r5337 r5618 16 16 source_tr,flux_tr,tr_seri) 17 17 18 USE chem_spla_mod_h19 USE chem_mod_h 18 USE lmdz_spla_ini, ONLY: masse_s,masse_ammsulfate ! remplaces USE de chem_mod_h chem_spla_mod_h 19 USE lmdz_spla_nightingale, ONLY: spla_nightingale 20 20 USE dimphy 21 21 USE indice_sol_mod … … 84 84 REAL :: lmt_h2sbio(klon) ! emissions de h2s bio 85 85 86 EXTERNAL condsurfs, liss , nightingale86 EXTERNAL condsurfs, liss 87 87 !========================================================================= 88 88 ! Modifications introduced by NHL … … 96 96 !========================================================================= 97 97 98 CALL nightingale(u_seri, v_seri, u10m_ec, v10m_ec, paprs, &98 CALL spla_nightingale(klon,klev,nbsrf,u_seri, v_seri, u10m_ec, v10m_ec, paprs, & 99 99 pplay, cdragh, cdragm, t_seri, q_seri, ftsol, & 100 100 tsol, pctsrf, lmt_dmsconc, lmt_dms) -
LMDZ6/branches/contrails/libf/phylmd/Dust/read_dust.f90
r5536 r5618 21 21 save ncid1, varid1, ncid2, varid2 22 22 !$OMP THREADPRIVATE(ncid1, varid1, ncid2, varid2) 23 integer :: start (4),count(4), status23 integer :: start_(4),count_(4) 24 24 integer :: i, j, ig 25 25 ! … … 28 28 if (debutphy) then 29 29 ! 30 ncid1=nf90_open('dust.nc',nf90_nowrite,rcode) 31 varid1=nf90_inq_varid(ncid1,'EMISSION',rcode) 30 rcode=nf90_open('dust.nc',nf90_nowrite,ncid1) 31 if ( rcode /= 0 ) then ; call abort_physic('LMDZ','open dust.nc dans read_vent',1) ; endif 32 33 rcode=nf90_inq_varid(ncid1,'EMISSION',varid1) 34 if ( rcode /= 0 ) then ; call abort_physic('LMDZ','inq varid EMISSION dans read_vent',1) ; endif 32 35 ! 33 36 endif 34 37 ! 35 start(1)=1 36 start(2)=1 37 start(4)=0 38 start_(1)=1 39 start_(2)=1 40 start_(3)=step 41 start_(4)=0 38 42 39 ! count (1)=iip140 count (1)=nbp_lon+141 ! count (2)=jjp142 count (2)=nbp_lat43 count (3)=144 count (4)=043 ! count_(1)=iip1 44 count_(1)=nbp_lon+1 45 ! count_(2)=jjp1 46 count_(2)=nbp_lat 47 count_(3)=1 48 count_(4)=0 45 49 ! 46 start(3)=step47 50 ! 48 status = nf90_get_var(ncid1, varid1, dust_nc_glo, start, count) 51 rcode = nf90_get_var(ncid1, varid1, dust_nc_glo, start_, count_) 52 if ( rcode /= 0 ) then ; call abort_physic('LMDZ','get EMISSION dans read_vent',1) ; endif 49 53 50 54 ! -
LMDZ6/branches/contrails/libf/phylmd/Dust/read_surface.f90
r5536 r5618 31 31 real surfa_glo(klon_glo,5) 32 32 ! 33 integer ncid, varid, rcode 34 integer start (2),count(2),status33 integer ncid, varid, rcode, varlatid,tmpid 34 integer start_(2),count_(2) 35 35 integer i,j,l,ig 36 36 character*1 str1 … … 41 41 real, dimension(nbp_lat) :: lats 42 42 real, dimension(nbp_lat) :: lats_glo 43 integer, dimension(1) :: start j,endj43 integer, dimension(1) :: start_j,endj 44 44 !JE20140526>> 45 45 !$OMP MASTER … … 47 47 48 48 print*,'Lecture du fichier donnees_lisa.nc' 49 ncid=nf90_open('donnees_lisa.nc',nf90_nowrite,rcode) 49 rcode=nf90_open('donnees_lisa.nc',nf90_nowrite,ncid) 50 if ( rcode /= 0 ) then ; call abort_physic('LMDZ','open donnees_lisa.nc dans read_vent',1) ; endif 51 50 52 51 53 !JE20140526<<: check if are inversed or not the latitude grid in donnes_lisa … … 54 56 isinversed=.false. 55 57 do i=1,5 56 if (i==1) aux4s='latu' 57 if (i==2) aux4s='LATU' 58 if (i==3) aux4s='LatU' 59 if (i==4) aux4s='Latu' 60 if (i==5) aux4s='latU' 61 status = nf90_inq_varid(ncid, aux4s, rcode) 62 ! print *,'stat,i',status,i,outcycle,aux4s 63 ! print *,'ifclause',status.NE. nf90_noerr ,outcycle == .false. 64 IF ((.not.(status.NE. nf90_noerr) ).and.( .not. outcycle )) THEN 65 outcycle=.true. 66 latstr=aux4s 67 ENDIF 58 if (i==1) aux4s='latu' 59 if (i==2) aux4s='LATU' 60 if (i==3) aux4s='LatU' 61 if (i==4) aux4s='Latu' 62 if (i==5) aux4s='latU' 63 rcode = nf90_inq_varid(ncid, aux4s, tmpid) 64 IF ((rcode==0).and.( .not. outcycle )) THEN 65 outcycle=.true. 66 varlatid=tmpid 67 ENDIF 68 68 enddo ! check if it inversed lat 69 startj(1)=1 70 ! endj(1)=jjp1 69 start_j(1)=1 71 70 endj(1)=nbp_lat 72 varid=nf90_inq_varid(ncid,latstr,rcode) 71 rcode = nf90_get_var(ncid, varlatid, lats_glo, start_j, endj) 72 if ( .not. outcycle ) then ; call abort_physic('LMDZ','get lat dans read_surface',1) ; endif 73 73 74 status = nf90_get_var(ncid, varid, lats_glo, startj, endj) 75 ! print *,latstr,varid,status,jjp1,rcode 76 ! IF (status .NE. nf90_noerr) print*,'NOOOOOOO' 77 ! print *,lats 78 !stop 74 79 75 80 76 ! check if netcdf is latitude inversed or not. … … 86 82 write(str1,'(i1)') i 87 83 varname=trim(name)//str1 88 print*,'lecture variable:',varname89 varid=nf90_inq_varid(ncid,trim(varname),rcode)84 rcode=nf90_inq_varid(ncid,trim(varname),varid) 85 if ( rcode /= 0 ) then ; call abort_physic('LMDZ','get'//varname//' dans read_vent',1) ; endif 90 86 ! varid=nf90_inq_varid(ncid,varname,rcode) 91 87 … … 93 89 ! ----------------------------------------------------- 94 90 95 start (1)=196 start (2)=197 count (1)=nbp_lon+198 ! count (1)=iip199 count (2)=nbp_lat100 ! count (2)=jjp191 start_(1)=1 92 start_(2)=1 93 count_(1)=nbp_lon+1 94 ! count_(1)=iip1 95 count_(2)=nbp_lat 96 ! count_(2)=jjp1 101 97 102 98 ! mise a zero des tableaux … … 106 102 ! Lecture 107 103 ! ----------------------- 108 status = nf90_get_var(ncid, varid, tmp_dyn_glo, start, count) 104 rcode = nf90_get_var(ncid, varid, tmp_dyn_glo, start_, count_) 105 if ( rcode /= 0 ) then ; call abort_physic('LMDZ','get'//varname//' dans read_vent',1) ; endif 109 106 110 107 ! call dump2d(iip1,jjp1,tmp_dyn,'tmp_dyn ') -
LMDZ6/branches/contrails/libf/phylmd/Dust/read_vent.f90
r5536 r5618 23 23 save ncidu1, varidu1, ncidv1, varidv1 24 24 !$OMP THREADPRIVATE(ncidu1, varidu1, ncidv1, varidv1) 25 integer :: start(4),count (4), status25 integer :: start(4),count_(4) 26 26 integer :: i, j, ig 27 integer :: lunout 28 29 lunout=6 27 30 28 31 … … 32 35 if (debutphy) then 33 36 ! 34 ncidu1=nf90_open('u10m.nc',nf90_nowrite,rcode) 35 varidu1=nf90_inq_varid(ncidu1,'U10M',rcode) 36 ncidv1=nf90_open('v10m.nc',nf90_nowrite,rcode) 37 varidv1=nf90_inq_varid(ncidv1,'V10M',rcode) 37 rcode=nf90_open('u10m.nc',nf90_nowrite,ncidu1) 38 if ( rcode /= 0 ) then ; call abort_physic('LMDZ','open u10m.nc dans read_vent',1) ; endif 39 rcode=nf90_inq_varid(ncidu1,'U10M',varidu1) 40 if ( rcode /= 0 ) then ; call abort_physic('LMDZ','get id u10m dans read_vent',1) ; endif 41 rcode=nf90_open('v10m.nc',nf90_nowrite,ncidv1) 42 if ( rcode /= 0 ) then ; call abort_physic('LMDZ','open v10m.nc dans read_vent',1) ; endif 43 rcode=nf90_inq_varid(ncidv1,'V10M',varidv1) 44 if ( rcode /= 0 ) then ; call abort_physic('LMDZ','get id v10m dans read_vent',1) ; endif 38 45 ! 39 46 endif … … 41 48 start(1)=1 42 49 start(2)=1 50 start(3)=step 43 51 start(4)=0 44 52 45 ! count (1)=iip146 count (1)=nbp_lon+147 ! count (2)=jjp148 count (2)=nbp_lat49 count (3)=150 count (4)=053 ! count_(1)=iip1 54 count_(1)=nbp_lon+1 55 ! count_(2)=jjp1 56 count_(2)=nbp_lat 57 count_(3)=1 58 count_(4)=0 51 59 ! 52 start(3)=step53 60 ! 54 status = nf90_get_var(ncidu1, varidu1, u10m_nc_glo, start, count) 61 rcode = nf90_get_var(ncidu1, varidu1, u10m_nc_glo, start, count_) 62 ! if ( rcode /= 0 ) then ; call abort_physic('LMDZ','lecture u10m dans read_vent',1) ; endif 63 if ( rcode /= 0 ) then ; write(lunout,*) 'WARNING : pas de temps manquant dans la lecture u10m dans read_vent' ; endif 64 rcode = nf90_get_var(ncidv1, varidv1, v10m_nc_glo, start, count_) 65 ! if ( rcode /= 0 ) then ; call abort_physic('LMDZ','lecture v10m dans read_vent',1) ; endif 66 if ( rcode /= 0 ) then ; write(lunout,*) 'WARNING : pas de temps manquant dans la lecture v10m dans read_vent' ; endif 55 67 56 ! print *,status 57 ! 58 status = nf90_get_var(ncidv1, varidv1, v10m_nc_glo, start, count) 68 69 ! ------- Tests 2024/12/31-FH---------------------------------------- 70 ! print*,'nbp_lon,npb_lat ',nbp_lon,nbp_lat 71 ! print*,'start ',start 72 ! print*,'count_ ',count_ 73 ! print*,'satus lecture u10m ',rcode 74 ! call dump2d(nbp_lon+1,nbp_lat,u10m_nc_glo,'U10M global read_vent') 75 ! call dump2d(nbp_lon+1,nbp_lat,v10m_nc_glo,'V10M global read_vent') 76 ! stop 77 ! ------- Tests ----------------------------------------------------- 59 78 60 79 ! … … 63 82 ! print *,'beforebidcor v10m_nc', v10m_nc(1,jjp1) 64 83 65 ! print *, status84 ! print *,rcode 66 85 ! call correctbid(iim,jjp1,u10m_nc) 67 86 ! call correctbid(iim,jjp1,v10m_nc)
Note: See TracChangeset
for help on using the changeset viewer.