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

Last change on this file since 2160 was 2160, checked in by Laurent Fairhead, 10 years ago

Merged trunk changes -r2070:2158 into testing branch. Compilation problems introduced by revision r2155 have been corrected by hand

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