source: LMDZ5/trunk/libf/phydev/physiq.F90 @ 2351

Last change on this file since 2351 was 2351, checked in by Ehouarn Millour, 9 years ago

More on physics/dynamics separation and cleanup:

  • Set things up so that all physics-related initializations are done via iniphysiq.
  • Created a "geometry_mod.F90" module in phy_common to store information on the loacl grid (i.e. replaces comgeomphy) and moreover give these variables more obvious names (e.g.: rlond => longitude, rlatd => latitude, airephy => cell_area).
  • removed obsolete comgeomphy.h and comgeomphy.F90

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: 7.1 KB
Line 
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
19      USE phys_state_var_mod, only : phys_state_var_init
20      USE mod_grid_phy_lmdz, ONLY: nbp_lon,nbp_lat
21
22#ifdef CPP_XIOS
23      USE xios, ONLY: xios_update_calendar
24      USE wxios, only: wxios_add_vaxis, wxios_set_timestep, wxios_closedef, &
25                       histwrite_phy
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
58integer,save :: itau=0 ! counter to count number of calls to physics
59!$OMP THREADPRIVATE(itau)
60real :: temp_newton(klon,klev)
61integer :: k
62logical, save :: first=.true.
63!$OMP THREADPRIVATE(first)
64
65! For I/Os
66integer :: itau0
67real :: zjulian
68real :: dtime
69integer :: nhori ! horizontal coordinate ID
70integer,save :: nid_hist ! output file ID
71!$OMP THREADPRIVATE(nid_hist)
72integer :: zvertid ! vertical coordinate ID
73integer,save :: iwrite_phys ! output every iwrite_phys physics step
74!$OMP THREADPRIVATE(iwrite_phys)
75integer,save :: iwrite_phys_omp ! intermediate variable to read iwrite_phys
76                                ! (must be shared by all threads)
77real :: t_ops ! frequency of the IOIPSL operations (eg average over...)
78real :: t_wrt ! frequency of the IOIPSL outputs
79
80! initializations
81if (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
143endif ! of if (debut)
144
145! increment local time counter itau
146itau=itau+1
147
148! set all tendencies to zero
149d_u(1:klon,1:klev)=0.
150d_v(1:klon,1:klev)=0.
151d_t(1:klon,1:klev)=0.
152d_qx(1:klon,1:klev,1:nqtot)=0.
153d_ps(1:klon)=0.
154
155! compute tendencies to return to the dynamics:
156! "friction" on the first layer
157d_u(1:klon,1)=-u(1:klon,1)/86400.
158d_v(1:klon,1)=-v(1:klon,1)/86400.
159! newtonian relaxation towards temp_newton()
160do 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
163enddo
164
165
166print*,'PHYDEV: itau=',itau
167
168! write some outputs:
169! IOIPSL
170#ifndef CPP_IOIPSL_NO_OUTPUT
171if (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))
176endif
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
197if (lafin) then
198  call phyredem("restartphy.nc")
199endif
200
201end subroutine physiq
Note: See TracBrowser for help on using the repository browser.