source: dynamico_lmdz/simple_physics/phyparam/param/physiq_mod.F90 @ 4204

Last change on this file since 4204 was 4178, checked in by dubos, 5 years ago

simple_physics : reorganization

File size: 7.3 KB
Line 
1! $Id: physiq.F 1565 2011-08-31 12:53:29Z jghattas $
2MODULE physiq_mod
3
4IMPLICIT NONE
5
6CONTAINS
7
8      SUBROUTINE physiq (nlon,nlev, &
9     &            debut,lafin,pdtphys, &
10     &            paprs,pplay,pphi,pphis,presnivs, &
11     &            u,v,t,qx, &
12     &            flxmass_w, &
13     &            d_u, d_v, d_t, d_qx, d_ps)
14
15      USE dimphy, only : klon,klev
16      USE infotrac_phy, only : nqtot
17      USE geometry_mod, only : latitude
18      USE comcstphy, only : rg
19      USE iophy, only : histbeg_phy,histwrite_phy
20      USE ioipsl, only : getin,histvert,histdef,histend,ymds2ju
21      USE mod_phys_lmdz_para, only : jj_nb
22      USE phys_state_var_mod, only : phys_state_var_init
23      USE mod_grid_phy_lmdz, ONLY: nbp_lon,nbp_lat
24
25#ifdef CPP_XIOS
26      USE xios, ONLY: xios_update_calendar
27      USE wxios, only: wxios_add_vaxis, wxios_set_cal, wxios_closedef
28      USE iophy, ONLY: histwrite_phy
29#endif
30
31      IMPLICIT none
32!
33! Routine argument:
34!
35      integer,intent(in) :: nlon ! number of atmospheric colums
36      integer,intent(in) :: nlev ! number of vertical levels (should be =klev)
37      logical,intent(in) :: debut ! signals first call to physics
38      logical,intent(in) :: lafin ! signals last call to physics
39      real,intent(in) :: pdtphys ! physics time step (s)
40      real,intent(in) :: paprs(klon,klev+1) ! interlayer pressure (Pa)
41      real,intent(in) :: pplay(klon,klev) ! mid-layer pressure (Pa)
42      real,intent(in) :: pphi(klon,klev) ! geopotential at mid-layer
43      real,intent(in) :: pphis(klon) ! surface geopotential
44      real,intent(in) :: presnivs(klev) ! pseudo-pressure (Pa) of mid-layers
45      real,intent(in) :: u(klon,klev) ! eastward zonal wind (m/s)
46      real,intent(in) :: v(klon,klev) ! northward meridional wind (m/s)
47      real,intent(in) :: t(klon,klev) ! temperature (K)
48      real,intent(in) :: qx(klon,klev,nqtot) ! tracers (.../kg_air)
49      real,intent(in) :: flxmass_w(klon,klev) ! vertical mass flux
50      real,intent(out) :: d_u(klon,klev) ! physics tendency on u (m/s/s)
51      real,intent(out) :: d_v(klon,klev) ! physics tendency on v (m/s/s)
52      real,intent(out) :: d_t(klon,klev) ! physics tendency on t (K/s)
53      real,intent(out) :: d_qx(klon,klev,nqtot) ! physics tendency on tracers
54      real,intent(out) :: d_ps(klon) ! physics tendency on surface pressure
55
56integer,save :: itau=0 ! counter to count number of calls to physics
57!$OMP THREADPRIVATE(itau)
58real :: temp_newton(klon,klev)
59integer :: k
60logical, save :: first=.true.
61!$OMP THREADPRIVATE(first)
62
63! For I/Os
64integer :: itau0
65real :: zjulian
66real :: dtime
67integer :: nhori ! horizontal coordinate ID
68integer,save :: nid_hist ! output file ID
69!$OMP THREADPRIVATE(nid_hist)
70integer :: zvertid ! vertical coordinate ID
71integer,save :: iwrite_phys ! output every iwrite_phys physics step
72!$OMP THREADPRIVATE(iwrite_phys)
73integer,save :: iwrite_phys_omp ! intermediate variable to read iwrite_phys
74                                ! (must be shared by all threads)
75real :: t_ops ! frequency of the IOIPSL operations (eg average over...)
76real :: t_wrt ! frequency of the IOIPSL outputs
77REAL,SAVE :: rjourvrai=0.
78REAL,SAVE :: gmtime=0.
79!$OMP THREADPRIVATE(rjourvrai,gmtime)
80
81
82! initializations
83if (debut) then ! Things to do only for the first call to physics
84! load initial conditions for physics (including the grid)
85  call phys_state_var_init() ! some initializations, required before calling phyetat0
86  call phyetat0("startphy.nc")
87
88! Initialize outputs:
89  itau0=0
90!$OMP MASTER
91  iwrite_phys_omp=1 !default: output every physics timestep
92  ! NB: getin() is not threadsafe; only one thread should call it.
93  call getin("iwrite_phys",iwrite_phys_omp)
94!$OMP END MASTER
95!$OMP BARRIER
96  iwrite_phys=iwrite_phys_omp
97  t_ops=pdtphys*iwrite_phys ! frequency of the IOIPSL operation
98  t_wrt=pdtphys*iwrite_phys ! frequency of the outputs in the file
99  ! compute zjulian for annee0=1979 and month=1 dayref=1 and hour=0.0
100  !CALL ymds2ju(annee0, month, dayref, hour, zjulian)
101  call ymds2ju(1979, 1, 1, 0.0, zjulian)
102  dtime=pdtphys
103#ifndef CPP_IOIPSL_NO_OUTPUT
104  ! Initialize IOIPSL output file
105  call histbeg_phy("histins.nc",itau0,zjulian,dtime,nhori,nid_hist)
106#endif
107
108!$OMP MASTER
109
110#ifndef CPP_IOIPSL_NO_OUTPUT
111! IOIPSL
112  ! define vertical coordinate
113  call histvert(nid_hist,"presnivs","Vertical levels","Pa",klev, &
114                presnivs,zvertid,'down')
115  ! define variables which will be written in "histins.nc" file
116  call histdef(nid_hist,'temperature','Atmospheric temperature','K', &
117               nbp_lon,jj_nb,nhori,klev,1,klev,zvertid,32, &
118               'inst(X)',t_ops,t_wrt)
119  call histdef(nid_hist,'u','Eastward Zonal Wind','m/s', &
120               nbp_lon,jj_nb,nhori,klev,1,klev,zvertid,32, &
121               'inst(X)',t_ops,t_wrt)
122  call histdef(nid_hist,'v','Northward Meridional Wind','m/s', &
123               nbp_lon,jj_nb,nhori,klev,1,klev,zvertid,32, &
124               'inst(X)',t_ops,t_wrt)
125  call histdef(nid_hist,'ps','Surface Pressure','Pa', &
126               nbp_lon,jj_nb,nhori,1,1,1,zvertid,32, &
127               'inst(X)',t_ops,t_wrt)
128  ! end definition sequence
129  call histend(nid_hist)
130#endif
131
132#ifdef CPP_XIOS
133!XIOS
134    ! Declare available vertical axes to be used in output files:   
135    CALL wxios_add_vaxis("presnivs", klev, presnivs)
136
137    ! Declare calendar and time step
138    CALL wxios_set_cal(dtime,"earth_360d",1,1,1,0.0,1,1,1,0.0)
139   
140    !Finalize the context:
141    CALL wxios_closedef()
142#endif
143!$OMP END MASTER
144!$OMP BARRIER
145endif ! of if (debut)
146
147! increment local time counter itau
148itau=itau+1
149gmtime=gmtime+pdtphys/86400.
150IF (gmtime>=1.) THEN
151   gmtime=gmtime-1.
152   rjourvrai=rjourvrai+1.
153ENDIF
154
155IF ( 1 == 0 ) THEN
156! set all tendencies to zero
157d_u(1:klon,1:klev)=0.
158d_v(1:klon,1:klev)=0.
159d_t(1:klon,1:klev)=0.
160d_qx(1:klon,1:klev,1:nqtot)=0.
161d_ps(1:klon)=0.
162
163! compute tendencies to return to the dynamics:
164! "friction" on the first layer
165d_u(1:klon,1)=-u(1:klon,1)/86400.
166d_v(1:klon,1)=-v(1:klon,1)/86400.
167! newtonian relaxation towards temp_newton()
168do k=1,klev
169  temp_newton(1:klon,k)=280.+cos(latitude(1:klon))*40.-pphi(1:klon,k)/rg*6.e-3
170  d_t(1:klon,k)=(temp_newton(1:klon,k)-t(1:klon,k))/1.e5
171enddo
172
173ELSE
174
175      CALL phyparam(klon,klev,nqtot, &
176                  debut,lafin, &
177                  rjourvrai,gmtime,pdtphys, &
178                  paprs,pplay,pphi,pphis,presnivs, &
179                  u,v,t,qx, &
180                  flxmass_w, &
181                  d_u,d_v,d_t,d_qx,d_ps)
182
183
184ENDIF
185
186
187print*,'PHYDEV: itau=',itau
188
189! write some outputs:
190! IOIPSL
191#ifndef CPP_IOIPSL_NO_OUTPUT
192if (modulo(itau,iwrite_phys)==0) then
193  call histwrite_phy(nid_hist,.false.,"temperature",itau,t)
194  call histwrite_phy(nid_hist,.false.,"u",itau,u)
195  call histwrite_phy(nid_hist,.false.,"v",itau,v)
196  call histwrite_phy(nid_hist,.false.,"ps",itau,paprs(:,1))
197endif
198#endif
199
200!XIOS
201#ifdef CPP_XIOS
202!$OMP MASTER
203    !Increment XIOS time
204    CALL xios_update_calendar(itau)
205!$OMP END MASTER
206!$OMP BARRIER
207
208    !Send fields to XIOS: (NB these fields must also be defined as
209    ! <field id="..." /> in iodef.xml to be correctly used
210    CALL histwrite_phy("temperature",t)
211    CALL histwrite_phy("temp_newton",temp_newton)
212    CALL histwrite_phy("u",u)
213    CALL histwrite_phy("v",v)
214    CALL histwrite_phy("ps",paprs(:,1))
215#endif
216
217! if lastcall, then it is time to write "restartphy.nc" file
218if (lafin) then
219  call phyredem("restartphy.nc")
220endif
221
222end subroutine physiq
223
224END MODULE physiq_mod
Note: See TracBrowser for help on using the repository browser.