source: LMDZ5/trunk/libf/phylmd/dyn1d/1D_interp_cases.h @ 2668

Last change on this file since 2668 was 2565, checked in by jyg, 8 years ago

Some small improvements to the 1D model:
(1) initialization of pbl_tke (-> 1+1=2);
(2) bug fix concerning nudge_tsoil=y;
(3) possibility of a constant moisture convergence
when forcing_type=0.

  • Property svn:keywords set to Id
File size: 29.2 KB
Line 
1!
2! $Id: 1D_interp_cases.h 2565 2016-06-10 14:01:28Z fhourdin $
3!
4!---------------------------------------------------------------------
5! Forcing_LES case: constant dq_dyn
6!---------------------------------------------------------------------
7      if (forcing_LES) then
8        DO l = 1,llm
9          d_q_adv(l,1) = dq_dyn(l,1)
10        ENDDO
11      endif ! forcing_LES
12!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
13!---------------------------------------------------------------------
14! Interpolation forcing in time and onto model levels
15!---------------------------------------------------------------------
16      if (forcing_GCSSold) then
17
18       call get_uvd(it,timestep,fich_gcssold_ctl,fich_gcssold_dat,              &
19     &               ht_gcssold,hq_gcssold,hw_gcssold,                          &
20     &               hu_gcssold,hv_gcssold,                                     &
21     &               hthturb_gcssold,hqturb_gcssold,Ts_gcssold,                 &
22     &               imp_fcg_gcssold,ts_fcg_gcssold,                            &
23     &               Tp_fcg_gcssold,Turb_fcg_gcssold)
24       if (prt_level.ge.1) then
25         print *,' get_uvd -> hqturb_gcssold ',it,hqturb_gcssold
26       endif
27! large-scale forcing :
28!!!      tsurf = ts_gcssold
29      do l = 1, llm
30!       u(l) = hu_gcssold(l) !  on prescrit le vent
31!       v(l) = hv_gcssold(l)    !  on prescrit le vent
32!       omega(l) = hw_gcssold(l)
33!       rho(l)  = play(l)/(rd*temp(l)*(1.+(rv/rd-1.)*q(l,1)))
34!       omega2(l)=-rho(l)*omega(l)
35       omega(l) = hw_gcssold(l)
36       omega2(l)= omega(l)/rg*airefi ! flxmass_w calcule comme ds physiq
37
38       alpha = rd*temp(l)*(1.+(rv/rd-1.)*q(l,1))/play(l)
39       d_th_adv(l) = ht_gcssold(l)
40       d_q_adv(l,1) = hq_gcssold(l)
41       dt_cooling(l) = 0.0
42      enddo
43
44      endif ! forcing_GCSSold
45!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
46!---------------------------------------------------------------------
47! Interpolation Toga forcing
48!---------------------------------------------------------------------
49      if (forcing_toga) then
50
51       if (prt_level.ge.1) then
52        print*,                                                             &
53     & '#### ITAP,day,day1,(day-day1)*86400,(day-day1)*86400/dt_toga=',     &
54     &    day,day1,(day-day1)*86400.,(day-day1)*86400/dt_toga
55       endif
56
57! time interpolation:
58        CALL interp_toga_time(daytime,day1,annee_ref                        &
59     &             ,year_ini_toga,day_ju_ini_toga,nt_toga,dt_toga           &
60     &             ,nlev_toga,ts_toga,plev_toga,t_toga,q_toga,u_toga        &
61     &             ,v_toga,w_toga,ht_toga,vt_toga,hq_toga,vq_toga           &
62     &             ,ts_prof,plev_prof,t_prof,q_prof,u_prof,v_prof,w_prof    &
63     &             ,ht_prof,vt_prof,hq_prof,vq_prof)
64
65        if (type_ts_forcing.eq.1) ts_cur = ts_prof ! SST used in read_tsurf1d
66
67! vertical interpolation:
68      CALL interp_toga_vertical(play,nlev_toga,plev_prof                    &
69     &         ,t_prof,q_prof,u_prof,v_prof,w_prof                          &
70     &         ,ht_prof,vt_prof,hq_prof,vq_prof                             &
71     &         ,t_mod,q_mod,u_mod,v_mod,w_mod                               &
72     &         ,ht_mod,vt_mod,hq_mod,vq_mod,mxcalc)
73
74! large-scale forcing :
75      tsurf = ts_prof
76      do l = 1, llm
77       u(l) = u_mod(l) ! sb: on prescrit le vent
78       v(l) = v_mod(l) ! sb: on prescrit le vent
79!       omega(l) = w_prof(l)
80!       rho(l)  = play(l)/(rd*temp(l)*(1.+(rv/rd-1.)*q(l,1)))
81!       omega2(l)=-rho(l)*omega(l)
82       omega(l) = w_mod(l)
83       omega2(l)= omega(l)/rg*airefi ! flxmass_w calcule comme ds physiq
84
85       alpha = rd*temp(l)*(1.+(rv/rd-1.)*q(l,1))/play(l)
86       d_th_adv(l) = alpha*omega(l)/rcpd-(ht_mod(l)+vt_mod(l))
87       d_q_adv(l,1) = -(hq_mod(l)+vq_mod(l))
88       dt_cooling(l) = 0.0
89      enddo
90
91      endif ! forcing_toga
92!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
93! Interpolation DICE forcing
94!---------------------------------------------------------------------
95      if (forcing_dice) then
96
97       if (prt_level.ge.1) then
98        print*,'#### ITAP,day,day1,(day-day1)*86400,(day-day1)*86400/dt_dice=',&
99     &    day,day1,(day-day1)*86400.,(day-day1)*86400/dt_dice
100       endif
101
102! time interpolation:
103      CALL interp_dice_time(daytime,day1,annee_ref                    &
104     &             ,year_ini_dice,day_ju_ini_dice,nt_dice,dt_dice     & 
105     &             ,nlev_dice,shf_dice,lhf_dice,lwup_dice,swup_dice   &
106     &             ,tg_dice,ustar_dice,psurf_dice,ug_dice,vg_dice     &
107     &             ,ht_dice,hq_dice,hu_dice,hv_dice,w_dice,omega_dice &
108     &             ,shf_prof,lhf_prof,lwup_prof,swup_prof,tg_prof     &
109     &             ,ustar_prof,psurf_prof,ug_profd,vg_profd           &
110     &             ,ht_profd,hq_profd,hu_profd,hv_profd,w_profd       &
111     &             ,omega_profd)
112!     do l = 1, llm
113!     print *,'llm l omega_profd',llm,l,omega_profd(l)
114!     enddo
115
116        if (type_ts_forcing.eq.1) ts_cur = tg_prof ! SST used in read_tsurf1d
117
118! vertical interpolation:
119      CALL interp_dice_vertical(play,nlev_dice,nt_dice,plev_dice        &
120     &         ,th_dice,qv_dice,u_dice,v_dice,o3_dice                   &
121     &         ,ht_profd,hq_profd,hu_profd,hv_profd,w_profd,omega_profd &
122     &         ,th_mod,qv_mod,u_mod,v_mod,o3_mod                        &
123     &         ,ht_mod,hq_mod,hu_mod,hv_mod,w_mod,omega_mod,mxcalc)
124!     do l = 1, llm
125!      print *,'llm l omega_mod',llm,l,omega_mod(l)
126!     enddo
127
128! Les forcages DICE sont donnes /jour et non /seconde !
129      ht_mod(:)=ht_mod(:)/86400.
130      hq_mod(:)=hq_mod(:)/86400.
131      hu_mod(:)=hu_mod(:)/86400.
132      hv_mod(:)=hv_mod(:)/86400.
133
134!calcul de l'advection verticale a partir du omega (repris cas TWPICE, MPL 05082013)
135!Calcul des gradients verticaux
136!initialisation
137      d_t_z(:)=0.
138      d_q_z(:)=0.
139      d_u_z(:)=0.
140      d_v_z(:)=0.
141      DO l=2,llm-1
142       d_t_z(l)=(temp(l+1)-temp(l-1))/(play(l+1)-play(l-1))
143       d_q_z(l)=(q(l+1,1)-q(l-1,1)) /(play(l+1)-play(l-1))
144       d_u_z(l)=(u(l+1)-u(l-1))/(play(l+1)-play(l-1))
145       d_v_z(l)=(v(l+1)-v(l-1))/(play(l+1)-play(l-1))
146      ENDDO
147      d_t_z(1)=d_t_z(2)
148      d_q_z(1)=d_q_z(2)
149!     d_u_z(1)=u(2)/(play(2)-psurf)/5.
150!     d_v_z(1)=v(2)/(play(2)-psurf)/5.
151      d_u_z(1)=0.
152      d_v_z(1)=0.
153      d_t_z(llm)=d_t_z(llm-1)
154      d_q_z(llm)=d_q_z(llm-1)
155      d_u_z(llm)=d_u_z(llm-1)
156      d_v_z(llm)=d_v_z(llm-1)
157
158!Calcul de l advection verticale: 
159! utiliser omega (Pa/s) et non w (m/s) !! MP 20131108
160      d_t_dyn_z(:)=omega_mod(:)*d_t_z(:)
161      d_q_dyn_z(:)=omega_mod(:)*d_q_z(:)
162      d_u_dyn_z(:)=omega_mod(:)*d_u_z(:)
163      d_v_dyn_z(:)=omega_mod(:)*d_v_z(:)
164
165! large-scale forcing :
166!     tsurf = tg_prof    MPL 20130925 commente
167      psurf = psurf_prof
168! For this case, fluxes are imposed
169      fsens=-1*shf_prof
170      flat=-1*lhf_prof
171      ust=ustar_prof
172      tg=tg_prof
173      print *,'ust= ',ust
174      do l = 1, llm
175       ug(l)= ug_profd
176       vg(l)= vg_profd
177!       omega(l) = w_prof(l)
178!      rho(l)  = play(l)/(rd*temp(l)*(1.+(rv/rd-1.)*q(l,1)))
179!       omega2(l)=-rho(l)*omega(l)
180!      omega(l) = w_mod(l)*(-rg*rho(l))
181       omega(l) = omega_mod(l)
182       omega2(l)= omega(l)/rg*airefi ! flxmass_w calcule comme ds physiq
183
184       alpha = rd*temp(l)*(1.+(rv/rd-1.)*q(l,1))/play(l)
185       d_th_adv(l) = alpha*omega(l)/rcpd+ht_mod(l)-d_t_dyn_z(l)
186       d_q_adv(l,1) = hq_mod(l)-d_q_dyn_z(l)
187       d_u_adv(l) = hu_mod(l)-d_u_dyn_z(l)
188       d_v_adv(l) = hv_mod(l)-d_v_dyn_z(l)
189       dt_cooling(l) = 0.0
190      enddo
191
192      endif ! forcing_dice
193!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
194!---------------------------------------------------------------------
195!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
196!---------------------------------------------------------------------
197! Interpolation forcing TWPice
198!---------------------------------------------------------------------
199      if (forcing_twpice) then
200
201        print*,                                                             &
202     & '#### ITAP,day,day1,(day-day1)*86400,(day-day1)*86400/dt_twpi=',     &
203     &    daytime,day1,(daytime-day1)*86400.,                               &
204     &    (daytime-day1)*86400/dt_twpi
205
206! time interpolation:
207        CALL interp_toga_time(daytime,day1,annee_ref                        &
208     &       ,year_ini_twpi,day_ju_ini_twpi,nt_twpi,dt_twpi,nlev_twpi       &
209     &       ,ts_twpi,plev_twpi,t_twpi,q_twpi,u_twpi,v_twpi,w_twpi          &
210     &       ,ht_twpi,vt_twpi,hq_twpi,vq_twpi                               &
211     &       ,ts_proftwp,plev_proftwp,t_proftwp,q_proftwp,u_proftwp         &
212     &       ,v_proftwp,w_proftwp                                           &
213     &       ,ht_proftwp,vt_proftwp,hq_proftwp,vq_proftwp)
214
215! vertical interpolation:
216      CALL interp_toga_vertical(play,nlev_twpi,plev_proftwp                 &
217     &         ,t_proftwp,q_proftwp,u_proftwp,v_proftwp,w_proftwp           &
218     &         ,ht_proftwp,vt_proftwp,hq_proftwp,vq_proftwp                 &
219     &         ,t_mod,q_mod,u_mod,v_mod,w_mod                               &
220     &         ,ht_mod,vt_mod,hq_mod,vq_mod,mxcalc)
221
222
223!calcul de l'advection verticale a partir du omega
224!Calcul des gradients verticaux
225!initialisation
226      d_t_z(:)=0.
227      d_q_z(:)=0.
228      d_t_dyn_z(:)=0.
229      d_q_dyn_z(:)=0.
230      DO l=2,llm-1
231       d_t_z(l)=(temp(l+1)-temp(l-1))/(play(l+1)-play(l-1))
232       d_q_z(l)=(q(l+1,1)-q(l-1,1))/(play(l+1)-play(l-1))
233      ENDDO
234      d_t_z(1)=d_t_z(2)
235      d_q_z(1)=d_q_z(2)
236      d_t_z(llm)=d_t_z(llm-1)
237      d_q_z(llm)=d_q_z(llm-1)
238
239!Calcul de l advection verticale
240      d_t_dyn_z(:)=w_mod(:)*d_t_z(:)
241      d_q_dyn_z(:)=w_mod(:)*d_q_z(:)
242
243!wind nudging above 500m with a 2h time scale
244        do l=1,llm
245        if (nudge_wind) then
246!           if (phi(l).gt.5000.) then
247        if (phi(l).gt.0.) then
248        u(l)=u(l)+timestep*(u_mod(l)-u(l))/(2.*3600.)
249        v(l)=v(l)+timestep*(v_mod(l)-v(l))/(2.*3600.)
250           endif   
251        else
252        u(l) = u_mod(l) 
253        v(l) = v_mod(l)
254        endif
255        enddo
256
257!CR:nudging of q and theta with a 6h time scale above 15km
258        if (nudge_thermo) then
259        do l=1,llm
260           zz(l)=phi(l)/9.8
261           if ((zz(l).le.16000.).and.(zz(l).gt.15000.)) then
262             zfact=(zz(l)-15000.)/1000.
263        q(l,1)=q(l,1)+timestep*(q_mod(l)-q(l,1))/(6.*3600.)*zfact
264        temp(l)=temp(l)+timestep*(t_mod(l)-temp(l))/(6.*3600.)*zfact
265           else if (zz(l).gt.16000.) then
266        q(l,1)=q(l,1)+timestep*(q_mod(l)-q(l,1))/(6.*3600.)
267        temp(l)=temp(l)+timestep*(t_mod(l)-temp(l))/(6.*3600.)
268           endif
269        enddo   
270        endif
271
272      do l = 1, llm
273       omega(l) = w_mod(l)
274       omega2(l)= omega(l)/rg*airefi ! flxmass_w calcule comme ds physiq
275       alpha = rd*temp(l)*(1.+(rv/rd-1.)*q(l,1))/play(l)
276!calcul de l'advection totale
277        if (cptadvw) then
278        d_th_adv(l) = alpha*omega(l)/rcpd+ht_mod(l)-d_t_dyn_z(l)
279!        print*,'temp vert adv',l,ht_mod(l),vt_mod(l),-d_t_dyn_z(l)
280        d_q_adv(l,1) = hq_mod(l)-d_q_dyn_z(l)
281!        print*,'q vert adv',l,hq_mod(l),vq_mod(l),-d_q_dyn_z(l)
282        else
283        d_th_adv(l) = alpha*omega(l)/rcpd+(ht_mod(l)+vt_mod(l))
284        d_q_adv(l,1) = (hq_mod(l)+vq_mod(l))
285        endif
286       dt_cooling(l) = 0.0
287      enddo
288
289      endif ! forcing_twpice
290
291!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
292!---------------------------------------------------------------------
293! Interpolation forcing AMMA
294!---------------------------------------------------------------------
295
296       if (forcing_amma) then
297
298        print*,                                                             &
299     & '#### ITAP,day,day1,(day-day1)*86400,(day-day1)*86400/dt_amma=',     &
300     &    daytime,day1,(daytime-day1)*86400.,                               &
301     &    (daytime-day1)*86400/dt_amma
302
303! time interpolation using TOGA interpolation routine
304        CALL interp_amma_time(daytime,day1,annee_ref                        &
305     &       ,year_ini_amma,day_ju_ini_amma,nt_amma,dt_amma,nlev_amma       &
306     &       ,vitw_amma,ht_amma,hq_amma,lat_amma,sens_amma                  &
307     &       ,vitw_profamma,ht_profamma,hq_profamma,lat_profamma            &
308     &       ,sens_profamma)
309
310      print*,'apres interpolation temporelle AMMA'
311
312      do k=1,nlev_amma
313         th_profamma(k)=0.
314         q_profamma(k)=0.
315         u_profamma(k)=0.
316         v_profamma(k)=0.
317         vt_profamma(k)=0.
318         vq_profamma(k)=0.
319       enddo
320! vertical interpolation using TOGA interpolation routine:
321!      write(*,*)'avant interp vert', t_proftwp
322      CALL interp_toga_vertical(play,nlev_amma,plev_amma                      &
323     &         ,th_profamma,q_profamma,u_profamma,v_profamma                 &
324     &         ,vitw_profamma                                               &
325     &         ,ht_profamma,vt_profamma,hq_profamma,vq_profamma             &
326     &         ,t_mod,q_mod,u_mod,v_mod,w_mod                               &
327     &         ,ht_mod,vt_mod,hq_mod,vq_mod,mxcalc)
328       write(*,*) 'Profil initial forcing AMMA interpole'
329
330
331!calcul de l'advection verticale a partir du omega
332!Calcul des gradients verticaux
333!initialisation
334      do l=1,llm
335      d_t_z(l)=0.
336      d_q_z(l)=0.
337      enddo
338
339      DO l=2,llm-1
340       d_t_z(l)=(temp(l+1)-temp(l-1))/(play(l+1)-play(l-1))
341       d_q_z(l)=(q(l+1,1)-q(l-1,1))/(play(l+1)-play(l-1))
342      ENDDO
343      d_t_z(1)=d_t_z(2)
344      d_q_z(1)=d_q_z(2)
345      d_t_z(llm)=d_t_z(llm-1)
346      d_q_z(llm)=d_q_z(llm-1)
347
348
349      do l = 1, llm
350       rho(l)  = play(l)/(rd*temp(l)*(1.+(rv/rd-1.)*q(l,1)))
351       omega(l) = w_mod(l)*(-rg*rho(l))
352       omega2(l)= omega(l)/rg*airefi ! flxmass_w calcule comme ds physiq
353       alpha = rd*temp(l)*(1.+(rv/rd-1.)*q(l,1))/play(l)
354!calcul de l'advection totale
355!        d_th_adv(l) = alpha*omega(l)/rcpd+ht_mod(l)-omega(l)*d_t_z(l)
356!attention: on impose dth
357        d_th_adv(l) = alpha*omega(l)/rcpd+                                  &
358     &         ht_mod(l)*(play(l)/pzero)**rkappa-omega(l)*d_t_z(l)
359!        d_th_adv(l) = 0.
360!        print*,'temp vert adv',l,ht_mod(l),vt_mod(l),-d_t_dyn_z(l)
361        d_q_adv(l,1) = hq_mod(l)-omega(l)*d_q_z(l)
362!        d_q_adv(l,1) = 0.
363!        print*,'q vert adv',l,hq_mod(l),vq_mod(l),-d_q_dyn_z(l)
364   
365       dt_cooling(l) = 0.0
366      enddo
367
368
369!     ok_flux_surf=.false.
370      fsens=-1.*sens_profamma
371      flat=-1.*lat_profamma
372
373      endif ! forcing_amma
374
375!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
376!---------------------------------------------------------------------
377! Interpolation forcing Rico
378!---------------------------------------------------------------------
379      if (forcing_rico) then
380!       call lstendH(llm,omega,dt_dyn,dq_dyn,du_dyn, dv_dyn,
381!     :  q,temp,u,v,play)
382       call lstendH(llm,nqtot,omega,dt_dyn,dq_dyn,q,temp,u,v,play)
383
384        do l=1,llm
385       d_th_adv(l) =  (dth_rico(l) +  dt_dyn(l))
386       d_q_adv(l,1) = (dqh_rico(l) +  dq_dyn(l,1))
387       d_q_adv(l,2) = 0.
388        enddo
389      endif  ! forcing_rico
390!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
391!---------------------------------------------------------------------
392! Interpolation forcing Arm_cu
393!---------------------------------------------------------------------
394      if (forcing_armcu) then
395
396        print*,                                                             &
397     & '#### ITAP,day,day1,(day-day1)*86400,(day-day1)*86400/dt_armcu=',    &
398     &    day,day1,(day-day1)*86400.,(day-day1)*86400/dt_armcu
399
400! time interpolation:
401! ATTENTION, cet appel ne convient pas pour TOGA !!
402! revoir 1DUTILS.h et les arguments
403      CALL interp_armcu_time(daytime,day1,annee_ref                         &
404     &            ,year_ini_armcu,day_ju_ini_armcu,nt_armcu,dt_armcu        &
405     &            ,nlev_armcu,sens_armcu,flat_armcu,adv_theta_armcu          &
406     &            ,rad_theta_armcu,adv_qt_armcu,sens_prof,flat_prof         &
407     &            ,adv_theta_prof,rad_theta_prof,adv_qt_prof)
408
409! vertical interpolation:
410! No vertical interpolation if nlev imposed to 19 or 40
411
412! For this case, fluxes are imposed
413       fsens=-1*sens_prof
414       flat=-1*flat_prof
415
416! Advective forcings are given in K or g/kg ... BY HOUR
417      do l = 1, llm
418       ug(l)= u_mod(l)
419       vg(l)= v_mod(l)
420       IF((phi(l)/RG).LT.1000) THEN
421         d_th_adv(l) = (adv_theta_prof + rad_theta_prof)/3600.
422         d_q_adv(l,1) = adv_qt_prof/1000./3600.
423         d_q_adv(l,2) = 0.0
424!        print *,'INF1000: phi dth dq1 dq2',
425!    :  phi(l)/RG,d_th_adv(l),d_q_adv(l,1),d_q_adv(l,2)
426       ELSEIF ((phi(l)/RG).GE.1000.AND.(phi(l)/RG).lt.3000) THEN
427         fact=((phi(l)/RG)-1000.)/2000.
428         fact=1-fact
429         d_th_adv(l) = (adv_theta_prof + rad_theta_prof)*fact/3600.
430         d_q_adv(l,1) = adv_qt_prof*fact/1000./3600.
431         d_q_adv(l,2) = 0.0
432!        print *,'SUP1000: phi fact dth dq1 dq2',
433!    :  phi(l)/RG,fact,d_th_adv(l),d_q_adv(l,1),d_q_adv(l,2)
434       ELSE
435         d_th_adv(l) = 0.0
436         d_q_adv(l,1) = 0.0
437         d_q_adv(l,2) = 0.0
438!        print *,'SUP3000: phi dth dq1 dq2',
439!    :  phi(l)/RG,d_th_adv(l),d_q_adv(l,1),d_q_adv(l,2)
440       ENDIF
441      dt_cooling(l) = 0.0 
442!     print *,'Interp armcu: phi dth dq1 dq2',
443!    :  l,phi(l),d_th_adv(l),d_q_adv(l,1),d_q_adv(l,2)
444      enddo
445      endif ! forcing_armcu
446!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
447!---------------------------------------------------------------------
448! Interpolation forcing in time and onto model levels
449!---------------------------------------------------------------------
450      if (forcing_sandu) then
451
452        print*,                                                             &
453     & '#### ITAP,day,day1,(day-day1)*86400,(day-day1)*86400/dt_sandu=',    &
454     &    day,day1,(day-day1)*86400.,(day-day1)*86400/dt_sandu
455
456! time interpolation:
457! ATTENTION, cet appel ne convient pas pour TOGA !!
458! revoir 1DUTILS.h et les arguments
459      CALL interp_sandu_time(daytime,day1,annee_ref                         &
460     &             ,year_ini_sandu,day_ju_ini_sandu,nt_sandu,dt_sandu       &
461     &             ,nlev_sandu                                              &
462     &             ,ts_sandu,ts_prof)
463
464        if (type_ts_forcing.eq.1) ts_cur = ts_prof ! SST used in read_tsurf1d
465
466! vertical interpolation:
467      CALL interp_sandu_vertical(play,nlev_sandu,plev_profs                 &
468     &         ,t_profs,thl_profs,q_profs,u_profs,v_profs,w_profs           &
469     &         ,omega_profs,o3mmr_profs                                     &
470     &         ,t_mod,thl_mod,q_mod,u_mod,v_mod,w_mod                       &
471     &         ,omega_mod,o3mmr_mod,mxcalc)
472!calcul de l'advection verticale
473!Calcul des gradients verticaux
474!initialisation
475      d_t_z(:)=0.
476      d_q_z(:)=0.
477      d_t_dyn_z(:)=0.
478      d_q_dyn_z(:)=0.
479! schema centre
480!     DO l=2,llm-1
481!      d_t_z(l)=(temp(l+1)-temp(l-1))
482!    &          /(play(l+1)-play(l-1))
483!      d_q_z(l)=(q(l+1,1)-q(l-1,1))
484!    &          /(play(l+1)-play(l-1))
485! schema amont
486      DO l=2,llm-1
487       d_t_z(l)=(temp(l+1)-temp(l))/(play(l+1)-play(l))
488       d_q_z(l)=(q(l+1,1)-q(l,1))/(play(l+1)-play(l))
489!     print *,'l temp2 temp0 play2 play0 omega_mod',
490!    & temp(l+1),temp(l-1),play(l+1),play(l-1),omega_mod(l)
491      ENDDO
492      d_t_z(1)=d_t_z(2)
493      d_q_z(1)=d_q_z(2)
494      d_t_z(llm)=d_t_z(llm-1)
495      d_q_z(llm)=d_q_z(llm-1)
496
497!  calcul de l advection verticale
498! Confusion w (m/s) et omega (Pa/s) !!
499      d_t_dyn_z(:)=omega_mod(:)*d_t_z(:)
500      d_q_dyn_z(:)=omega_mod(:)*d_q_z(:)
501!     do l=1,llm
502!      print *,'d_t_dyn omega_mod d_t_z d_q_dyn d_q_z',
503!    :l,d_t_dyn_z(l),omega_mod(l),d_t_z(l),d_q_dyn_z(l),d_q_z(l)
504!     enddo
505
506
507! large-scale forcing : pour le cas Sandu ces forcages sont la SST
508! et une divergence constante -> profil de omega
509      tsurf = ts_prof
510      write(*,*) 'SST suivante: ',tsurf
511      do l = 1, llm
512       omega(l) = omega_mod(l)
513       omega2(l)= omega(l)/rg*airefi ! flxmass_w calcule comme ds physiq
514
515       alpha = rd*temp(l)*(1.+(rv/rd-1.)*q(l,1))/play(l)
516!
517!      d_th_adv(l) = 0.0
518!      d_q_adv(l,1) = 0.0
519!CR:test advection=0
520!calcul de l'advection verticale
521        d_th_adv(l) = alpha*omega(l)/rcpd-d_t_dyn_z(l)
522!        print*,'temp adv',l,-d_t_dyn_z(l)
523        d_q_adv(l,1) = -d_q_dyn_z(l)
524!        print*,'q adv',l,-d_q_dyn_z(l)
525       dt_cooling(l) = 0.0
526      enddo
527      endif ! forcing_sandu
528!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
529!---------------------------------------------------------------------
530! Interpolation forcing in time and onto model levels
531!---------------------------------------------------------------------
532      if (forcing_astex) then
533
534        print*,                                                             &
535     & '#### ITAP,day,day1,(day-day1)*86400,(day-day1)*86400/dt_astex=',    &
536     &    day,day1,(day-day1)*86400.,(day-day1)*86400/dt_astex
537
538! time interpolation:
539! ATTENTION, cet appel ne convient pas pour TOGA !!
540! revoir 1DUTILS.h et les arguments
541      CALL interp_astex_time(daytime,day1,annee_ref                         &
542     &             ,year_ini_astex,day_ju_ini_astex,nt_astex,dt_astex       &
543     &             ,nlev_astex,div_astex,ts_astex,ug_astex,vg_astex         &
544     &             ,ufa_astex,vfa_astex,div_prof,ts_prof,ug_prof,vg_prof    &
545     &             ,ufa_prof,vfa_prof)
546
547        if (type_ts_forcing.eq.1) ts_cur = ts_prof ! SST used in read_tsurf1d
548
549! vertical interpolation:
550      CALL interp_astex_vertical(play,nlev_astex,plev_profa                 &
551     &         ,t_profa,thl_profa,qv_profa,ql_profa,qt_profa                &
552     &         ,u_profa,v_profa,w_profa,tke_profa,o3mmr_profa               &
553     &         ,t_mod,thl_mod,qv_mod,ql_mod,qt_mod,u_mod,v_mod,w_mod        &
554     &         ,tke_mod,o3mmr_mod,mxcalc)
555!calcul de l'advection verticale
556!Calcul des gradients verticaux
557!initialisation
558      d_t_z(:)=0.
559      d_q_z(:)=0.
560      d_t_dyn_z(:)=0.
561      d_q_dyn_z(:)=0.
562! schema centre
563!     DO l=2,llm-1
564!      d_t_z(l)=(temp(l+1)-temp(l-1))
565!    &          /(play(l+1)-play(l-1))
566!      d_q_z(l)=(q(l+1,1)-q(l-1,1))
567!    &          /(play(l+1)-play(l-1))
568! schema amont
569      DO l=2,llm-1
570       d_t_z(l)=(temp(l+1)-temp(l))/(play(l+1)-play(l))
571       d_q_z(l)=(q(l+1,1)-q(l,1))/(play(l+1)-play(l))
572!     print *,'l temp2 temp0 play2 play0 omega_mod',
573!    & temp(l+1),temp(l-1),play(l+1),play(l-1),omega_mod(l)
574      ENDDO
575      d_t_z(1)=d_t_z(2)
576      d_q_z(1)=d_q_z(2)
577      d_t_z(llm)=d_t_z(llm-1)
578      d_q_z(llm)=d_q_z(llm-1)
579
580!  calcul de l advection verticale
581! Confusion w (m/s) et omega (Pa/s) !!
582      d_t_dyn_z(:)=w_mod(:)*d_t_z(:)
583      d_q_dyn_z(:)=w_mod(:)*d_q_z(:)
584!     do l=1,llm
585!      print *,'d_t_dyn omega_mod d_t_z d_q_dyn d_q_z',
586!    :l,d_t_dyn_z(l),omega_mod(l),d_t_z(l),d_q_dyn_z(l),d_q_z(l)
587!     enddo
588
589
590! large-scale forcing : pour le cas Astex ces forcages sont la SST
591! la divergence,ug,vg,ufa,vfa
592      tsurf = ts_prof
593      write(*,*) 'SST suivante: ',tsurf
594      do l = 1, llm
595       omega(l) = w_mod(l)
596       omega2(l)= omega(l)/rg*airefi ! flxmass_w calcule comme ds physiq
597
598       alpha = rd*temp(l)*(1.+(rv/rd-1.)*q(l,1))/play(l)
599!
600!      d_th_adv(l) = 0.0
601!      d_q_adv(l,1) = 0.0
602!CR:test advection=0
603!calcul de l'advection verticale
604        d_th_adv(l) = alpha*omega(l)/rcpd-d_t_dyn_z(l)
605!        print*,'temp adv',l,-d_t_dyn_z(l)
606        d_q_adv(l,1) = -d_q_dyn_z(l)
607!        print*,'q adv',l,-d_q_dyn_z(l)
608       dt_cooling(l) = 0.0
609      enddo
610      endif ! forcing_astex
611
612!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
613!---------------------------------------------------------------------
614! Interpolation forcing standard case
615!---------------------------------------------------------------------
616      if (forcing_case) then
617
618        print*,                                                             &
619     & '#### ITAP,day,day1,(day-day1)*86400,(day-day1)*86400/pdt_cas=',     &
620     &    daytime,day1,(daytime-day1)*86400.,                               &
621     &    (daytime-day1)*86400/pdt_cas
622
623! time interpolation:
624        CALL interp_case_time(daytime,day1,annee_ref                                        &
625!    &       ,year_ini_cas,day_ju_ini_cas,nt_cas,pdt_cas,nlev_cas                           &
626     &       ,nt_cas,nlev_cas                                                               &
627     &       ,ts_cas,plev_cas,t_cas,q_cas,u_cas,v_cas,ug_cas,vg_cas                         &
628     &       ,vitw_cas,du_cas,hu_cas,vu_cas                                                 &
629     &       ,dv_cas,hv_cas,vv_cas,dt_cas,ht_cas,vt_cas,dtrad_cas                           &
630     &       ,dq_cas,hq_cas,vq_cas,lat_cas,sens_cas,ustar_cas                               &
631     &       ,uw_cas,vw_cas,q1_cas,q2_cas                                                   &
632     &       ,ts_prof_cas,plev_prof_cas,t_prof_cas,q_prof_cas,u_prof_cas,v_prof_cas         &
633     &       ,ug_prof_cas,vg_prof_cas,vitw_prof_cas,du_prof_cas,hu_prof_cas,vu_prof_cas     &
634     &       ,dv_prof_cas,hv_prof_cas,vv_prof_cas,dt_prof_cas,ht_prof_cas,vt_prof_cas       &
635     &       ,dtrad_prof_cas,dq_prof_cas,hq_prof_cas,vq_prof_cas,lat_prof_cas               &
636     &       ,sens_prof_cas,ustar_prof_cas,uw_prof_cas,vw_prof_cas,q1_prof_cas,q2_prof_cas)
637
638             ts_cur = ts_prof_cas
639             psurf=plev_prof_cas(1)
640
641! vertical interpolation:
642      CALL interp_case_vertical(play,nlev_cas,plev_prof_cas            &
643     &         ,t_prof_cas,q_prof_cas,u_prof_cas,v_prof_cas,ug_prof_cas,vg_prof_cas,vitw_prof_cas                         &
644     &         ,du_prof_cas,hu_prof_cas,vu_prof_cas,dv_prof_cas,hv_prof_cas,vv_prof_cas           &
645     &         ,dt_prof_cas,ht_prof_cas,vt_prof_cas,dtrad_prof_cas,dq_prof_cas,hq_prof_cas,vq_prof_cas           &
646     &         ,t_mod_cas,q_mod_cas,u_mod_cas,v_mod_cas,ug_mod_cas,vg_mod_cas,w_mod_cas                              &
647     &         ,du_mod_cas,hu_mod_cas,vu_mod_cas,dv_mod_cas,hv_mod_cas,vv_mod_cas               &
648     &         ,dt_mod_cas,ht_mod_cas,vt_mod_cas,dtrad_mod_cas,dq_mod_cas,hq_mod_cas,vq_mod_cas,mxcalc)
649
650
651!calcul de l'advection verticale a partir du omega
652!Calcul des gradients verticaux
653!initialisation
654      d_t_z(:)=0.
655      d_q_z(:)=0.
656      d_u_z(:)=0.
657      d_v_z(:)=0.
658      d_t_dyn_z(:)=0.
659      d_q_dyn_z(:)=0.
660      d_u_dyn_z(:)=0.
661      d_v_dyn_z(:)=0.
662      DO l=2,llm-1
663       d_t_z(l)=(temp(l+1)-temp(l-1))/(play(l+1)-play(l-1))
664       d_q_z(l)=(q(l+1,1)-q(l-1,1))/(play(l+1)-play(l-1))
665       d_u_z(l)=(u(l+1)-u(l-1))/(play(l+1)-play(l-1))
666       d_v_z(l)=(v(l+1)-v(l-1))/(play(l+1)-play(l-1))
667      ENDDO
668      d_t_z(1)=d_t_z(2)
669      d_q_z(1)=d_q_z(2)
670      d_u_z(1)=d_u_z(2)
671      d_v_z(1)=d_v_z(2)
672      d_t_z(llm)=d_t_z(llm-1)
673      d_q_z(llm)=d_q_z(llm-1)
674      d_u_z(llm)=d_u_z(llm-1)
675      d_v_z(llm)=d_v_z(llm-1)
676
677!Calcul de l advection verticale
678      d_t_dyn_z(:)=w_mod_cas(:)*d_t_z(:)
679      d_q_dyn_z(:)=w_mod_cas(:)*d_q_z(:)
680      d_u_dyn_z(:)=w_mod_cas(:)*d_u_z(:)
681      d_v_dyn_z(:)=w_mod_cas(:)*d_v_z(:)
682
683!wind nudging
684      if (nudge_u.gt.0.) then
685        do l=1,llm
686           u(l)=u(l)+timestep*(u_mod_cas(l)-u(l))/(nudge_u)
687        enddo
688      else
689        do l=1,llm
690        u(l) = u_mod_cas(l) 
691        enddo
692      endif
693
694      if (nudge_v.gt.0.) then
695        do l=1,llm
696           v(l)=v(l)+timestep*(v_mod_cas(l)-v(l))/(nudge_v)
697        enddo
698      else
699        do l=1,llm
700        v(l) = v_mod_cas(l) 
701        enddo
702      endif
703
704      if (nudge_w.gt.0.) then
705        do l=1,llm
706           w(l)=w(l)+timestep*(w_mod_cas(l)-w(l))/(nudge_w)
707        enddo
708      else
709        do l=1,llm
710        w(l) = w_mod_cas(l) 
711        enddo
712      endif
713
714!nudging of q and temp
715      if (nudge_t.gt.0.) then
716        do l=1,llm
717           temp(l)=temp(l)+timestep*(t_mod_cas(l)-temp(l))/(nudge_t)
718        enddo
719      endif
720      if (nudge_q.gt.0.) then
721        do l=1,llm
722           q(l,1)=q(l,1)+timestep*(q_mod_cas(l)-q(l,1))/(nudge_q)
723        enddo
724      endif
725
726      do l = 1, llm
727       omega(l) = w_mod_cas(l)
728       omega2(l)= omega(l)/rg*airefi ! flxmass_w calcule comme ds physiq
729       alpha = rd*temp(l)*(1.+(rv/rd-1.)*q(l,1))/play(l)
730
731!calcul advection
732        if ((tend_u.eq.1).and.(tend_w.eq.0)) then
733           d_u_adv(l)=du_mod_cas(l)
734        else if ((tend_u.eq.1).and.(tend_w.eq.1)) then
735           d_u_adv(l)=hu_mod_cas(l)-d_u_dyn_z(l)
736        endif
737
738        if ((tend_v.eq.1).and.(tend_w.eq.0)) then
739           d_v_adv(l)=dv_mod_cas(l)
740        else if ((tend_v.eq.1).and.(tend_w.eq.1)) then
741           d_v_adv(l)=hv_mod_cas(l)-d_v_dyn_z(l)
742        endif
743
744        if ((tend_t.eq.1).and.(tend_w.eq.0)) then
745!           d_th_adv(l)=alpha*omega(l)/rcpd+dt_mod_cas(l)
746           d_th_adv(l)=alpha*omega(l)/rcpd-dt_mod_cas(l)
747        else if ((tend_t.eq.1).and.(tend_w.eq.1)) then
748!           d_th_adv(l)=alpha*omega(l)/rcpd+ht_mod_cas(l)-d_t_dyn_z(l)
749           d_th_adv(l)=alpha*omega(l)/rcpd-ht_mod_cas(l)-d_t_dyn_z(l)
750        endif
751
752        if ((tend_q.eq.1).and.(tend_w.eq.0)) then
753!           d_q_adv(l,1)=dq_mod_cas(l)
754           d_q_adv(l,1)=-1*dq_mod_cas(l)
755        else if ((tend_q.eq.1).and.(tend_w.eq.1)) then
756!           d_q_adv(l,1)=hq_mod_cas(l)-d_q_dyn_z(l)
757           d_q_adv(l,1)=-1*hq_mod_cas(l)-d_q_dyn_z(l)
758        endif
759         
760        if (tend_rayo.eq.1) then
761           dt_cooling(l) = dtrad_mod_cas(l)
762!          print *,'dt_cooling=',dt_cooling(l)
763        else
764           dt_cooling(l) = 0.0
765        endif
766      enddo
767
768      endif ! forcing_case
769
770
771!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
772
Note: See TracBrowser for help on using the repository browser.