source: LMDZ5/trunk/libf/phydev/physiq_mod.F90 @ 2569

Last change on this file since 2569 was 2422, checked in by Ehouarn Millour, 8 years ago

Small modification in the way time and calendar are handled: Now all the time keeping is done in the physics and only the timestep is transfered from the dynamics to the physics. Due to changes in computations and roundoffs this will change reference bench results.
The implementation of this change in phymar is left as future work.
EM

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
File size: 6.8 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_timestep, wxios_closedef, &
28                       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
77
78! initializations
79if (debut) then ! Things to do only for the first call to physics
80! load initial conditions for physics (including the grid)
81  call phys_state_var_init() ! some initializations, required before calling phyetat0
82  call phyetat0("startphy.nc")
83
84! Initialize outputs:
85  itau0=0
86!$OMP MASTER
87  iwrite_phys_omp=1 !default: output every physics timestep
88  ! NB: getin() is not threadsafe; only one thread should call it.
89  call getin("iwrite_phys",iwrite_phys_omp)
90!$OMP END MASTER
91!$OMP BARRIER
92  iwrite_phys=iwrite_phys_omp
93  t_ops=pdtphys*iwrite_phys ! frequency of the IOIPSL operation
94  t_wrt=pdtphys*iwrite_phys ! frequency of the outputs in the file
95  ! compute zjulian for annee0=1979 and month=1 dayref=1 and hour=0.0
96  !CALL ymds2ju(annee0, month, dayref, hour, zjulian)
97  call ymds2ju(1979, 1, 1, 0.0, zjulian)
98  dtime=pdtphys
99#ifndef CPP_IOIPSL_NO_OUTPUT
100  ! Initialize IOIPSL output file
101  call histbeg_phy("histins.nc",itau0,zjulian,dtime,nhori,nid_hist)
102#endif
103
104!$OMP MASTER
105
106#ifndef CPP_IOIPSL_NO_OUTPUT
107! IOIPSL
108  ! define vertical coordinate
109  call histvert(nid_hist,"presnivs","Vertical levels","Pa",klev, &
110                presnivs,zvertid,'down')
111  ! define variables which will be written in "histins.nc" file
112  call histdef(nid_hist,'temperature','Atmospheric temperature','K', &
113               nbp_lon,jj_nb,nhori,klev,1,klev,zvertid,32, &
114               'inst(X)',t_ops,t_wrt)
115  call histdef(nid_hist,'u','Eastward Zonal Wind','m/s', &
116               nbp_lon,jj_nb,nhori,klev,1,klev,zvertid,32, &
117               'inst(X)',t_ops,t_wrt)
118  call histdef(nid_hist,'v','Northward Meridional Wind','m/s', &
119               nbp_lon,jj_nb,nhori,klev,1,klev,zvertid,32, &
120               'inst(X)',t_ops,t_wrt)
121  call histdef(nid_hist,'ps','Surface Pressure','Pa', &
122               nbp_lon,jj_nb,nhori,1,1,1,zvertid,32, &
123               'inst(X)',t_ops,t_wrt)
124  ! end definition sequence
125  call histend(nid_hist)
126#endif
127
128#ifdef CPP_XIOS
129!XIOS
130    ! Declare available vertical axes to be used in output files:   
131    !CALL wxios_add_vaxis("presnivs", "dummy-not-used", klev, presnivs)
132    CALL wxios_add_vaxis("presnivs", klev, presnivs)
133
134    ! Declare time step length (in s):
135    CALL wxios_set_timestep(dtime)
136
137    !Finalize the context:
138    CALL wxios_closedef()
139#endif
140!$OMP END MASTER
141endif ! of if (debut)
142
143! increment local time counter itau
144itau=itau+1
145
146! set all tendencies to zero
147d_u(1:klon,1:klev)=0.
148d_v(1:klon,1:klev)=0.
149d_t(1:klon,1:klev)=0.
150d_qx(1:klon,1:klev,1:nqtot)=0.
151d_ps(1:klon)=0.
152
153! compute tendencies to return to the dynamics:
154! "friction" on the first layer
155d_u(1:klon,1)=-u(1:klon,1)/86400.
156d_v(1:klon,1)=-v(1:klon,1)/86400.
157! newtonian relaxation towards temp_newton()
158do k=1,klev
159  temp_newton(1:klon,k)=280.+cos(latitude(1:klon))*40.-pphi(1:klon,k)/rg*6.e-3
160  d_t(1:klon,k)=(temp_newton(1:klon,k)-t(1:klon,k))/1.e5
161enddo
162
163
164print*,'PHYDEV: itau=',itau
165
166! write some outputs:
167! IOIPSL
168#ifndef CPP_IOIPSL_NO_OUTPUT
169if (modulo(itau,iwrite_phys)==0) then
170  call histwrite_phy(nid_hist,.false.,"temperature",itau,t)
171  call histwrite_phy(nid_hist,.false.,"u",itau,u)
172  call histwrite_phy(nid_hist,.false.,"v",itau,v)
173  call histwrite_phy(nid_hist,.false.,"ps",itau,paprs(:,1))
174endif
175#endif
176
177!XIOS
178#ifdef CPP_XIOS
179!$OMP MASTER
180    !Increment XIOS time
181    CALL xios_update_calendar(itau)
182!$OMP END MASTER
183!$OMP BARRIER
184
185    !Send fields to XIOS: (NB these fields must also be defined as
186    ! <field id="..." /> in iodef.xml to be correctly used
187    CALL histwrite_phy("temperature",t)
188    CALL histwrite_phy("temp_newton",temp_newton)
189    CALL histwrite_phy("u",u)
190    CALL histwrite_phy("v",v)
191    CALL histwrite_phy("ps",paprs(:,1))
192#endif
193
194! if lastcall, then it is time to write "restartphy.nc" file
195if (lafin) then
196  call phyredem("restartphy.nc")
197endif
198
199end subroutine physiq
200
201END MODULE physiq_mod
Note: See TracBrowser for help on using the repository browser.