SUBROUTINE physiq( $ ngrid,nlayer,nq $ ,firstcall,lastcall $ ,pday,ptime,ptimestep $ ,pplev,pplay,pphi $ ,pu,pv,pt,pq $ ,pw $ ,pdu,pdv,pdt,pdq,pdpsrf,tracerdyn #ifdef MESOSCALE #include "meso_inc/meso_inc_invar.F" #endif $ ) IMPLICIT NONE c======================================================================= c c subject: c -------- c c Organisation of the physical parametrisations of the LMD c martian atmospheric general circulation model. c c The GCM can be run without or with tracer transport c depending on the value of Logical "tracer" in file "callphys.def" c Tracers may be water vapor, ice OR chemical species OR dust particles c c SEE comments in initracer.F about numbering of tracer species... c c It includes: c c 1. Initialization: c 1.1 First call initializations c 1.2 Initialization for every call to physiq c 1.2.5 Compute mean mass and cp, R and thermal conduction coeff. c 2. Compute radiative transfer tendencies c (longwave and shortwave) for CO2 and aerosols. c 3. Gravity wave and subgrid scale topography drag : c 4. Vertical diffusion (turbulent mixing): c 5. Convective adjustment c 6. Condensation and sublimation of carbon dioxide. c 7. TRACERS : c 7a. water and water ice c 7b. call for photochemistry when tracers are chemical species c 7c. other scheme for tracer (dust) transport (lifting, sedimentation) c 7d. updates (CO2 pressure variations, surface budget) c 8. Contribution to tendencies due to thermosphere c 9. Surface and sub-surface temperature calculations c 10. Write outputs : c - "startfi", "histfi" (if it's time) c - Saving statistics (if "callstats = .true.") c - Dumping eof (if "calleofdump = .true.") c - Output any needed variables in "diagfi" c 11. Diagnostic: mass conservation of tracers c c author: c ------- c Frederic Hourdin 15/10/93 c Francois Forget 1994 c Christophe Hourdin 02/1997 c Subroutine completly rewritten by F.Forget (01/2000) c Introduction of the photochemical module: S. Lebonnois (11/2002) c Introduction of the thermosphere module: M. Angelats i Coll (2002) c Water ice clouds: Franck Montmessin (update 06/2003) c Radiatively active tracers: J.-B. Madeleine (10/2008-06/2009) c Nb: See callradite.F for more information. c Mesoscale lines: Aymeric Spiga (2007 - 2011) -- check MESOSCALE flags c jul 2011 malv+fgg: Modified calls to NIR heating routine and 15 um cooling parameterization c c arguments: c ---------- c c input: c ------ c ecri period (in dynamical timestep) to write output c ngrid Size of the horizontal grid. c All internal loops are performed on that grid. c nlayer Number of vertical layers. c nq Number of advected fields c firstcall True at the first call c lastcall True at the last call c pday Number of days counted from the North. Spring c equinoxe. c ptime Universal time (0 0 !!!!!!!!!!!!!!!!!!!!! This is due to single precision rounding problems if (((pq(ig,l,igcm_ccn_number) + & pdq(ig,l,igcm_ccn_number)*ptimestep)) .le. 0) & then pdq(ig,l,igcm_ccn_number) = & - pq(ig,l,igcm_ccn_number)/ptimestep + 1e-30 endif if (((pq(ig,l,igcm_dust_number) + & pdq(ig,l,igcm_dust_number)*ptimestep)) .le. 0) & then pdq(ig,l,igcm_dust_number) = & - pq(ig,l,igcm_dust_number)/ptimestep + 1e-30 endif !!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!! pdq(ig,l,igcm_dust_mass)= & pdq(ig,l,igcm_dust_mass)+ & zdqcloud(ig,l,igcm_dust_mass) pdq(ig,l,igcm_dust_number)= & pdq(ig,l,igcm_dust_number)+ & zdqcloud(ig,l,igcm_dust_number) ENDIF ENDDO ENDDO ENDIF ! of IF (water) THEN ! Increment water ice surface tracer tendency DO ig=1,ngrid dqsurf(ig,igcm_h2o_ice)=dqsurf(ig,igcm_h2o_ice)+ & zdqscloud(ig,igcm_h2o_ice) ENDDO END IF ! of IF (water) c 7b. Chemical species c ------------------ #ifndef MESOSCALE c -------------- c photochemistry : c -------------- IF (photochem .or. thermochem) then !NB: Photochemistry includes condensation of H2O2 PRINT*, 'SURFDUST,SURFICE TO BE IMPLEMENTED. YAAAAAARG.' call calchim(ptimestep,pplay,pplev,pt,pdt,dist_sol,mu0, $ zzlev,zzlay,zday,pq,pdq,zdqchim,zdqschim, $ zdqcloud,zdqscloud,tauref,co2ice, $ pu,pdu,pv,pdv,surfdust,surfice) ! increment values of tracers: DO iq=1,nq ! loop on all tracers; tendencies for non-chemistry ! tracers is zero anyways DO l=1,nlayer DO ig=1,ngrid pdq(ig,l,iq)=pdq(ig,l,iq)+zdqchim(ig,l,iq) ENDDO ENDDO ENDDO ! of DO iq=1,nq ! add condensation tendency for H2O2 if (igcm_h2o2.ne.0) then DO l=1,nlayer DO ig=1,ngrid pdq(ig,l,igcm_h2o2)=pdq(ig,l,igcm_h2o2) & +zdqcloud(ig,l,igcm_h2o2) ENDDO ENDDO endif ! increment surface values of tracers: DO iq=1,nq ! loop on all tracers; tendencies for non-chemistry ! tracers is zero anyways DO ig=1,ngrid dqsurf(ig,iq)=dqsurf(ig,iq)+zdqschim(ig,iq) ENDDO ENDDO ! of DO iq=1,nq ! add condensation tendency for H2O2 if (igcm_h2o2.ne.0) then DO ig=1,ngrid dqsurf(ig,igcm_h2o2)=dqsurf(ig,igcm_h2o2) & +zdqscloud(ig,igcm_h2o2) ENDDO endif END IF ! of IF (photochem.or.thermochem) #endif c 7c. Aerosol particles c ------------------- c ---------- c Dust devil : c ---------- IF(callddevil) then call dustdevil(ngrid,nlayer,nq, pplev,pu,pv,pt, tsurf,q2, & zdqdev,zdqsdev) if (dustbin.ge.1) then do iq=1,nq DO l=1,nlayer DO ig=1,ngrid pdq(ig,l,iq)=pdq(ig,l,iq)+ zdqdev(ig,l,iq) ENDDO ENDDO enddo do iq=1,nq DO ig=1,ngrid dqsurf(ig,iq)= dqsurf(ig,iq) + zdqsdev(ig,iq) ENDDO enddo endif ! of if (dustbin.ge.1) END IF ! of IF (callddevil) c ------------- c Sedimentation : acts also on water ice c ------------- IF (sedimentation) THEN !call zerophys(ngrid*nlayer*nq, zdqsed) zdqsed(1:ngrid,1:nlayer,1:nq)=0 !call zerophys(ngrid*nq, zdqssed) zdqssed(1:ngrid,1:nq)=0 call callsedim(ngrid,nlayer, ptimestep, & pplev,zzlev, zzlay, pt, rdust, rice, & rsedcloud,rhocloud, & pq, pdq, zdqsed, zdqssed,nq, & tau,tauscaling) DO iq=1, nq DO l=1,nlayer DO ig=1,ngrid pdq(ig,l,iq)=pdq(ig,l,iq)+ zdqsed(ig,l,iq) ENDDO ENDDO ENDDO DO iq=1, nq DO ig=1,ngrid dqsurf(ig,iq)= dqsurf(ig,iq) + zdqssed(ig,iq) ENDDO ENDDO END IF ! of IF (sedimentation) c 7d. Updates c --------- DO iq=1, nq DO ig=1,ngrid c --------------------------------- c Updating tracer budget on surface c --------------------------------- qsurf(ig,iq)=qsurf(ig,iq)+ptimestep*dqsurf(ig,iq) ENDDO ! (ig) ENDDO ! (iq) endif ! of if (tracer) #ifndef MESOSCALE c----------------------------------------------------------------------- c 8. THERMOSPHERE CALCULATION c----------------------------------------------------------------------- if (callthermos) then call thermosphere(pplev,pplay,dist_sol, $ mu0,ptimestep,ptime,zday,tsurf,zzlev,zzlay, & pt,pq,pu,pv,pdt,pdq, $ zdteuv,zdtconduc,zdumolvis,zdvmolvis,zdqmoldiff) DO l=1,nlayer DO ig=1,ngrid dtrad(ig,l)=dtrad(ig,l)+zdteuv(ig,l) pdt(ig,l)=pdt(ig,l)+zdtconduc(ig,l) & +zdteuv(ig,l) pdv(ig,l)=pdv(ig,l)+zdvmolvis(ig,l) pdu(ig,l)=pdu(ig,l)+zdumolvis(ig,l) DO iq=1, nq pdq(ig,l,iq)=pdq(ig,l,iq)+zdqmoldiff(ig,l,iq) ENDDO ENDDO ENDDO endif ! of if (callthermos) #endif c----------------------------------------------------------------------- c 9. Surface and sub-surface soil temperature c----------------------------------------------------------------------- c c c 9.1 Increment Surface temperature: c ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ DO ig=1,ngrid tsurf(ig)=tsurf(ig)+ptimestep*zdtsurf(ig) ENDDO c Prescribe a cold trap at south pole (except at high obliquity !!) c Temperature at the surface is set there to be the temperature c corresponding to equilibrium temperature between phases of CO2 IF (tracer.AND.water.AND.(ngridmx.NE.1)) THEN #ifndef MESOSCALE if (caps.and.(obliquit.lt.27.)) then ! NB: Updated surface pressure, at grid point 'ngrid', is ! ps(ngrid)=pplev(ngrid,1)+pdpsrf(ngrid)*ptimestep tsurf(ngrid)=1./(1./136.27-r/5.9e+5*alog(0.0095* & (pplev(ngrid,1)+pdpsrf(ngrid)*ptimestep))) endif #endif c ------------------------------------------------------------- c Change of surface albedo in case of ground frost c everywhere except on the north permanent cap and in regions c covered by dry ice. c ALWAYS PLACE these lines after newcondens !!! c ------------------------------------------------------------- do ig=1,ngrid if ((co2ice(ig).eq.0).and. & (qsurf(ig,igcm_h2o_ice).gt.frost_albedo_threshold)) then albedo(ig,1) = albedo_h2o_ice albedo(ig,2) = albedo_h2o_ice c write(*,*) "frost thickness", qsurf(ig,igcm_h2o_ice) c write(*,*) "physiq.F frost :" c & ,lati(ig)*180./pi, long(ig)*180./pi endif enddo ! of do ig=1,ngrid ENDIF ! of IF (tracer.AND.water.AND.(ngridmx.NE.1)) c c 9.2 Compute soil temperatures and subsurface heat flux: c ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ IF (callsoil) THEN CALL soil(ngrid,nsoilmx,.false.,inertiedat, & ptimestep,tsurf,tsoil,capcal,fluxgrd) ENDIF c----------------------------------------------------------------------- c 10. Write output files c ---------------------- c ------------------------------- c Dynamical fields incrementation c ------------------------------- c (FOR OUTPUT ONLY : the actual model integration is performed in the dynamics) ! temperature, zonal and meridional wind DO l=1,nlayer DO ig=1,ngrid zt(ig,l)=pt(ig,l) + pdt(ig,l)*ptimestep zu(ig,l)=pu(ig,l) + pdu(ig,l)*ptimestep zv(ig,l)=pv(ig,l) + pdv(ig,l)*ptimestep ENDDO ENDDO ! tracers DO iq=1, nq DO l=1,nlayer DO ig=1,ngrid zq(ig,l,iq)=pq(ig,l,iq) +pdq(ig,l,iq)*ptimestep ENDDO ENDDO ENDDO ! surface pressure DO ig=1,ngrid ps(ig)=pplev(ig,1) + pdpsrf(ig)*ptimestep ENDDO ! pressure DO l=1,nlayer DO ig=1,ngrid zplev(ig,l)=pplev(ig,l)/pplev(ig,1)*ps(ig) zplay(ig,l)=pplay(ig,l)/pplev(ig,1)*ps(ig) ENDDO ENDDO ! Density DO l=1,nlayer DO ig=1,ngrid rho(ig,l) = zplay(ig,l)/(rnew(ig,l)*zt(ig,l)) ENDDO ENDDO ! Potential Temperature DO ig=1,ngridmx DO l=1,nlayermx zh(ig,l) = zt(ig,l)*(zplay(ig,l)/zplev(ig,1))**rcp ENDDO ENDDO c Compute surface stress : (NB: z0 is a common in surfdat.h) c DO ig=1,ngrid c cd = (0.4/log(zzlay(ig,1)/z0(ig)))**2 c zstress(ig) = rho(ig,1)*cd*(zu(ig,1)**2 + zv(ig,1)**2) c ENDDO c Sum of fluxes in solar spectral bands (for output only) DO ig=1,ngrid fluxtop_sw_tot(ig)=fluxtop_sw(ig,1) + fluxtop_sw(ig,2) fluxsurf_sw_tot(ig)=fluxsurf_sw(ig,1) + fluxsurf_sw(ig,2) ENDDO c ******* TEST ****************************************************** ztim1 = 999 DO l=1,nlayer DO ig=1,ngrid if (pt(ig,l).lt.ztim1) then ztim1 = pt(ig,l) igmin = ig lmin = l end if ENDDO ENDDO if(min(pt(igmin,lmin),zt(igmin,lmin)).lt.70.) then write(*,*) 'PHYSIQ: stability WARNING :' write(*,*) 'pt, zt Tmin = ', pt(igmin,lmin), zt(igmin,lmin), & 'ig l =', igmin, lmin end if c ******************************************************************* c --------------------- c Outputs to the screen c --------------------- IF (lwrite) THEN PRINT*,'Global diagnostics for the physics' PRINT*,'Variables and their increments x and dx/dt * dt' WRITE(*,'(a6,a10,2a15)') 'Ts','dTs','ps','dps' WRITE(*,'(2f10.5,2f15.5)') s tsurf(igout),zdtsurf(igout)*ptimestep, s pplev(igout,1),pdpsrf(igout)*ptimestep WRITE(*,'(a4,a6,5a10)') 'l','u','du','v','dv','T','dT' WRITE(*,'(i4,6f10.5)') (l, s pu(igout,l),pdu(igout,l)*ptimestep, s pv(igout,l),pdv(igout,l)*ptimestep, s pt(igout,l),pdt(igout,l)*ptimestep, s l=1,nlayer) ENDIF ! of IF (lwrite) IF (ngrid.NE.1) THEN #ifndef MESOSCALE c ------------------------------------------------------------------- c Writing NetCDF file "RESTARTFI" at the end of the run c ------------------------------------------------------------------- c Note: 'restartfi' is stored just before dynamics are stored c in 'restart'. Between now and the writting of 'restart', c there will have been the itau=itau+1 instruction and c a reset of 'time' (lastacll = .true. when itau+1= itaufin) c thus we store for time=time+dtvr IF(lastcall) THEN ztime_fin = ptime + ptimestep/(float(iphysiq)*daysec) write(*,*)'PHYSIQ: for physdem ztime_fin =',ztime_fin call physdem1("restartfi.nc",long,lati,nsoilmx,nq, . ptimestep,pday, . ztime_fin,tsurf,tsoil,co2ice,emis,q2,qsurf, . area,albedodat,inertiedat,zmea,zstd,zsig, . zgam,zthe) ENDIF #endif c ------------------------------------------------------------------- c Calculation of diagnostic variables written in both stats and c diagfi files c ------------------------------------------------------------------- if (tracer) then if (water) then mtot(:)=0 icetot(:)=0 rave(:)=0 tauTES(:)=0 do ig=1,ngrid do l=1,nlayermx mtot(ig) = mtot(ig) + & zq(ig,l,igcm_h2o_vap) * & (pplev(ig,l) - pplev(ig,l+1)) / g icetot(ig) = icetot(ig) + & zq(ig,l,igcm_h2o_ice) * & (pplev(ig,l) - pplev(ig,l+1)) / g rave(ig) = rave(ig) + & zq(ig,l,igcm_h2o_ice) * & (pplev(ig,l) - pplev(ig,l+1)) / g * & rice(ig,l) * (1.+nuice_ref) c Computing abs optical depth at 825 cm-1 in each c layer to simulate NEW TES retrieval Qabsice = min( & max(0.4e6*rice(ig,l)*(1.+nuice_ref)-0.05 ,0.),1.2 & ) opTES(ig,l)= 0.75 * Qabsice * & zq(ig,l,igcm_h2o_ice) * & (pplev(ig,l) - pplev(ig,l+1)) / g & / (rho_ice * rice(ig,l) * (1.+nuice_ref)) tauTES(ig)=tauTES(ig)+ opTES(ig,l) enddo rave(ig)=rave(ig)/max(icetot(ig),1.e-30) if (icetot(ig)*1e3.lt.0.01) rave(ig)=0. enddo endif ! of if (water) endif ! of if (tracer) c ----------------------------------------------------------------- c WSTATS: Saving statistics c ----------------------------------------------------------------- c ("stats" stores and accumulates 8 key variables in file "stats.nc" c which can later be used to make the statistic files of the run: c "stats") only possible in 3D runs ! IF (callstats) THEN call wstats(ngrid,"ps","Surface pressure","Pa",2,ps) call wstats(ngrid,"tsurf","Surface temperature","K",2,tsurf) call wstats(ngrid,"co2ice","CO2 ice cover", & "kg.m-2",2,co2ice) call wstats(ngrid,"fluxsurf_lw", & "Thermal IR radiative flux to surface","W.m-2",2, & fluxsurf_lw) call wstats(ngrid,"fluxsurf_sw", & "Solar radiative flux to surface","W.m-2",2, & fluxsurf_sw_tot) call wstats(ngrid,"fluxtop_lw", & "Thermal IR radiative flux to space","W.m-2",2, & fluxtop_lw) call wstats(ngrid,"fluxtop_sw", & "Solar radiative flux to space","W.m-2",2, & fluxtop_sw_tot) call wstats(ngrid,"temp","Atmospheric temperature","K",3,zt) call wstats(ngrid,"u","Zonal (East-West) wind","m.s-1",3,zu) call wstats(ngrid,"v","Meridional (North-South) wind", & "m.s-1",3,zv) call wstats(ngrid,"w","Vertical (down-up) wind", & "m.s-1",3,pw) call wstats(ngrid,"rho","Atmospheric density","none",3,rho) call wstats(ngrid,"pressure","Pressure","Pa",3,pplay) c call wstats(ngrid,"q2", c & "Boundary layer eddy kinetic energy", c & "m2.s-2",3,q2) c call wstats(ngrid,"emis","Surface emissivity","w.m-1",2, c & emis) c call wstats(ngrid,"ssurf","Surface stress","N.m-2", c & 2,zstress) c call wstats(ngrid,"sw_htrt","sw heat.rate", c & "W.m-2",3,zdtsw) c call wstats(ngrid,"lw_htrt","lw heat.rate", c & "W.m-2",3,zdtlw) if (tracer) then if (water) then c vmr=zq(1:ngridmx,1:nlayermx,igcm_h2o_vap) c & *mugaz/mmol(igcm_h2o_vap) c call wstats(ngrid,"vmr_h2ovapor", c & "H2O vapor volume mixing ratio","mol/mol", c & 3,vmr) c vmr=zq(1:ngridmx,1:nlayermx,igcm_h2o_ice) c & *mugaz/mmol(igcm_h2o_ice) c call wstats(ngrid,"vmr_h2oice", c & "H2O ice volume mixing ratio","mol/mol", c & 3,vmr) call wstats(ngrid,"h2o_ice_s", & "surface h2o_ice","kg/m2", & 2,qsurf(1,igcm_h2o_ice)) c call wstats(ngrid,'albedo', c & 'albedo', c & '',2,albedo(1:ngridmx,1)) call wstats(ngrid,"mtot", & "total mass of water vapor","kg/m2", & 2,mtot) call wstats(ngrid,"icetot", & "total mass of water ice","kg/m2", & 2,icetot) c call wstats(ngrid,"reffice", c & "Mean reff","m", c & 2,rave) c call wstats(ngrid,"rice", c & "Ice particle size","m", c & 3,rice) c If activice is true, tauTES is computed in aeropacity.F; if (.not.activice) then call wstats(ngrid,"tauTESap", & "tau abs 825 cm-1","", & 2,tauTES) endif endif ! of if (water) if (thermochem.or.photochem) then do iq=1,nq if ((noms(iq).eq."o").or.(noms(iq).eq."co2").or. . (noms(iq).eq."co").or.(noms(iq).eq."n2").or. . (noms(iq).eq."h2").or. . (noms(iq).eq."o3")) then do l=1,nlayer do ig=1,ngrid vmr(ig,l)=zq(ig,l,iq)*mmean(ig,l)/mmol(iq) end do end do call wstats(ngrid,"vmr_"//trim(noms(iq)), . "Volume mixing ratio","mol/mol",3,vmr) endif ! do ig = 1,ngrid ! colden(ig,iq) = 0. !FL ! end do ! do l=1,nlayer !FL ! do ig=1,ngrid !FL ! colden(ig,iq) = colden(ig,iq) + zq(ig,l,iq) !FL ! $ *(pplev(ig,l)-pplev(ig,l+1)) !FL ! $ *6.022e22/(mmol(iq)*g) !FL ! end do !FL ! end do !FL ! call wstats(ngrid,"c_"//trim(noms(iq)), !FL ! $ "column","mol cm-2",2,colden(1,iq)) !FL end do end if ! of if (thermochem.or.photochem) end if ! of if (tracer) IF(lastcall) THEN write (*,*) "Writing stats..." call mkstats(ierr) ENDIF ENDIF !if callstats c (Store EOF for Mars Climate database software) IF (calleofdump) THEN CALL eofdump(ngrid, nlayer, zu, zv, zt, rho, ps) ENDIF #ifdef MESOSCALE !!! !!! OUTPUT FIELDS !!! wtsurf(1:ngrid) = tsurf(1:ngrid) !! surface temperature wco2ice(1:ngrid) = co2ice(1:ngrid) !! co2 ice mtot(1:ngrid) = mtot(1:ngrid) * 1.e6 / rho_ice !! JF TAU_lay(:)=tau(:,1)!!true opacity (not a reference like tauref) IF (igcm_dust_mass .ne. 0) THEN qsurfice_dust(1:ngrid) = qsurf(1:ngrid,igcm_dust_mass) ENDIF IF (igcm_h2o_ice .ne. 0) THEN qsurfice(1:ngrid) = qsurf(1:ngrid,igcm_h2o_ice) vmr=1.e6 * zq(1:ngrid,1:nlayer,igcm_h2o_ice) . * mugaz / mmol(igcm_h2o_ice) ENDIF !! Dust quantity integration along the vertical axe dustot(:)=0 do ig=1,ngrid do l=1,nlayermx dustot(ig) = dustot(ig) + & zq(ig,l,igcm_dust_mass) & * (pplev(ig,l) - pplev(ig,l+1)) / g enddo enddo c AUTOMATICALLY GENERATED FROM REGISTRY #include "fill_save.inc" #else c ========================================================== c WRITEDIAGFI: Outputs in netcdf file "DIAGFI", containing c any variable for diagnostic (output with period c "ecritphy", set in "run.def") c ========================================================== c WRITEDIAGFI can ALSO be called from any other subroutines c for any variables !! c call WRITEDIAGFI(ngrid,"emis","Surface emissivity","w.m-1",2, c & emis) call WRITEDIAGFI(ngrid,"pplay","Pressure","Pa",3,zplay) ! call WRITEDIAGFI(ngrid,"pplev","Pressure","Pa",3,zplev) call WRITEDIAGFI(ngrid,"tsurf","Surface temperature","K",2, & tsurf) call WRITEDIAGFI(ngrid,"ps","surface pressure","Pa",2,ps) call WRITEDIAGFI(ngrid,"co2ice","co2 ice thickness","kg.m-2",2, & co2ice) c call WRITEDIAGFI(ngrid,"temp7","temperature in layer 7", c & "K",2,zt(1,7)) c call WRITEDIAGFI(ngrid,"fluxsurf_lw","fluxsurf_lw","W.m-2",2, c & fluxsurf_lw) c call WRITEDIAGFI(ngrid,"fluxsurf_sw","fluxsurf_sw","W.m-2",2, c & fluxsurf_sw_tot) c call WRITEDIAGFI(ngrid,"fluxtop_lw","fluxtop_lw","W.m-2",2, c & fluxtop_lw) c call WRITEDIAGFI(ngrid,"fluxtop_sw","fluxtop_sw","W.m-2",2, c & fluxtop_sw_tot) call WRITEDIAGFI(ngrid,"temp","temperature","K",3,zt) call WRITEDIAGFI(ngrid,"u","Zonal wind","m.s-1",3,zu) call WRITEDIAGFI(ngrid,"v","Meridional wind","m.s-1",3,zv) call WRITEDIAGFI(ngrid,"w","Vertical wind","m.s-1",3,pw) call WRITEDIAGFI(ngrid,"rho","density","none",3,rho) c call WRITEDIAGFI(ngrid,"q2","q2","kg.m-3",3,q2) ! call WRITEDIAGFI(ngrid,'Teta','T potentielle','K',3,zh) c call WRITEDIAGFI(ngrid,"pressure","Pressure","Pa",3,pplay) c call WRITEDIAGFI(ngrid,"ssurf","Surface stress","N.m-2",2, c & zstress) c call WRITEDIAGFI(ngridmx,'sw_htrt','sw heat. rate', c & 'w.m-2',3,zdtsw) c call WRITEDIAGFI(ngridmx,'lw_htrt','lw heat. rate', c & 'w.m-2',3,zdtlw) c CALL WRITEDIAGFI(ngridmx,'tauTESap', c & 'tau abs 825 cm-1', c & '',2,tauTES) #ifdef MESOINI call WRITEDIAGFI(ngrid,"emis","Surface emissivity","w.m-1",2, & emis) call WRITEDIAGFI(ngrid,"rho","density","none",3,rho) call WRITEDIAGFI(ngrid,"tsoil","Soil temperature", & "K",3,tsoil) call WRITEDIAGFI(ngrid,"inertiedat","Soil inertia", & "K",3,inertiedat) #endif c ---------------------------------------------------------- c Outputs of the CO2 cycle c ---------------------------------------------------------- if (tracer.and.(igcm_co2.ne.0)) then ! call WRITEDIAGFI(ngrid,"co2_l1","co2 mix. ratio in 1st layer", ! & "kg/kg",2,zq(1,1,igcm_co2)) ! call WRITEDIAGFI(ngrid,"co2","co2 mass mixing ratio", ! & "kg/kg",3,zq(1,1,igcm_co2)) ! Compute co2 column co2col(:)=0 do l=1,nlayermx do ig=1,ngrid co2col(ig)=co2col(ig)+ & zq(ig,l,igcm_co2)*(pplev(ig,l)-pplev(ig,l+1))/g enddo enddo call WRITEDIAGFI(ngrid,"co2col","CO2 column","kg.m-2",2, & co2col) !!!!! FL ! do iq = 1,nq ! if (noms(iq) .ne. "dust_mass" .and. ! $ noms(iq) .ne. "dust_number") then ! call writediagfi(ngrid,"c_"//trim(noms(iq)), ! $ "column","mol cm-2",2,colden(1,iq)) ! end if ! end do !!!!! FL endif ! of if (tracer.and.(igcm_co2.ne.0)) c ---------------------------------------------------------- c Outputs of the water cycle c ---------------------------------------------------------- if (tracer) then if (water) then #ifdef MESOINI !!!! waterice = q01, voir readmeteo.F90 call WRITEDIAGFI(ngridmx,'q01',noms(igcm_h2o_ice), & 'kg/kg',3, & zq(1:ngridmx,1:nlayermx,igcm_h2o_ice)) !!!! watervapor = q02, voir readmeteo.F90 call WRITEDIAGFI(ngridmx,'q02',noms(igcm_h2o_vap), & 'kg/kg',3, & zq(1:ngridmx,1:nlayermx,igcm_h2o_vap)) !!!! surface waterice qsurf02 (voir readmeteo) call WRITEDIAGFI(ngridmx,'qsurf02','surface tracer', & 'kg.m-2',2, & qsurf(1:ngridmx,igcm_h2o_ice)) #endif CALL WRITEDIAGFI(ngridmx,'mtot', & 'total mass of water vapor', & 'kg/m2',2,mtot) CALL WRITEDIAGFI(ngridmx,'icetot', & 'total mass of water ice', & 'kg/m2',2,icetot) c vmr=zq(1:ngridmx,1:nlayermx,igcm_h2o_ice) c & *mugaz/mmol(igcm_h2o_ice) c call WRITEDIAGFI(ngridmx,'vmr_h2oice','h2o ice vmr', c & 'mol/mol',3,vmr) c vmr=zq(1:ngridmx,1:nlayermx,igcm_h2o_vap) c & *mugaz/mmol(igcm_h2o_vap) c call WRITEDIAGFI(ngridmx,'vmr_h2ovap','h2o vap vmr', c & 'mol/mol',3,vmr) c CALL WRITEDIAGFI(ngridmx,'reffice', c & 'Mean reff', c & 'm',2,rave) c call WRITEDIAGFI(ngridmx,'rice','Ice particle size', c & 'm',3,rice) c If activice is true, tauTES is computed in aeropacity.F; if (.not.activice) then CALL WRITEDIAGFI(ngridmx,'tauTESap', & 'tau abs 825 cm-1', & '',2,tauTES) endif call WRITEDIAGFI(ngridmx,'h2o_ice_s', & 'surface h2o_ice', & 'kg.m-2',2,qsurf(1,igcm_h2o_ice)) if (caps) then do ig=1,ngridmx if (watercaptag(ig)) watercapflag(ig) = 1 enddo c CALL WRITEDIAGFI(ngridmx,'watercaptag', c & 'Ice water caps', c & '',2,watercapflag) endif c CALL WRITEDIAGFI(ngridmx,'albedo', c & 'albedo', c & '',2,albedo(1:ngridmx,1)) endif !(water) if (water.and..not.photochem) then iq=nq c write(str2(1:2),'(i2.2)') iq c call WRITEDIAGFI(ngridmx,'dqs'//str2,'dqscloud', c & 'kg.m-2',2,zdqscloud(1,iq)) c call WRITEDIAGFI(ngridmx,'dqch'//str2,'var chim', c & 'kg/kg',3,zdqchim(1,1,iq)) c call WRITEDIAGFI(ngridmx,'dqd'//str2,'var dif', c & 'kg/kg',3,zdqdif(1,1,iq)) c call WRITEDIAGFI(ngridmx,'dqa'//str2,'var adj', c & 'kg/kg',3,zdqadj(1,1,iq)) c call WRITEDIAGFI(ngridmx,'dqc'//str2,'var c', c & 'kg/kg',3,zdqc(1,1,iq)) endif !(water.and..not.photochem) endif c ---------------------------------------------------------- c Outputs of the dust cycle c ---------------------------------------------------------- c call WRITEDIAGFI(ngridmx,'tauref', c & 'Dust ref opt depth','NU',2,tauref) if (tracer.and.(dustbin.ne.0)) then c call WRITEDIAGFI(ngridmx,'tau','taudust','SI',2,tau(1,1)) if (doubleq) then c call WRITEDIAGFI(ngridmx,'qsurf','qsurf', c & 'kg.m-2',2,qsurf(1,igcm_dust_mass)) c call WRITEDIAGFI(ngridmx,'Nsurf','N particles', c & 'N.m-2',2,qsurf(1,igcm_dust_number)) c call WRITEDIAGFI(ngridmx,'dqsdev','ddevil lift', c & 'kg.m-2.s-1',2,zdqsdev(1,1)) c call WRITEDIAGFI(ngridmx,'dqssed','sedimentation', c & 'kg.m-2.s-1',2,zdqssed(1,1)) c call WRITEDIAGFI(ngridmx,'dqsdif','diffusion', c & 'kg.m-2.s-1',2,zdqsdif(1,1)) c call WRITEDIAGFI(ngridmx,'reffdust','reffdust', c & 'm',3,rdust*ref_r0) c call WRITEDIAGFI(ngridmx,'dustq','Dust mass mr', c & 'kg/kg',3,pq(1,1,igcm_dust_mass)) c call WRITEDIAGFI(ngridmx,'dustN','Dust number', c & 'part/kg',3,pq(1,1,igcm_dust_number)) #ifdef MESOINI call WRITEDIAGFI(ngridmx,'dustN','Dust number', & 'part/kg',3,pq(1,1,igcm_dust_number)) #endif else do iq=1,dustbin write(str2(1:2),'(i2.2)') iq call WRITEDIAGFI(ngridmx,'q'//str2,'mix. ratio', & 'kg/kg',3,zq(1,1,iq)) call WRITEDIAGFI(ngridmx,'qsurf'//str2,'qsurf', & 'kg.m-2',2,qsurf(1,iq)) end do endif ! (doubleq) if (scavenging) then call WRITEDIAGFI(ngridmx,'ccnq','CCN mass mr', & 'kg/kg',3,pq(1,1,igcm_ccn_mass)) call WRITEDIAGFI(ngridmx,'ccnN','CCN number', & 'part/kg',3,pq(1,1,igcm_ccn_number)) endif ! (scavenging) c if (submicron) then c call WRITEDIAGFI(ngridmx,'dustsubm','subm mass mr', c & 'kg/kg',3,pq(1,1,igcm_dust_submicron)) c endif ! (submicron) end if ! (tracer.and.(dustbin.ne.0)) c ---------------------------------------------------------- c ---------------------------------------------------------- c PBL OUTPUS c ---------------------------------------------------------- c ---------------------------------------------------------- c ---------------------------------------------------------- c Outputs of surface layer c ---------------------------------------------------------- z_out=0. if (calltherm .and. (z_out .gt. 0.)) then call surflayer_interpol(ngrid,nlayer,z0,g,zzlay,zu,zv,wmax_th & ,tsurf,zh,z_out,Teta_out,u_out,ustar,tstar,L_mo) zu2(:)=sqrt(zu(:,1)*zu(:,1)+zv(:,1)*zv(:,1)) call WRITEDIAGFI(ngridmx,'sqrt(zu2)', & 'horizontal velocity norm','m/s', & 2,zu2) call WRITEDIAGFI(ngridmx,'Teta_out', & 'potential temperature at z_out','K', & 2,Teta_out) call WRITEDIAGFI(ngridmx,'u_out', & 'horizontal velocity norm at z_out','m/s', & 2,u_out) call WRITEDIAGFI(ngridmx,'u*', & 'friction velocity','m/s', & 2,ustar) call WRITEDIAGFI(ngridmx,'teta*', & 'friction potential temperature','K', & 2,tstar) call WRITEDIAGFI(ngrid,'L', & 'Monin Obukhov length','m', & 2,L_mo) else if((.not. calltherm).and.(z_out .gt. 0.)) then print*, 'WARNING : no interpolation in surface-layer :' print*, 'Outputing surface-layer quantities without thermals & does not make sense' endif endif c ---------------------------------------------------------- c Outputs of thermals c ---------------------------------------------------------- if (calltherm) then ! call WRITEDIAGFI(ngrid,'dtke', ! & 'tendance tke thermiques','m**2/s**2', ! & 3,dtke_th) ! call WRITEDIAGFI(ngrid,'d_u_ajs', ! & 'tendance u thermiques','m/s', ! & 3,pdu_th*ptimestep) ! call WRITEDIAGFI(ngrid,'d_v_ajs', ! & 'tendance v thermiques','m/s', ! & 3,pdv_th*ptimestep) ! if (tracer) then ! if (nq .eq. 2) then ! call WRITEDIAGFI(ngrid,'deltaq_th', ! & 'delta q thermiques','kg/kg', ! & 3,ptimestep*pdq_th(:,:,2)) ! endif ! endif call WRITEDIAGFI(ngridmx,'lmax_th', & 'hauteur du thermique','K', & 2,lmax_th_out) call WRITEDIAGFI(ngridmx,'hfmax_th', & 'maximum TH heat flux','K.m/s', & 2,hfmax_th) call WRITEDIAGFI(ngridmx,'wmax_th', & 'maximum TH vertical velocity','m/s', & 2,wmax_th) endif c ---------------------------------------------------------- c ---------------------------------------------------------- c END OF PBL OUTPUS c ---------------------------------------------------------- c ---------------------------------------------------------- c ---------------------------------------------------------- c Output in netcdf file "diagsoil.nc" for subterranean c variables (output every "ecritphy", as for writediagfi) c ---------------------------------------------------------- ! Write soil temperature ! call writediagsoil(ngrid,"soiltemp","Soil temperature","K", ! & 3,tsoil) ! Write surface temperature ! call writediagsoil(ngrid,"tsurf","Surface temperature","K", ! & 2,tsurf) c ========================================================== c END OF WRITEDIAGFI c ========================================================== #endif ELSE ! if(ngrid.eq.1) print*,'Ls =',zls*180./pi, & ' tauref(700 Pa) =',tauref c ---------------------------------------------------------------------- c Output in grads file "g1d" (ONLY when using testphys1d) c (output at every X physical timestep) c ---------------------------------------------------------------------- c c CALL writeg1d(ngrid,1,fluxsurf_lw,'Fs_ir','W.m-2') c CALL writeg1d(ngrid,1,tsurf,'tsurf','K') c CALL writeg1d(ngrid,1,ps,'ps','Pa') c CALL writeg1d(ngrid,nlayer,zt,'T','K') c CALL writeg1d(ngrid,nlayer,pu,'u','m.s-1') c CALL writeg1d(ngrid,nlayer,pv,'v','m.s-1') c CALL writeg1d(ngrid,nlayer,pw,'w','m.s-1') ! THERMALS STUFF 1D z_out=0. if (calltherm .and. (z_out .gt. 0.)) then call surflayer_interpol(ngrid,nlayer,z0,g,zzlay,zu,zv,wmax_th & ,tsurf,zh,z_out,Teta_out,u_out,ustar,tstar,L_mo) zu2(:)=sqrt(zu(:,1)*zu(:,1)+zv(:,1)*zv(:,1)) call WRITEDIAGFI(ngridmx,'sqrt(zu2)', & 'horizontal velocity norm','m/s', & 0,zu2) call WRITEDIAGFI(ngridmx,'Teta_out', & 'potential temperature at z_out','K', & 0,Teta_out) call WRITEDIAGFI(ngridmx,'u_out', & 'horizontal velocity norm at z_out','m/s', & 0,u_out) call WRITEDIAGFI(ngridmx,'u*', & 'friction velocity','m/s', & 0,ustar) call WRITEDIAGFI(ngridmx,'teta*', & 'friction potential temperature','K', & 0,tstar) else if((.not. calltherm).and.(z_out .gt. 0.)) then print*, 'WARNING : no interpolation in surface-layer :' print*, 'Outputing surface-layer quantities without thermals & does not make sense' endif endif if(calltherm) then call WRITEDIAGFI(ngridmx,'lmax_th', & 'hauteur du thermique','point', & 0,lmax_th_out) call WRITEDIAGFI(ngridmx,'hfmax_th', & 'maximum TH heat flux','K.m/s', & 0,hfmax_th) call WRITEDIAGFI(ngridmx,'wmax_th', & 'maximum TH vertical velocity','m/s', & 0,wmax_th) co2col(:)=0. if (tracer) then do l=1,nlayermx do ig=1,ngrid co2col(ig)=co2col(ig)+ & zq(ig,l,1)*(pplev(ig,l)-pplev(ig,l+1))/g enddo enddo end if call WRITEDIAGFI(ngrid,'co2col','integrated co2 mass' & & ,'kg/m-2',0,co2col) endif call WRITEDIAGFI(ngrid,'w','vertical velocity' & & ,'m/s',1,pw) call WRITEDIAGFI(ngrid,"q2","q2","kg.m-3",1,q2) call WRITEDIAGFI(ngrid,"tsurf","Surface temperature","K",0, & tsurf) call WRITEDIAGFI(ngrid,"u","u wind","m/s",1,zu) call WRITEDIAGFI(ngrid,"v","v wind","m/s",1,zv) call WRITEDIAGFI(ngrid,"pplay","Pressure","Pa",1,zplay) call WRITEDIAGFI(ngrid,"pplev","Pressure","Pa",1,zplev) call WRITEDIAGFI(ngrid,"rho","rho","kg.m-3",1,rho) ! or output in diagfi.nc (for testphys1d) call WRITEDIAGFI(ngridmx,'ps','Surface pressure','Pa',0,ps) call WRITEDIAGFI(ngridmx,'temp','Temperature', & 'K',1,zt) if(tracer) then c CALL writeg1d(ngrid,1,tau,'tau','SI') do iq=1,nq c CALL writeg1d(ngrid,nlayer,zq(1,1,iq),noms(iq),'kg/kg') call WRITEDIAGFI(ngridmx,trim(noms(iq)), & trim(noms(iq)),'kg/kg',1,zq(1,1,iq)) end do if (doubleq) then call WRITEDIAGFI(ngridmx,'rdust','rdust', & 'm',1,rdust) endif end if cccccccccccccccccccccc scavenging outputs 1D TN ccccccccccccccccccc ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc IF (scavenging) THEN CALL WRITEDIAGFI(ngridmx,'tauTESap', & 'tau abs 825 cm-1', & '',1,tauTES) h2o_tot = qsurf(1,igcm_h2o_ice) do l=1,nlayer h2o_tot = h2o_tot + & (zq(ig,l,igcm_h2o_vap) + zq(ig,l,igcm_h2o_ice)) & * (pplev(ig,l) - pplev(ig,l+1)) / g ccndust_mass(l) = & pq(1,l,igcm_dust_mass)+pq(1,l,igcm_ccn_mass) ccndust_number(l) = & pq(1,l,igcm_dust_number)+pq(1,l,igcm_ccn_number) end do do iq=1,nq call WRITEDIAGFI(ngridmx,trim(noms(iq))//'_s', & trim(noms(iq))//'_s','kg/kg',0,qsurf(1,iq)) end do call WRITEDIAGFI(ngridmx,'dqssed q','sedimentation q', & 'kg.m-2.s-1',0,zdqssed(:,igcm_dust_number)) call WRITEDIAGFI(ngridmx,'dqsdif q','diffusion q', & 'kg.m-2.s-1',0,zdqsdif(:,igcm_dust_number)) call WRITEDIAGFI(ngridmx,'dqssed N','sedimentation N', & 'kg.m-2.s-1',0,zdqssed(:,igcm_dust_number)) call WRITEDIAGFI(ngridmx,'dqsdif N','diffusion N', & 'kg.m-2.s-1',0,zdqsdif(:,igcm_dust_number)) call WRITEDIAGFI(ngrid,"rice","ice radius","m",1, & rice) ENDIF ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc zlocal(1)=-log(pplay(1,1)/pplev(1,1))* Rnew(1,1)*zt(1,1)/g do l=2,nlayer-1 tmean=zt(1,l) if(zt(1,l).ne.zt(1,l-1)) & tmean=(zt(1,l)-zt(1,l-1))/log(zt(1,l)/zt(1,l-1)) zlocal(l)= zlocal(l-1) & -log(pplay(1,l)/pplay(1,l-1))*rnew(1,l)*tmean/g enddo zlocal(nlayer)= zlocal(nlayer-1)- & log(pplay(1,nlayer)/pplay(1,nlayer-1))* & rnew(1,nlayer)*tmean/g END IF ! if(ngrid.ne.1) icount=icount+1 RETURN END