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 | |
---|
64 | integer,save :: itau=0 ! counter to count number of calls to physics |
---|
65 | !$OMP THREADPRIVATE(itau) |
---|
66 | real :: temp_newton(klon,klev) |
---|
67 | integer :: k |
---|
68 | logical, save :: first=.true. |
---|
69 | !$OMP THREADPRIVATE(first) |
---|
70 | |
---|
71 | ! For I/Os |
---|
72 | integer :: itau0 |
---|
73 | real :: zjulian |
---|
74 | real :: dtime |
---|
75 | integer :: nhori ! horizontal coordinate ID |
---|
76 | integer,save :: nid_hist ! output file ID |
---|
77 | !$OMP THREADPRIVATE(nid_hist) |
---|
78 | integer :: zvertid ! vertical coordinate ID |
---|
79 | integer,save :: iwrite_phys ! output every iwrite_phys physics step |
---|
80 | !$OMP THREADPRIVATE(iwrite_phys) |
---|
81 | integer :: iwrite_phys_omp ! intermediate variable to read iwrite_phys |
---|
82 | real :: t_ops ! frequency of the IOIPSL operations (eg average over...) |
---|
83 | real :: t_wrt ! frequency of the IOIPSL outputs |
---|
84 | |
---|
85 | ! initializations |
---|
86 | if (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 | #ifndef CPP_NO_IOIPSL |
---|
107 | ! Initialize IOIPSL output file |
---|
108 | call histbeg_phy("histins.nc",itau0,zjulian,dtime,nhori,nid_hist) |
---|
109 | #endif |
---|
110 | |
---|
111 | !$OMP MASTER |
---|
112 | |
---|
113 | #ifndef CPP_NO_IOIPSL |
---|
114 | ! IOIPSL |
---|
115 | ! define vertical coordinate |
---|
116 | call histvert(nid_hist,"presnivs","Vertical levels","Pa",klev, & |
---|
117 | presnivs,zvertid,'down') |
---|
118 | ! define variables which will be written in "histins.nc" file |
---|
119 | call histdef(nid_hist,'temperature','Atmospheric temperature','K', & |
---|
120 | iim,jj_nb,nhori,klev,1,klev,zvertid,32, & |
---|
121 | 'inst(X)',t_ops,t_wrt) |
---|
122 | call histdef(nid_hist,'u','Eastward Zonal Wind','m/s', & |
---|
123 | iim,jj_nb,nhori,klev,1,klev,zvertid,32, & |
---|
124 | 'inst(X)',t_ops,t_wrt) |
---|
125 | call histdef(nid_hist,'v','Northward Meridional 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,'ps','Surface Pressure','Pa', & |
---|
129 | iim,jj_nb,nhori,1,1,1,zvertid,32, & |
---|
130 | 'inst(X)',t_ops,t_wrt) |
---|
131 | ! end definition sequence |
---|
132 | call histend(nid_hist) |
---|
133 | #endif |
---|
134 | |
---|
135 | #ifdef CPP_XIOS |
---|
136 | !XIOS |
---|
137 | ! Déclaration de l'axe vertical du fichier: |
---|
138 | CALL wxios_add_vaxis("presnivs", "histins", klev, presnivs) |
---|
139 | |
---|
140 | !Déclaration du pas de temps: |
---|
141 | CALL wxios_set_timestep(dtime) |
---|
142 | |
---|
143 | !Finalisation du contexte: |
---|
144 | CALL wxios_closedef() |
---|
145 | #endif |
---|
146 | !$OMP END MASTER |
---|
147 | endif ! of if (debut) |
---|
148 | |
---|
149 | ! increment local time counter itau |
---|
150 | itau=itau+1 |
---|
151 | |
---|
152 | ! set all tendencies to zero |
---|
153 | d_u(1:klon,1:klev)=0. |
---|
154 | d_v(1:klon,1:klev)=0. |
---|
155 | d_t(1:klon,1:klev)=0. |
---|
156 | d_qx(1:klon,1:klev,1:nqtot)=0. |
---|
157 | d_ps(1:klon)=0. |
---|
158 | |
---|
159 | ! compute tendencies to return to the dynamics: |
---|
160 | ! "friction" on the first layer |
---|
161 | d_u(1:klon,1)=-u(1:klon,1)/86400. |
---|
162 | d_v(1:klon,1)=-v(1:klon,1)/86400. |
---|
163 | ! newtonian relaxation towards temp_newton() |
---|
164 | do k=1,klev |
---|
165 | temp_newton(1:klon,k)=280.+cos(rlatd(1:klon))*40.-pphi(1:klon,k)/rg*6.e-3 |
---|
166 | d_t(1:klon,k)=(temp_newton(1:klon,k)-t(1:klon,k))/1.e5 |
---|
167 | enddo |
---|
168 | |
---|
169 | |
---|
170 | !print*,'PHYDEV: itau=',itau |
---|
171 | |
---|
172 | ! write some outputs: |
---|
173 | ! IOIPSL |
---|
174 | #ifndef CPP_NO_IOIPSL |
---|
175 | if (modulo(itau,iwrite_phys)==0) then |
---|
176 | call histwrite_phy(nid_hist,.false.,"temperature",itau,t) |
---|
177 | call histwrite_phy(nid_hist,.false.,"u",itau,u) |
---|
178 | call histwrite_phy(nid_hist,.false.,"v",itau,v) |
---|
179 | call histwrite_phy(nid_hist,.false.,"ps",itau,paprs(:,1)) |
---|
180 | endif |
---|
181 | #endif |
---|
182 | |
---|
183 | !XIOS |
---|
184 | #ifdef CPP_XIOS |
---|
185 | !$OMP MASTER |
---|
186 | !Increment XIOS time |
---|
187 | CALL wxios_update_calendar(itau) |
---|
188 | |
---|
189 | !Send fields to XIOS: |
---|
190 | CALL histwrite_phy("temperature",t) |
---|
191 | CALL histwrite_phy("u",u) |
---|
192 | CALL histwrite_phy("v",v) |
---|
193 | CALL histwrite_phy("ps",paprs(:,1)) |
---|
194 | !$OMP END MASTER |
---|
195 | #endif |
---|
196 | |
---|
197 | ! if lastcall, then it is time to write "restartphy.nc" file |
---|
198 | if (lafin) then |
---|
199 | call phyredem("restartphy.nc") |
---|
200 | endif |
---|
201 | |
---|
202 | end |
---|