PROGRAM testphys1d_triton ! to use 'getin' USE ioipsl_getincom use planet_h use comgeomfi_h use comsoil_h IMPLICIT NONE !================================================================== ! ! Purpose ! ------- ! Run the physics package of the universal model in a 1D column. ! ! It can be compiled with a command like (e.g. for 25 layers): ! "makegcm -p pluto -d 25 testphys1d" ! It requires the files "callphys.def", "z2sig.def", ! "traceur.def", and "run1d.def" with a line "INCLUDEDEF=callphys.def" ! ! Authors ! ------- ! Frederic Hourdin ! R. Fournier ! F. Forget ! F. Montmessin (water ice added) !================================================================== #include "dimensions.h" #include "dimphys.h" #include "surfdat.h" !#include "comsoil.h" #include "comdiurn.h" #include "callkeys.h" #include "comcstfi.h" #include "comsaison.h" #include "control.h" #include "comvert.h" #include "netcdf.inc" #include "comg1d.h" #include "fisice.h" #include "logic.h" #include "advtrac.h" c -------------------------------------------------------------- c Declarations c -------------------------------------------------------------- c INTEGER nlayer,nlevel,nsoil,ndt INTEGER ilayer,ilevel,isoil,idt,iq LOGICAl firstcall,lastcall c INTEGER day0 ! date initial (sol ; =0 a Ls=0) INTEGER lecttsoil ! lecture of tsoil from proftsoil INTEGER lecthaze ! lecture of haze from profhaze REAL day ! date durant le run REAL AU ! astronomical unit AU=149 million km REAL time ! time (0 area(1)=1.E+0 c le geopotentiel au sol est inutile en 1D car tout est controle c par la pression de surface ---> phisfi(1)=0.E+0 c "inifis" reproduit un certain nombre d'initialisations deja faites c + lecture des clefs de callphys.def c + calcul de la frequence d'appel au rayonnement c + calcul des sinus et cosinus des longitude latitude ! Possible issue with dtphys in input and include!!! CALL inifis(1,llm,day0,daysec,dtphys, . lati,long,area,rad,g,r,cpp) c Initialisation pour prendre en compte les vents en 1-D c ------------------------------------------------------ ptif=2.E+0*omeg*sinlat(1) c vent geostrophique gru=10. ! default value for gru PRINT *,'zonal eastward component of the geostrophic wind (m/s) ?' call getin("u",gru) write(*,*) " u = ",gru grv=0. !default value for grv PRINT *,'meridional northward component of the geostrophic', &' wind (m/s) ?' call getin("v",grv) write(*,*) " v = ",grv c Initialisation des vents au premier pas de temps DO ilayer=1,nlayer u(ilayer)=gru v(ilayer)=grv ENDDO c energie cinetique turbulente DO ilevel=1,nlevel q2(ilevel)=0.E+0 ENDDO c Surface c ------------------------------------------- if(i_n2.gt.0)then qsurf(i_n2)=0 ! default value for N2ice print*,'Initial N2 ice on the surface (kg.m-2)' call getin("n2ice",qsurf(i_n2)) write(*,*) " n2ice = ",qsurf(i_n2) endif c calcul des pressions et altitudes en utilisant les niveaux sigma c ---------------------------------------------------------------- c Vertical Coordinates c """""""""""""""""""" hybrid=.false. PRINT *,'Hybrid coordinates ?' call getin("hybrid",hybrid) write(*,*) " hybrid = ", hybrid CALL disvert ! we want only the scale height from z2sig, in order to compute zlay open(91,file="z2sig.def",form='formatted') read(91,*) Hscale close(91) DO ilevel=1,nlevel plev(ilevel)=ap(ilevel)+psurf*bp(ilevel) ENDDO DO ilayer=1,nlayer play(ilayer)=aps(ilayer)+psurf*bps(ilayer) ENDDO DO ilayer=1,nlayer ! zlay(ilayer)=-300.E+0 *r*log(play(ilayer)/plev(1)) ! & /g zlay(ilayer)=-1000.0*Hscale*log(play(ilayer)/plev(1)) ENDDO c Orbital parameters c ------------------ PRINT *,'Solar longitude of perihelion Lsperi ' call getin("Lsperi",Lsperi) write(*,*) " Lsperi = ", Lsperi Lsperi = Lsperi * pi/180. ! Ls of perihelion c Calcul du sol correspondant a Lsperi call call_dayperi(Lsperi,excentric,peri_day,year_day) PRINT *,'date of perihelion (sol)',peri_day c Profil de temperature au premier appel c -------------------------------------- pks=psurf**rcp c Altitude en km dans profile: on divise zlay par 1000 tmp1(0)=0.E+0 DO ilayer=1,nlayer tmp1(ilayer)=zlay(ilayer)/1000.E+0 ENDDO call profile(nlayer+1,tmp1,tmp2) tsurf=tmp2(0) DO ilayer=1,nlayer temp(ilayer)=tmp2(ilayer) ENDDO ! Initialize soil properties and temperature ! ------------------------------------------ volcapa=1.e6 ! volumetric heat capacity lecttsoil=0 ! default value for lecttsoil call getin("lecttsoil",lecttsoil) if (lecttsoil==1) then OPEN(14,file='proftsoil',status='old',form='formatted',err=101) DO isoil=1,nsoil READ (14,*) tsoil(isoil) inertiedat(1,isoil)=inertiedat(1,1) ! soil thermal inertia ENDDO GOTO 201 101 STOP'fichier proftsoil inexistant' 201 CONTINUE CLOSE(14) else DO isoil=1,nsoil inertiedat(1,isoil)=inertiedat(1,1) ! soil thermal inertia tsoil(isoil)=tsurf ! soil temperature ENDDO endif ! Initialize depths ! ----------------- do isoil=0,nsoil-1 mlayer(isoil)=2.e-4*(2.**(isoil-0.5)) ! mid-layer depth enddo do isoil=1,nsoil layer(isoil)=2.e-4*(2.**(isoil-1)) ! layer depth enddo c Initialisation pour les sorties GRADS dans "g1d.dat" et "g1d.ctl" c ---------------------------------------------------------------- c (effectuee avec "writeg1d" a partir de "physiq.F" c ou tout autre subroutine physique, y compris celle ci). g1d_nlayer=nlayer g1d_nomfich='g1d.dat' g1d_unitfich=40 g1d_nomctl='g1d.ctl' g1d_unitctl=41 g1d_premier=.true. g2d_premier=.true. ! Initialize haze profile ! ------------------------------------------ if (haze) then lecthaze=0 ! default value for lecthaze call getin("lecthaze",lecthaze) if (lecthaze==1) then OPEN(15,file='profhaze',status='old',form='formatted',err=301) DO iq=1,nq if (iq.eq.i_haze) then DO ilayer=1,nlayer READ (15,*) q(ilayer,iq) ENDDO endif ENDDO GOTO 401 301 STOP'fichier profhaze inexistant' 401 CONTINUE CLOSE(15) endif endif c Ecriture de "startfi" c -------------------- c (Ce fichier sera aussitot relu au premier c appel de "physiq", mais il est necessaire pour passer c les variables purement physiques a "physiq"... call physdem1("startfi.nc",long,lati,nsoilmx,nqmx, . dtphys,float(day0), . time,tsurf,tsoil,emis,q2,qsurf, . area,albedodat,inertiedat,zmea,zstd,zsig,zgam,zthe) c======================================================================= c======================================================================= c======================================================================= c BOUCLE TEMPORELLE DU MODELE 1D c======================================================================= c======================================================================= c======================================================================= firstcall=.true. lastcall=.false. DO idt=1,ndt IF (idt.eq.ndt-day_step-1) then !test lastcall=.true. call solarlong(day*1.0,zls) write(103,*) 'Ls=',zls*180./pi write(103,*) 'Lat=', lati(1)*180./pi write(103,*) 'RunEnd - Atmos. Temp. File' write(103,*) 'RunEnd - Atmos. Temp. File' write(104,*) 'Ls=',zls*180./pi write(104,*) 'Lat=', lati(1) write(104,*) 'RunEnd - Atmos. Temp. File' ENDIF c calcul du geopotentiel c ~~~~~~~~~~~~~~~~~~~~~ DO ilayer=1,nlayer s(ilayer)=(aps(ilayer)/psurf+bps(ilayer))**rcp h(ilayer)=cpp*temp(ilayer)/(pks*s(ilayer)) ENDDO phi(1)=pks*h(1)*(1.E+0-s(1)) DO ilayer=2,nlayer phi(ilayer)=phi(ilayer-1)+ & pks*(h(ilayer-1)+h(ilayer))*.5E+0 & *(s(ilayer-1)-s(ilayer)) ENDDO c appel de la physique c -------------------- CALL physiq (1,llm,nqmx, , firstcall,lastcall, , day,time,dtphys, , plev,play,phi, , u, v,temp, q, , w, C - sorties s du, dv, dtemp, dq,dpsurf,tracerdyn) c evolution du vent : modele 1D c ----------------------------- c la physique calcule les derivees temporelles de u et v. c on y rajoute betement un effet Coriolis. c c DO ilayer=1,nlayer c du(ilayer)=du(ilayer)+ptif*(v(ilayer)-grv) c dv(ilayer)=dv(ilayer)+ptif*(-u(ilayer)+gru) c ENDDO c Pour certain test : pas de coriolis a l'equateur c if(lati(1).eq.0.) then DO ilayer=1,nlayer du(ilayer)=du(ilayer)+ (gru-u(ilayer))/1.e4 dv(ilayer)=dv(ilayer)+ (grv-v(ilayer))/1.e4 ENDDO c end if c c Calcul du temps au pas de temps suivant c --------------------------------------- firstcall=.false. time=time+dtphys/daysec IF (time.gt.1.E+0) then time=time-1.E+0 day=day+1 ENDIF c calcul des vitesses et temperature au pas de temps suivant c ---------------------------------------------------------- DO ilayer=1,nlayer u(ilayer)=u(ilayer)+dtphys*du(ilayer) v(ilayer)=v(ilayer)+dtphys*dv(ilayer) temp(ilayer)=temp(ilayer)+dtphys*dtemp(ilayer) ENDDO c calcul des pressions au pas de temps suivant c ---------------------------------------------------------- psurf=psurf+dtphys*dpsurf ! evolution de la pression de surface DO ilevel=1,nlevel plev(ilevel)=ap(ilevel)+psurf*bp(ilevel) ENDDO DO ilayer=1,nlayer play(ilayer)=aps(ilayer)+psurf*bps(ilayer) ENDDO c calcul traceur au pas de temps suivant c -------------------------------------- DO iq = 1, nqmx DO ilayer=1,nlayer q(ilayer,iq)=q(ilayer,iq)+dtphys*dq(ilayer,iq) ENDDO END DO ENDDO ! fin de la boucle temporelle c ======================================================== c GESTION DES SORTIE c ======================================================== c fermeture pour conclure les sorties format grads dans "g1d.dat" c et "g1d.ctl" (effectuee avec "writeg1d" a partir de "physiq.F" c ou tout autre subroutine physique, y compris celle ci). ! save atm temperature profile if(saveprofile)then OPEN(12,file='profile.out',form='formatted') write(12,*) tsurf DO ilayer=1,nlayermx write(12,*) temp(ilayer) ENDDO CLOSE(12) endif ! save haze profile if (haze.and.lecthaze.eq.1) then OPEN(16,file='profhaze.out',form='formatted') DO iq=1,nq if (iq.eq.i_haze) then DO ilayer=1,nlayer write(16,*) q(ilayer,iq) ENDDO endif ENDDO CLOSE(16) endif ! here we compute altitude CORRECTLY!!! ! print*,'zlay=',zlay/1000. ! rho = play(1)/(R*tsurf) ! zlay(1)=(plev(1)-plev(2))/(g*rho) ! do ilayer=2,nlayer ! rho = play(ilayer)/(R*temp(ilayer)) ! rho = play(ilayer)/(R*230.0) ! dz = (plev(ilayer-1)-plev(ilayer))/(g*rho) ! zlay(ilayer)=zlay(ilayer-1)+dz ! enddo ! print*,'zlay=',zlay/1000. ! stop c CALL endg1d(1,nlayer,zphi/(g*1000.),ndt) do ilayer=1,nlayer zlay(ilayer)=-18.0e3*log(play(ilayer)/psurf) enddo CALL endg1d(1,nlayer,zlay/1000.,ndt) c ======================================================== END c*********************************************************************** c*********************************************************************** c Subroutines Bidons utilise seulement en 3D, mais c necessaire a la compilation de testphys1d en 1-D subroutine gr_fi_dyn RETURN END c*********************************************************************** c*********************************************************************** #include "../dyn3d/disvert.F" #include "call_dayperi.F"