source: LMDZ5/branches/testing/libf/phylmd/dyn1d/1D_interp_cases.h @ 2408

Last change on this file since 2408 was 2408, checked in by Laurent Fairhead, 9 years ago

Merged trunk changes r2298:2396 into testing branch

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