LMDZ
physiq.F90
Go to the documentation of this file.
1 ! $Id: physiq.F 1565 2011-08-31 12:53:29Z jghattas $
2 !#define IO_DEBUG
3 
4  SUBROUTINE physiq (nlon,nlev, &
5  & debut,lafin,jd_cur, jh_cur,pdtphys, &
6  & paprs,pplay,pphi,pphis,presnivs, &
7  & u,v,rot,t,qx, &
8  & flxmass_w, &
9  & d_u, d_v, d_t, d_qx, d_ps &
10  & , dudyn)
11 
12  USE dimphy, only : klon,klev
13  USE infotrac_phy, only : nqtot
14  USE geometry_mod, only : latitude
15  USE comcstphy, only : rg
16  USE iophy, only : histbeg_phy,histwrite_phy
17  USE ioipsl, only : getin,histvert,histdef,histend,ymds2ju
18  USE mod_phys_lmdz_para, only : jj_nb
21 
22 #ifdef CPP_XIOS
23  USE xios, ONLY: xios_update_calendar
24  USE wxios, only: wxios_add_vaxis, wxios_set_timestep, wxios_closedef, &
26 #endif
27 
28  IMPLICIT none
29 !
30 ! Routine argument:
31 !
32  integer,intent(in) :: nlon ! number of atmospheric colums
33  integer,intent(in) :: nlev ! number of vertical levels (should be =klev)
34  real,intent(in) :: jD_cur ! current day number (Julian day)
35  real,intent(in) :: jH_cur ! current time of day (as fraction of day)
36  logical,intent(in) :: debut ! signals first call to physics
37  logical,intent(in) :: lafin ! signals last call to physics
38  real,intent(in) :: pdtphys ! physics time step (s)
39  real,intent(in) :: paprs(klon,klev+1) ! interlayer pressure (Pa)
40  real,intent(in) :: pplay(klon,klev) ! mid-layer pressure (Pa)
41  real,intent(in) :: pphi(klon,klev) ! geopotential at mid-layer
42  real,intent(in) :: pphis(klon) ! surface geopotential
43  real,intent(in) :: presnivs(klev) ! pseudo-pressure (Pa) of mid-layers
44  real,intent(in) :: u(klon,klev) ! eastward zonal wind (m/s)
45  real,intent(in) :: v(klon,klev) ! northward meridional wind (m/s)
46  real,intent(in) :: t(klon,klev) ! temperature (K)
47  real,intent(in) :: qx(klon,klev,nqtot) ! tracers (.../kg_air)
48  real,intent(in) :: flxmass_w(klon,klev) ! vertical mass flux
49  real,intent(out) :: d_u(klon,klev) ! physics tendency on u (m/s/s)
50  real,intent(out) :: d_v(klon,klev) ! physics tendency on v (m/s/s)
51  real,intent(out) :: d_t(klon,klev) ! physics tendency on t (K/s)
52  real,intent(out) :: d_qx(klon,klev,nqtot) ! physics tendency on tracers
53  real,intent(out) :: d_ps(klon) ! physics tendency on surface pressure
54  real,intent(in) :: dudyn(nbp_lon+1,nbp_lat,klev) ! Not used
55  REAL, intent(in):: rot(klon, klev) ! Not used
56  ! relative vorticity, in s-1, needed for frontal waves
57 
58 integer,save :: itau=0 ! counter to count number of calls to physics
59 !$OMP THREADPRIVATE(itau)
60 real :: temp_newton(klon,klev)
61 integer :: k
62 logical, save :: first=.true.
63 !$OMP THREADPRIVATE(first)
64 
65 ! For I/Os
66 integer :: itau0
67 real :: zjulian
68 real :: dtime
69 integer :: nhori ! horizontal coordinate ID
70 integer,save :: nid_hist ! output file ID
71 !$OMP THREADPRIVATE(nid_hist)
72 integer :: zvertid ! vertical coordinate ID
73 integer,save :: iwrite_phys ! output every iwrite_phys physics step
74 !$OMP THREADPRIVATE(iwrite_phys)
75 integer,save :: iwrite_phys_omp ! intermediate variable to read iwrite_phys
76  ! (must be shared by all threads)
77 real :: t_ops ! frequency of the IOIPSL operations (eg average over...)
78 real :: t_wrt ! frequency of the IOIPSL outputs
79 
80 ! initializations
81 if (debut) then ! Things to do only for the first call to physics
82 ! load initial conditions for physics (including the grid)
83  call phys_state_var_init() ! some initializations, required before calling phyetat0
84  call phyetat0("startphy.nc")
85 
86 ! Initialize outputs:
87  itau0=0
88 !$OMP MASTER
89  iwrite_phys_omp=1 !default: output every physics timestep
90  ! NB: getin() is not threadsafe; only one thread should call it.
91  call getin("iwrite_phys",iwrite_phys_omp)
92 !$OMP END MASTER
93 !$OMP BARRIER
94  iwrite_phys=iwrite_phys_omp
95  t_ops=pdtphys*iwrite_phys ! frequency of the IOIPSL operation
96  t_wrt=pdtphys*iwrite_phys ! frequency of the outputs in the file
97  ! compute zjulian for annee0=1979 and month=1 dayref=1 and hour=0.0
98  !CALL ymds2ju(annee0, month, dayref, hour, zjulian)
99  call ymds2ju(1979, 1, 1, 0.0, zjulian)
100  dtime=pdtphys
101 #ifndef CPP_IOIPSL_NO_OUTPUT
102  ! Initialize IOIPSL output file
103  call histbeg_phy("histins.nc",itau0,zjulian,dtime,nhori,nid_hist)
104 #endif
105 
106 !$OMP MASTER
107 
108 #ifndef CPP_IOIPSL_NO_OUTPUT
109 ! IOIPSL
110  ! define vertical coordinate
111  call histvert(nid_hist,"presnivs","Vertical levels","Pa",klev, &
112  presnivs,zvertid,'down')
113  ! define variables which will be written in "histins.nc" file
114  call histdef(nid_hist,'temperature','Atmospheric temperature','K', &
115  nbp_lon,jj_nb,nhori,klev,1,klev,zvertid,32, &
116  'inst(X)',t_ops,t_wrt)
117  call histdef(nid_hist,'u','Eastward Zonal Wind','m/s', &
118  nbp_lon,jj_nb,nhori,klev,1,klev,zvertid,32, &
119  'inst(X)',t_ops,t_wrt)
120  call histdef(nid_hist,'v','Northward Meridional Wind','m/s', &
121  nbp_lon,jj_nb,nhori,klev,1,klev,zvertid,32, &
122  'inst(X)',t_ops,t_wrt)
123  call histdef(nid_hist,'ps','Surface Pressure','Pa', &
124  nbp_lon,jj_nb,nhori,1,1,1,zvertid,32, &
125  'inst(X)',t_ops,t_wrt)
126  ! end definition sequence
127  call histend(nid_hist)
128 #endif
129 
130 #ifdef CPP_XIOS
131 !XIOS
132  ! Declare available vertical axes to be used in output files:
133  !CALL wxios_add_vaxis("presnivs", "dummy-not-used", klev, presnivs)
134  CALL wxios_add_vaxis("presnivs", klev, presnivs)
135 
136  ! Declare time step length (in s):
137  CALL wxios_set_timestep(dtime)
138 
139  !Finalize the context:
140  CALL wxios_closedef()
141 #endif
142 !$OMP END MASTER
143 endif ! of if (debut)
144 
145 ! increment local time counter itau
146 itau=itau+1
147 
148 ! set all tendencies to zero
149 d_u(1:klon,1:klev)=0.
150 d_v(1:klon,1:klev)=0.
151 d_t(1:klon,1:klev)=0.
152 d_qx(1:klon,1:klev,1:nqtot)=0.
153 d_ps(1:klon)=0.
154 
155 ! compute tendencies to return to the dynamics:
156 ! "friction" on the first layer
157 d_u(1:klon,1)=-u(1:klon,1)/86400.
158 d_v(1:klon,1)=-v(1:klon,1)/86400.
159 ! newtonian relaxation towards temp_newton()
160 do k=1,klev
161  temp_newton(1:klon,k)=280.+cos(latitude(1:klon))*40.-pphi(1:klon,k)/rg*6.e-3
162  d_t(1:klon,k)=(temp_newton(1:klon,k)-t(1:klon,k))/1.e5
163 enddo
164 
165 
166 print*,'PHYDEV: itau=',itau
167 
168 ! write some outputs:
169 ! IOIPSL
170 #ifndef CPP_IOIPSL_NO_OUTPUT
171 if (modulo(itau,iwrite_phys)==0) then
172  call histwrite_phy(nid_hist,.false.,"temperature",itau,t)
173  call histwrite_phy(nid_hist,.false.,"u",itau,u)
174  call histwrite_phy(nid_hist,.false.,"v",itau,v)
175  call histwrite_phy(nid_hist,.false.,"ps",itau,paprs(:,1))
176 endif
177 #endif
178 
179 !XIOS
180 #ifdef CPP_XIOS
181 !$OMP MASTER
182  !Increment XIOS time
183  CALL xios_update_calendar(itau)
184 !$OMP END MASTER
185 !$OMP BARRIER
186 
187  !Send fields to XIOS: (NB these fields must also be defined as
188  ! <field id="..." /> in iodef.xml to be correctly used
189  CALL histwrite_phy("temperature",t)
190  CALL histwrite_phy("temp_newton",temp_newton)
191  CALL histwrite_phy("u",u)
192  CALL histwrite_phy("v",v)
193  CALL histwrite_phy("ps",paprs(:,1))
194 #endif
195 
196 ! if lastcall, then it is time to write "restartphy.nc" file
197 if (lafin) then
198  call phyredem("restartphy.nc")
199 endif
200 
201 end subroutine physiq
!$Id zjulian!correction pour l heure initiale!jyg!jyg CALL ymds2ju(annee_ref, 1, day_ref, hour, zjulian)!jyg CALL histbeg_phy("histrac"
integer, save klon
Definition: dimphy.F90:3
subroutine phyredem(fichnom)
Definition: phyredem.F90:5
integer, save klev
Definition: dimphy.F90:7
!$Id presnivs(llm)
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL false
Definition: calcul_STDlev.h:26
!$Id zjulian!correction pour l heure initiale!jyg!jyg CALL nid_tra CALL histvert(nid_tra,"presnivs","Vertical levels","Pa", klev, presnivs, nvert,"down") zsto
subroutine physiq(nlon, nlev, debut, lafin, jD_cur, jH_cur, pdtphys, paprs, pplay, pphi, pphis, presnivs, u, v, rot, t, qx, flxmass_w, d_u, d_v, d_t, d_qx, d_ps, dudyn)
Definition: physiq.F90:11
integer, save nqtot
Definition: infotrac_phy.F90:8
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL pplay
Definition: calcul_STDlev.h:26
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL ulevSTD CALL &zphi philevSTD CALL &zx_rh rhlevSTD!DO klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon du jour ou toutes les read_climoz CALL &zphi geo500!IM on interpole a chaque pas de temps le paprs
subroutine histbeg_phy(name, itau0, zjulian, dtime, nhori, nid_day)
Definition: iophy.F90:159
real rg
Definition: comcstphy.F90:5
!$Id Turb_fcg_gcssold get_uvd hqturb_gcssold endif!large scale llm day day1 day day1 *dt_toga endif!time annee_ref dt_toga u_toga vq_toga w_prof vq_prof llm u(l)
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL ulevSTD CALL &zphi philevSTD CALL &zx_rh rhlevSTD!DO klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon du jour ou toutes les read_climoz CALL true
!$Id zjulian!correction pour l heure initiale!jyg!jyg CALL pdtphys
Definition: ini_histrac.h:11
subroutine phys_state_var_init()
subroutine phyetat0(fichnom)
Definition: phyetat0.F90:5
Definition: dimphy.F90:1
Definition: iophy.F90:4
real, dimension(:), allocatable, save latitude
Definition: geometry_mod.F90:8