source: LMDZ5/branches/testing/libf/phydev/physiq.F90 @ 1885

Last change on this file since 1885 was 1864, checked in by Laurent Fairhead, 11 years ago

Création d'une nouvelle testing:

merge des modifications du trunk entre r1796 et r1860


New testing version

merged modifications between r1796 and r1860 from the trunk

i.e.
svn merge -r1796:1860 http://svn.lmd.jussieu.fr/LMDZ/LMDZ5/trunk

File size: 6.8 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 wxios
24#endif
25
26      IMPLICIT none
27#include "dimensions.h"
28
29      integer,parameter :: jjmp1=jjm+1-1/jjm
30      integer,parameter :: iip1=iim+1
31!
32! Routine argument:
33!
34      integer,intent(in) :: nlon ! number of atmospheric colums
35      integer,intent(in) :: nlev ! number of vertical levels (should be =klev)
36      real,intent(in) :: jD_cur ! current day number (Julian day)
37      real,intent(in) :: jH_cur ! current time of day (as fraction of day)
38      logical,intent(in) :: debut ! signals first call to physics
39      logical,intent(in) :: lafin ! signals last call to physics
40      real,intent(in) :: pdtphys ! physics time step (s)
41      real,intent(in) :: paprs(klon,klev+1) ! interlayer pressure (Pa)
42      real,intent(in) :: pplay(klon,klev) ! mid-layer pressure (Pa)
43      real,intent(in) :: pphi(klon,klev) ! geopotential at mid-layer
44      real,intent(in) :: pphis(klon) ! surface geopotential
45      real,intent(in) :: presnivs(klev) ! pseudo-pressure (Pa) of mid-layers
46      integer,parameter :: longcles=20
47      real,intent(in) :: clesphy0(longcles) ! Not used
48      real,intent(in) :: u(klon,klev) ! eastward zonal wind (m/s)
49      real,intent(in) :: v(klon,klev) ! northward meridional wind (m/s)
50      real,intent(in) :: t(klon,klev) ! temperature (K)
51      real,intent(in) :: qx(klon,klev,nqtot) ! tracers (.../kg_air)
52      real,intent(in) :: flxmass_w(klon,klev) ! vertical mass flux
53      real,intent(out) :: d_u(klon,klev) ! physics tendency on u (m/s/s)
54      real,intent(out) :: d_v(klon,klev) ! physics tendency on v (m/s/s)
55      real,intent(out) :: d_t(klon,klev) ! physics tendency on t (K/s)
56      real,intent(out) :: d_qx(klon,klev,nqtot) ! physics tendency on tracers
57      real,intent(out) :: d_ps(klon) ! physics tendency on surface pressure
58      real,intent(in) :: dudyn(iim+1,jjmp1,klev) ! Not used
59!FH! REAL PVteta(klon,nbteta)
60!      REAL PVteta(klon,1)
61      real,intent(in) :: PVteta(klon,3) ! Not used ; should match definition
62                                        ! in calfis.F
63
64integer,save :: itau=0 ! counter to count number of calls to physics
65!$OMP THREADPRIVATE(itau)
66real :: temp_newton(klon,klev)
67integer :: k
68logical, save :: first=.true.
69!$OMP THREADPRIVATE(first)
70
71! For I/Os
72integer :: itau0
73real :: zjulian
74real :: dtime
75integer :: nhori ! horizontal coordinate ID
76integer,save :: nid_hist ! output file ID
77!$OMP THREADPRIVATE(nid_hist)
78integer :: zvertid ! vertical coordinate ID
79integer,save :: iwrite_phys ! output every iwrite_phys physics step
80!$OMP THREADPRIVATE(iwrite_phys)
81integer :: iwrite_phys_omp ! intermediate variable to read iwrite_phys
82real :: t_ops ! frequency of the IOIPSL operations (eg average over...)
83real :: t_wrt ! frequency of the IOIPSL outputs
84
85! initializations
86if (debut) then ! Things to do only for the first call to physics
87! load initial conditions for physics (including the grid)
88  call phys_state_var_init() ! some initializations, required before calling phyetat0
89  call phyetat0("startphy.nc")
90
91! Initialize outputs:
92  itau0=0
93!$OMP MASTER
94  iwrite_phys_omp=1 !default: output every physics timestep
95  ! NB: getin() is not threadsafe; only one thread should call it.
96  call getin("iwrite_phys",iwrite_phys_omp)
97!$OMP END MASTER
98!$OMP BARRIER
99  iwrite_phys=iwrite_phys_omp
100  t_ops=pdtphys*iwrite_phys ! frequency of the IOIPSL operation
101  t_wrt=pdtphys*iwrite_phys ! frequency of the outputs in the file
102  ! compute zjulian for annee0=1979 and month=1 dayref=1 and hour=0.0
103  !CALL ymds2ju(annee0, month, dayref, hour, zjulian)
104  call ymds2ju(1979, 1, 1, 0.0, zjulian)
105  dtime=pdtphys
106  call histbeg_phy("histins.nc",itau0,zjulian,dtime,nhori,nid_hist)
107
108
109
110!$OMP MASTER
111
112
113
114  ! define vertical coordinate
115  call histvert(nid_hist,"presnivs","Vertical levels","Pa",klev, &
116                presnivs,zvertid,'down')
117  ! define variables which will be written in "histins.nc" file
118  call histdef(nid_hist,'temperature','Atmospheric temperature','K', &
119               iim,jj_nb,nhori,klev,1,klev,zvertid,32, &
120               'inst(X)',t_ops,t_wrt)
121  call histdef(nid_hist,'u','Eastward Zonal Wind','m/s', &
122               iim,jj_nb,nhori,klev,1,klev,zvertid,32, &
123               'inst(X)',t_ops,t_wrt)
124  call histdef(nid_hist,'v','Northward Meridional Wind','m/s', &
125               iim,jj_nb,nhori,klev,1,klev,zvertid,32, &
126               'inst(X)',t_ops,t_wrt)
127  call histdef(nid_hist,'ps','Surface Pressure','Pa', &
128               iim,jj_nb,nhori,1,1,1,zvertid,32, &
129               'inst(X)',t_ops,t_wrt)
130  ! end definition sequence
131  call histend(nid_hist)
132
133!XIOS
134#ifdef CPP_XIOS
135    ! Déclaration de l'axe vertical du fichier:   
136    !CALL wxios_add_vaxis("presnivs", "histins", klev, presnivs)
137
138    !Déclaration du pas de temps:
139    !CALL wxios_set_timestep(dtime)
140
141    !Finalisation du contexte:
142    !CALL wxios_closedef()
143#endif
144!$OMP END MASTER
145endif ! of if (debut)
146
147! increment counter itau
148itau=itau+1
149
150! set all tendencies to zero
151d_u(1:klon,1:klev)=0.
152d_v(1:klon,1:klev)=0.
153d_t(1:klon,1:klev)=0.
154d_qx(1:klon,1:klev,1:nqtot)=0.
155d_ps(1:klon)=0.
156
157! compute tendencies to return to the dynamics:
158! "friction" on the first layer
159d_u(1:klon,1)=-u(1:klon,1)/86400.
160d_v(1:klon,1)=-v(1:klon,1)/86400.
161! newtonian relaxation towards temp_newton()
162do k=1,klev
163  temp_newton(1:klon,k)=280.+cos(rlatd(1:klon))*40.-pphi(1:klon,k)/rg*6.e-3
164  d_t(1:klon,k)=(temp_newton(1:klon,k)-t(1:klon,k))/1.e5
165enddo
166
167
168!print*,'PHYDEV: itau=',itau
169
170! write some outputs:
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
178!XIOS
179#ifdef CPP_XIOS
180!$OMP MASTER
181    !On incrémente le pas de temps XIOS
182    !CALL wxios_update_calendar(itau)
183
184    !Et on écrit, avec la routine histwrite dédiée:
185    !CALL histwrite_phy("temperature",t)
186    !CALL histwrite_phy("u",u)
187    !CALL histwrite_phy("v",v)
188    !CALL histwrite_phy("ps",paprs(:,1))
189!$OMP END MASTER
190#endif
191
192! if lastcall, then it is time to write "restartphy.nc" file
193if (lafin) then
194  call phyredem("restartphy.nc")
195endif
196
197end
Note: See TracBrowser for help on using the repository browser.