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

Last change on this file since 2002 was 2002, checked in by Ehouarn Millour, 10 years ago

Further cleanup concerning XIOS (mainly about axes being defined as axes and not as groups of axes).
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.3 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,clesphy0, &
7     &            u,v,t,qx, &
8     &            flxmass_w, &
9     &            d_u, d_v, d_t, d_qx, d_ps &
10     &            , dudyn &
11     &            , PVteta)
12
13      USE dimphy, only : klon,klev
14      USE infotrac, only : nqtot
15      USE comgeomphy, only : rlatd
16      USE comcstphy, only : rg
17      USE iophy, only : histbeg_phy,histwrite_phy
18      USE ioipsl, only : getin,histvert,histdef,histend,ymds2ju
19      USE mod_phys_lmdz_para, only : jj_nb
20      USE phys_state_var_mod, only : phys_state_var_init
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#include "dimensions.h"
30
31      integer,parameter :: jjmp1=jjm+1-1/jjm
32      integer,parameter :: iip1=iim+1
33!
34! Routine argument:
35!
36      integer,intent(in) :: nlon ! number of atmospheric colums
37      integer,intent(in) :: nlev ! number of vertical levels (should be =klev)
38      real,intent(in) :: jD_cur ! current day number (Julian day)
39      real,intent(in) :: jH_cur ! current time of day (as fraction of day)
40      logical,intent(in) :: debut ! signals first call to physics
41      logical,intent(in) :: lafin ! signals last call to physics
42      real,intent(in) :: pdtphys ! physics time step (s)
43      real,intent(in) :: paprs(klon,klev+1) ! interlayer pressure (Pa)
44      real,intent(in) :: pplay(klon,klev) ! mid-layer pressure (Pa)
45      real,intent(in) :: pphi(klon,klev) ! geopotential at mid-layer
46      real,intent(in) :: pphis(klon) ! surface geopotential
47      real,intent(in) :: presnivs(klev) ! pseudo-pressure (Pa) of mid-layers
48      integer,parameter :: longcles=20
49      real,intent(in) :: clesphy0(longcles) ! Not used
50      real,intent(in) :: u(klon,klev) ! eastward zonal wind (m/s)
51      real,intent(in) :: v(klon,klev) ! northward meridional wind (m/s)
52      real,intent(in) :: t(klon,klev) ! temperature (K)
53      real,intent(in) :: qx(klon,klev,nqtot) ! tracers (.../kg_air)
54      real,intent(in) :: flxmass_w(klon,klev) ! vertical mass flux
55      real,intent(out) :: d_u(klon,klev) ! physics tendency on u (m/s/s)
56      real,intent(out) :: d_v(klon,klev) ! physics tendency on v (m/s/s)
57      real,intent(out) :: d_t(klon,klev) ! physics tendency on t (K/s)
58      real,intent(out) :: d_qx(klon,klev,nqtot) ! physics tendency on tracers
59      real,intent(out) :: d_ps(klon) ! physics tendency on surface pressure
60      real,intent(in) :: dudyn(iim+1,jjmp1,klev) ! Not used
61!FH! REAL PVteta(klon,nbteta)
62!      REAL PVteta(klon,1)
63      real,intent(in) :: PVteta(klon,3) ! Not used ; should match definition
64                                        ! in calfis.F
65
66integer,save :: itau=0 ! counter to count number of calls to physics
67!$OMP THREADPRIVATE(itau)
68real :: temp_newton(klon,klev)
69integer :: k
70logical, save :: first=.true.
71!$OMP THREADPRIVATE(first)
72
73! For I/Os
74integer :: itau0
75real :: zjulian
76real :: dtime
77integer :: nhori ! horizontal coordinate ID
78integer,save :: nid_hist ! output file ID
79!$OMP THREADPRIVATE(nid_hist)
80integer :: zvertid ! vertical coordinate ID
81integer,save :: iwrite_phys ! output every iwrite_phys physics step
82!$OMP THREADPRIVATE(iwrite_phys)
83integer,save :: iwrite_phys_omp ! intermediate variable to read iwrite_phys
84                                ! (must be shared by all threads)
85real :: t_ops ! frequency of the IOIPSL operations (eg average over...)
86real :: t_wrt ! frequency of the IOIPSL outputs
87
88! initializations
89if (debut) then ! Things to do only for the first call to physics
90! load initial conditions for physics (including the grid)
91  call phys_state_var_init() ! some initializations, required before calling phyetat0
92  call phyetat0("startphy.nc")
93
94! Initialize outputs:
95  itau0=0
96!$OMP MASTER
97  iwrite_phys_omp=1 !default: output every physics timestep
98  ! NB: getin() is not threadsafe; only one thread should call it.
99  call getin("iwrite_phys",iwrite_phys_omp)
100!$OMP END MASTER
101!$OMP BARRIER
102  iwrite_phys=iwrite_phys_omp
103  t_ops=pdtphys*iwrite_phys ! frequency of the IOIPSL operation
104  t_wrt=pdtphys*iwrite_phys ! frequency of the outputs in the file
105  ! compute zjulian for annee0=1979 and month=1 dayref=1 and hour=0.0
106  !CALL ymds2ju(annee0, month, dayref, hour, zjulian)
107  call ymds2ju(1979, 1, 1, 0.0, zjulian)
108  dtime=pdtphys
109#ifndef CPP_NO_IOIPSL
110  ! Initialize IOIPSL output file
111  call histbeg_phy("histins.nc",itau0,zjulian,dtime,nhori,nid_hist)
112#endif
113
114!$OMP MASTER
115
116#ifndef CPP_NO_IOIPSL
117! IOIPSL
118  ! define vertical coordinate
119  call histvert(nid_hist,"presnivs","Vertical levels","Pa",klev, &
120                presnivs,zvertid,'down')
121  ! define variables which will be written in "histins.nc" file
122  call histdef(nid_hist,'temperature','Atmospheric temperature','K', &
123               iim,jj_nb,nhori,klev,1,klev,zvertid,32, &
124               'inst(X)',t_ops,t_wrt)
125  call histdef(nid_hist,'u','Eastward Zonal Wind','m/s', &
126               iim,jj_nb,nhori,klev,1,klev,zvertid,32, &
127               'inst(X)',t_ops,t_wrt)
128  call histdef(nid_hist,'v','Northward Meridional Wind','m/s', &
129               iim,jj_nb,nhori,klev,1,klev,zvertid,32, &
130               'inst(X)',t_ops,t_wrt)
131  call histdef(nid_hist,'ps','Surface Pressure','Pa', &
132               iim,jj_nb,nhori,1,1,1,zvertid,32, &
133               'inst(X)',t_ops,t_wrt)
134  ! end definition sequence
135  call histend(nid_hist)
136#endif
137
138#ifdef CPP_XIOS
139!XIOS
140    ! Declare available vertical axes to be used in output files:   
141    !CALL wxios_add_vaxis("presnivs", "dummy-not-used", klev, presnivs)
142    CALL wxios_add_vaxis("presnivs", klev, presnivs)
143
144    ! Declare time step length (in s):
145    CALL wxios_set_timestep(dtime)
146
147    !Finalize the context:
148    CALL wxios_closedef()
149#endif
150!$OMP END MASTER
151endif ! of if (debut)
152
153! increment local time counter itau
154itau=itau+1
155
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(rlatd(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
173
174print*,'PHYDEV: itau=',itau
175
176! write some outputs:
177! IOIPSL
178#ifndef CPP_NO_IOIPSL
179if (modulo(itau,iwrite_phys)==0) then
180  call histwrite_phy(nid_hist,.false.,"temperature",itau,t)
181  call histwrite_phy(nid_hist,.false.,"u",itau,u)
182  call histwrite_phy(nid_hist,.false.,"v",itau,v)
183  call histwrite_phy(nid_hist,.false.,"ps",itau,paprs(:,1))
184endif
185#endif
186
187!XIOS
188#ifdef CPP_XIOS
189!$OMP MASTER
190    !Increment XIOS time
191    CALL xios_update_calendar(itau)
192!$OMP END MASTER
193!$OMP BARRIER
194
195    !Send fields to XIOS: (NB these fields must also be defined as
196    ! <field id="..." /> in iodef.xml to be correctly used
197    CALL histwrite_phy("temperature",t)
198    CALL histwrite_phy("temp_newton",temp_newton)
199    CALL histwrite_phy("u",u)
200    CALL histwrite_phy("v",v)
201    CALL histwrite_phy("ps",paprs(:,1))
202#endif
203
204! if lastcall, then it is time to write "restartphy.nc" file
205if (lafin) then
206  call phyredem("restartphy.nc")
207endif
208
209end subroutine physiq
Note: See TracBrowser for help on using the repository browser.