PROGRAM anldiag_nc IMPLICIT NONE c====================================================================== c c c Program designed to read output files from the MARS gcm c or the Mars Climate database. c c Francois Forget 1999 c Version used by monica to interpolate in zaeroid and p coordinate c c======================================================================= c declarations: c ------------- #include "dimensions.h" #include "paramet.h" #include "comconst.h" #include "comdissip.h" #include "comvert.h" #include "comgeom2.h" #include "logic.h" #include "temps.h" #include "control.h" #include "ener.h" #include "description.h" #include "netcdf.inc" INTEGER itau,nbpas,nbpasmx, coor,sor,varoutsize integer varspecsize integer varout(6),varspec(nqmx) integer itau0 PARAMETER(nbpasmx=1000000) REAL temps(nbpasmx),y INTEGER unitlec INTEGER i,j,l,irec,itautot,ierr,iq,n,ff,k real, dimension(:),allocatable :: lat,lon,alt integer:: nout,latdimout,londimout,altdimout,timedimout,timevarout integer:: latdim,londim,altdim,dimid integer:: latvar,lonvar,altvar,timevar integer:: latlen,lonlen,altlen,timelen integer, dimension(4) :: edges,corner,id integer, dimension(3) :: edges2,corner2 INTEGER unit,nvarid,nid,varid REAL mugaz REAL missing PARAMETER(missing=1E+20) REAL valid_range(2) DATA valid_range /0., 300.0/ c variables meteo dans la grille verticale GCM c -------------------------------------------- REAL v(iip1,jjp1,llm),u(iip1,jjp1,llm),w(iip1,jjp1,llm) REAL t(iip1,jjp1,llm),rho(iip1,jjp1,llm),phi(iip1,jjp1,llm) REAL ps(iip1,jjp1) , tsurf(iip1,jjp1) REAL Rnew(iip1,jjp1,llm) real euv(iip1,jjp1,llm),con(iip1,jjp1,llm),nir(iip1,jjp1,llm) real nspec(iip1,jjp1,llm,nqmx),spec(iip1,jjp1,llm) REAL v_sd(iip1,jjp1,llm),u_sd(iip1,jjp1,llm) real w_sd(iip1,jjp1,llm),t_sd(iip1,jjp1,llm) real rho_sd(iip1,jjp1,llm) real euv_sd(iip1,jjp1,llm),con_sd(iip1,jjp1,llm) real nir_sd(iip1,jjp1,llm) real nspec_sd(iip1,jjp1,llm,nqmx) c ALtitude of the GCM levels (+1 dummy "thermosphere level") c ------------------------- REAL zlocal(iip1,jjp1,llm+1) ! altitude above the local surface (m) REAL zareoid(iip1,jjp1,llm+1) ! altitude above the mola areoid (m) real tmean ! use to integrate hydrostatic equation real sig_therm ! dummy "thermosphere level" as in atmemcd.F real T_therm c variables meteo en coordonnee de pression c -------------------------------------------- REAL vp(iip1,jjp1,llm),up(iip1,jjp1,llm),wp(iip1,jjp1,llm) REAL tp(iip1,jjp1,llm),rhop(iip1,jjp1,llm) REAL nspecp(iip1,jjp1,llm,nqmx) REAL phip(iip1,jjp1,llm) REAL vp_sd(iip1,jjp1,llm),up_sd(iip1,jjp1,llm) real wp_sd(iip1,jjp1,llm),tp_sd(iip1,jjp1,llm) real rhop_sd(iip1,jjp1,llm),nspecp_sd(iip1,jjp1,llm,nqmx) c Niveaux de pression (Pa) real pref(llm) c Version 32 layers : ************ data pref/ &1000.,884., 783. , 610., 475, 370, 288, 224, 174, 140., &115 , 80.6481, 48.0445, 26.6881, 14.1462, 7.29102, 3.70004, &1.86241, 0.933516, 0.466924, 0.233296, 0.116503, 5.81631E-02, & 2.90335E-02,1.44919E-02, 7.23328E-03, 3.61027E-03, 1.80193E-03, & 8.99364E-04,4.48881E-04, 2.15769E-04, 1.3E-04/ c Version 50 layers : ************ c data pref/ c &1000.,884., 783. , 610., 475, 370, 288, 224, 174, 140., c &115 , 80.6481, 48.0445, 26.6881, 14.1462, 7.29102, 3.70004, c &1.86241, 0.933516, 0.466924, 0.233296, 0.116503, 5.81631E-02, c & 2.90335E-02,1.44919E-02, 7.23328E-03, 3.61027E-03, 1.80193E-03, c & 8.99364E-04,4.48881E-04, 2.15769E-04, 1.3E-04, c & 7.23328e-05, 3.61027e-05, 1.80193e-05, 8.99364e-06, c & 4.48881e-06, 2.15769e-06, 1.3e-06, c & 7.23328e-07, 3.61027e-07, 1.80193e-07, 8.99364e-08, c & 4.48881e-08, 2.15769e-08, 1.3e-08, c & 7.23328e-09, 3.61027e-09, 1.80193e-09, 8.99364e-10/ c data pref/ c &1000.,884., 783. , 610., 475, 370, 288, 224, 174, 140., c &115 , 80.6481, 48.0445, 26.6881, 14.1462, 7.29102, 3.70004, c &1.86241, 0.933516, 0.466924, 0.233296, 0.116503, 5.81631E-02, c & 2.90335E-02,1.44919E-02 / c data pref/ c & 101.4369,94.4369,87.4369,80.4369,73.4369,66.4369,59.4369,52.4369, c & 45.4369,38.4369,31.5527,25.0626,18.9666,13.5138,8.97780, c & 5.54010,3.19040,1.73630,0.907000,0.460400,0.228200,0.109700, c & 0.0500,0.0200,0.0050/ c variables meteo en coordonnee de zareoid c -------------------------------------------- REAL va(iip1,jjp1,llm),ua(iip1,jjp1,llm),wa(iip1,jjp1,llm) REAL ta(iip1,jjp1,llm),rhoa(iip1,jjp1,llm),ra(iip1,jjp1,llm) real euva(iip1,jjp1,llm),cona(iip1,jjp1,llm),nira(iip1,jjp1,llm) real nspeca(iip1,jjp1,llm,nqmx) REAL va_sd(iip1,jjp1,llm),ua_sd(iip1,jjp1,llm) real wa_sd(iip1,jjp1,llm),ta_sd(iip1,jjp1,llm) real rhoa_sd(iip1,jjp1,llm) real euva_sd(iip1,jjp1,llm),cona_sd(iip1,jjp1,llm) real nira_sd(iip1,jjp1,llm) real nspeca_sd(iip1,jjp1,llm,nqmx) REAL vij(llm),uij(llm),zaij(llm),wij(llm),rij(llm) REAL tij(llm),rhoij(llm+1),sigij(llm) real euvij(llm),conij(llm),nirij(llm) real nspecij(llm+1,nqmx) REAL vij_sd(llm),uij_sd(llm) real wij_sd(llm),tij_sd(llm),rhoij_sd(llm+1) real euvij_sd(llm),conij_sd(llm),nirij_sd(llm) real nspecij_sd(llm+1,nqmx) c Niveaux de zareoide (m) real zaref(llm) real p_zaref,p_zaij(llm+1) ! used to interpolate rho c Surface data (sometime needed for some analysis): c ------------------------------------------------ character relief*3 real phis(iip1,jjp1) real alb(iip1,jjp1),ith(iip1,jjp1) real zmeaS(iip1,jjp1),zstdS(iip1,jjp1) real zsigS(iip1,jjp1),zgamS(iip1,jjp1),ztheS(iip1,jjp1) real utime real localtime(iip1) common/temporaire/localtime INTEGER*4 day0 integer nmoy(jjp1,llm),tp1,tp2,pass CHARACTER*1 yes,yescomp integer iformat c declarations de l'interface avec mywrite: c ----------------------------------------- CHARACTER file*80 CHARACTER nomfich*60 CHARACTER nomfile(2)*60,nomfileout(2)*60 integer fichsize,fstats CHARACTER fdiag*60 c externe: c -------- EXTERNAL iniconst,inigeom,covcont,mywrite EXTERNAL inifilr,exner EXTERNAL solarlong,coordij,moy2 EXTERNAL SSUM REAL SSUM EXTERNAL lnblnk INTEGER lnblnk c Dust c ---- #include "fxyprim.h" character*10 noms(nqmx),varnoms(6) data noms/"co2","co","o","o1d","o2","o3","h","h2", $ "oh","ho2","h2o2", "n2", "h2o"/ data varnoms/"T","U","V","W","RHO","Species"/ c----------------------------------------------------------------------- c initialisations: c ---------------- unitlec=11 itautot=0 c Lecture du fichier a lire c ------------------------- print*,' ' PRINT*,'File to process: 1)DIAGFI 2)STATS 3)BOTH' READ(5,'(i)') fichsize if(fichsize.ne.2)then i=1 PRINT*,' enter name of diagfi file (w/o .nc)' READ(5,'(a)') nomfile(i) fdiag=nomfile(i) PRINT*,' do you want to rename the output file? & 1) Yes 2) No' READ(5,'(i)') sor if (sor.eq.1) then PRINT*,' enter label for output file' READ(5,'(a)') nomfileout(i) elseif(sor.eq.2) then nomfileout(i)=nomfile(i) endif endif if(fichsize.ne.1)then i=i+1 PRINT*,' enter name of stats file (w/o .nc)' READ(5,'(a)') nomfile(i) PRINT*,' do you want to rename the output file? & 1) Yes 2) No' READ(5,'(i)') sor if (sor.eq.1) then PRINT*,' enter label for output file' READ(5,'(a)') nomfileout(i) elseif(sor.eq.2) then nomfileout(i)=nomfile(i) endif if(fichsize.eq.2) then PRINT*,' enter name of diagfi file for controle (w/o .nc)' read(5,'(a)') fdiag endif fstats=1 endif if (fichsize.ge.2) fichsize=fichsize-1 print*,' ' print*,'Output in: 1) netcdf 2) IDL 3) both ?' READ(5,'(i)') sor print*,' ' print*,'Coordinates in: 1) pressure 2) Zareoid 3) both ?' READ(5,'(i)') coor print*,' ' print*,'Fields: T U V W Rho Species All ?' print*,'Type total number of desired outputs or 6 for All ' READ(5,'(i)') varoutsize if(varoutsize.lt.6) then print*,' ' print*,'Fields: T U V W Rho Species ' print*,' # : 1 2 3 4 5 6' print*,' ' do i=1,varoutsize print*,'Type number of variable ',i READ(5,'(i)') varout(i) enddo endif if(varoutsize.eq.6) then do i=1,6 varout(i)=i enddo endif do i=1,varoutsize if (varout(i).eq.6) then print*,'Type total number of desired species or 13 for All' READ(5,'(i2)') varspecsize if(varspecsize.ne.13) then print*,' ' print*,'Select Species: CO2 CO O O(1D) O2 O3' print*,' 1 2 3 4 5 6' print*,' H H2 OH HO2 H2O2 N2 H2O' print*,' 7 8 9 10 11 12 13' do n=1,varspecsize print*,'Type number of species ',i read(5,'(i)') varspec(n) enddo else do n=1,varspecsize varspec(n)=n enddo endif endif enddo if(varoutsize.gt.6) print*,'Value must be <= 6' ! LOOP ON FILES ! ================================================================= do ff=1,fichsize file=nomfile(ff) nomfich=nomfile(ff) file=file(1:lnblnk(file)) PRINT*,'file',file c Ouverture fichiers : c ------------------ write(*,*) "opening "//trim(nomfich)//"..." ierr = NF_OPEN(trim(adjustl(nomfich))//".nc",NF_NOWRITE,nid) if (ierr.NE.NF_NOERR) then write(*,*) 'ERROR: Pb opening file '//nomfich stop "" endif ! Control & lecture on dimensions ! ================================================================= ierr=NF_INQ_DIMID(nid,"latitude",latdim) ierr=NF_INQ_VARID(nid,"latitude",latvar) if (ierr.NE.NF_NOERR) then write(*,*) 'ERROR: Field is missing' stop "" endif ierr=NF_INQ_DIMLEN(nid,latdim,latlen) ! write(*,*) "latlen: ",latlen ierr=NF_INQ_DIMID(nid,"longitude",londim) ierr=NF_INQ_VARID(nid,"longitude",lonvar) if (ierr.NE.NF_NOERR) then write(*,*) 'ERROR: Field is lacking' stop "" endif ierr=NF_INQ_DIMLEN(nid,londim,lonlen) ! write(*,*) "lonlen: ",lonlen ierr=NF_INQ_DIMID(nid,"altitude",altdim) ierr=NF_INQ_VARID(nid,"altitude",altvar) if (ierr.NE.NF_NOERR) then write(*,*) 'ERROR: Field is lacking' stop "" endif ierr=NF_INQ_DIMLEN(nid,altdim,altlen) ! write(*,*) "altlen: ",altlen if (ff.eq.1) then allocate(lat(latlen)) allocate(lon(lonlen)) allocate(alt(altlen)) endif #ifdef NC_DOUBLE ierr = NF_GET_VAR_DOUBLE(nid,latvar,lat) ierr = NF_GET_VAR_DOUBLE(nid,lonvar,lon) ierr = NF_GET_VAR_DOUBLE(nid,altvar,alt) #else ierr = NF_GET_VAR_REAL(nid,latvar,lat) ierr = NF_GET_VAR_REAL(nid,lonvar,lon) ierr = NF_GET_VAR_REAL(nid,altvar,alt) #endif c Lecture Time : ierr= NF_INQ_DIMID (nid,"Time",dimid) IF (ierr.NE.NF_NOERR) THEN PRINT*, 'anl_NC: Le champ