source: LMDZ5/branches/testing/libf/phy1d/1D_interp_cases.h @ 1684

Last change on this file since 1684 was 1665, checked in by Laurent Fairhead, 12 years ago

Version testing basée sur la r1628

http://lmdz.lmd.jussieu.fr/utilisateurs/distribution-du-modele/versions-intermediaires


Testing release based on r1628

File size: 9.3 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     i             ,year_ini_toga,day_ju_ini_toga,nt_toga,dt_toga
48     i             ,nlev_toga,ts_toga,plev_toga,t_toga,q_toga,u_toga
49     i             ,v_toga,w_toga,ht_toga,vt_toga,hq_toga,vq_toga
50     o             ,ts_prof,plev_prof,t_prof,q_prof,u_prof,v_prof,w_prof
51     o             ,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!---------------------------------------------------------------------
82! Interpolation forcing TWPice
83!---------------------------------------------------------------------
84      if (forcing_twpice) then
85
86        print*,
87     : '#### ITAP,day,day1,(day-day1)*86400,(day-day1)*86400/dt_twpi=',
88     :    daytime,day1,(daytime-day1)*86400.,
89     :    (daytime-day1)*86400/dt_twpi
90
91! time interpolation:
92        CALL interp_toga_time(daytime,day1,annee_ref
93     i       ,year_ini_twpi,day_ju_ini_twpi,nt_twpi,dt_twpi,nlev_twpi
94     i       ,ts_twpi,plev_twpi,t_twpi,q_twpi,u_twpi,v_twpi,w_twpi
95     i       ,ht_twpi,vt_twpi,hq_twpi,vq_twpi
96     o       ,ts_proftwp,plev_proftwp,t_proftwp,q_proftwp,u_proftwp
97     o       ,v_proftwp,w_proftwp
98     o       ,ht_proftwp,vt_proftwp,hq_proftwp,vq_proftwp)
99
100! vertical interpolation:
101      CALL interp_toga_vertical(play,nlev_twpi,plev_proftwp
102     :         ,t_proftwp,q_proftwp,u_proftwp,v_proftwp,w_proftwp
103     :         ,ht_proftwp,vt_proftwp,hq_proftwp,vq_proftwp
104     :         ,t_mod,q_mod,u_mod,v_mod,w_mod
105     :         ,ht_mod,vt_mod,hq_mod,vq_mod,mxcalc)
106
107
108!calcul de l'advection verticale a partir du omega
109cCalcul des gradients verticaux
110cinitialisation
111      d_t_z(:)=0.
112      d_q_z(:)=0.
113      d_t_dyn_z(:)=0.
114      d_q_dyn_z(:)=0.
115      DO l=2,llm-1
116       d_t_z(l)=(temp(l+1)-temp(l-1))
117     &          /(play(l+1)-play(l-1))
118       d_q_z(l)=(q(l+1,1)-q(l-1,1))
119     &          /(play(l+1)-play(l-1))
120      ENDDO
121      d_t_z(1)=d_t_z(2)
122      d_q_z(1)=d_q_z(2)
123      d_t_z(llm)=d_t_z(llm-1)
124      d_q_z(llm)=d_q_z(llm-1)
125
126cCalcul de l advection verticale
127      d_t_dyn_z(:)=w_mod(:)*d_t_z(:)
128      d_q_dyn_z(:)=w_mod(:)*d_q_z(:)
129
130!wind nudging above 500m with a 2h time scale
131        do l=1,llm
132        if (nudge_wind) then
133!           if (phi(l).gt.5000.) then
134        if (phi(l).gt.0.) then
135        u(l)=u(l)
136     .      +timestep*(u_mod(l)-u(l))/(2.*3600.)
137        v(l)=v(l) 
138     .      +timestep*(v_mod(l)-v(l))/(2.*3600.)
139           endif   
140        else
141        u(l) = u_mod(l) 
142        v(l) = v_mod(l)
143        endif
144        enddo
145
146!CR:nudging of q and theta with a 6h time scale above 15km
147        if (nudge_thermo) then
148        do l=1,llm
149           zz(l)=phi(l)/9.8
150           if ((zz(l).le.16000.).and.(zz(l).gt.15000.)) then
151             zfact=(zz(l)-15000.)/1000.
152        q(l,1)=q(l,1)
153     .      +timestep*(q_mod(l)-q(l,1))/(6.*3600.)*zfact
154        temp(l)=temp(l) 
155     .      +timestep*(t_mod(l)-temp(l))/(6.*3600.)*zfact
156           else if (zz(l).gt.16000.) then
157        q(l,1)=q(l,1)
158     .      +timestep*(q_mod(l)-q(l,1))/(6.*3600.)
159        temp(l)=temp(l) 
160     .      +timestep*(t_mod(l)-temp(l))/(6.*3600.)
161           endif
162        enddo   
163        endif
164
165      do l = 1, llm
166       omega(l) = w_mod(l)
167       omega2(l)= omega(l)/rg*airefi ! flxmass_w calcule comme ds physiq
168       alpha = rd*temp(l)*(1.+(rv/rd-1.)*q(l,1))/play(l)
169!calcul de l'advection totale
170        if (cptadvw) then
171        d_th_adv(l) = alpha*omega(l)/rcpd+ht_mod(l)-d_t_dyn_z(l)
172!        print*,'temp vert adv',l,ht_mod(l),vt_mod(l),-d_t_dyn_z(l)
173        d_q_adv(l,1) = hq_mod(l)-d_q_dyn_z(l)
174!        print*,'q vert adv',l,hq_mod(l),vq_mod(l),-d_q_dyn_z(l)
175        else
176        d_th_adv(l) = alpha*omega(l)/rcpd+(ht_mod(l)+vt_mod(l))
177        d_q_adv(l,1) = (hq_mod(l)+vq_mod(l))
178        endif
179       dt_cooling(l) = 0.0
180      enddo
181
182      endif ! forcing_twpice
183!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
184!---------------------------------------------------------------------
185! Interpolation forcing Rico
186!---------------------------------------------------------------------
187      if (forcing_rico) then
188!       call lstendH(llm,omega,dt_dyn,dq_dyn,du_dyn, dv_dyn,
189!     :  q,temp,u,v,play)
190       call lstendH(llm,nqtot,omega,dt_dyn,dq_dyn,
191     :  q,temp,u,v,play)
192
193        do l=1,llm
194       d_th_adv(l) =  (dth_rico(l) +  dt_dyn(l))
195       d_q_adv(l,1) = (dqh_rico(l) +  dq_dyn(l,1))
196       d_q_adv(l,2) = 0.
197        enddo
198      endif  ! forcing_rico
199!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
200!---------------------------------------------------------------------
201! Interpolation forcing Arm_cu
202!---------------------------------------------------------------------
203      if (forcing_armcu) then
204
205        print*,
206     : '#### ITAP,day,day1,(day-day1)*86400,(day-day1)*86400/dt_armcu=',
207     :    day,day1,(day-day1)*86400.,(day-day1)*86400/dt_armcu
208
209! time interpolation:
210! ATTENTION, cet appel ne convient pas pour TOGA !!
211! revoir 1DUTILS.h et les arguments
212      CALL interp_armcu_time(daytime,day1,annee_ref
213     i            ,year_ini_armcu,day_ju_ini_armcu,nt_armcu,dt_armcu
214     i            ,nlev_armcu,sens_armcu,flat_armcu,adv_theta_armcu
215     i            ,rad_theta_armcu,adv_qt_armcu,sens_prof,flat_prof
216     i            ,adv_theta_prof,rad_theta_prof,adv_qt_prof)
217
218! vertical interpolation:
219! No vertical interpolation if nlev imposed to 19 or 40
220
221! For this case, fluxes are imposed
222       fsens=-1*sens_prof
223       flat=-1*flat_prof
224
225! Advective forcings are given in K or g/kg ... BY HOUR
226      do l = 1, llm
227       ug(l)= u_mod(l)
228       vg(l)= v_mod(l)
229       IF((phi(l)/RG).LT.1000) THEN
230         d_th_adv(l) = (adv_theta_prof + rad_theta_prof)/3600.
231         d_q_adv(l,1) = adv_qt_prof/1000./3600.
232         d_q_adv(l,2) = 0.0
233!        print *,'INF1000: phi dth dq1 dq2',
234!    :  phi(l)/RG,d_th_adv(l),d_q_adv(l,1),d_q_adv(l,2)
235       ELSEIF ((phi(l)/RG).GE.1000.AND.(phi(l)/RG).lt.3000) THEN
236         fact=((phi(l)/RG)-1000.)/2000.
237         fact=1-fact
238         d_th_adv(l) = (adv_theta_prof + rad_theta_prof)*fact/3600.
239         d_q_adv(l,1) = adv_qt_prof*fact/1000./3600.
240         d_q_adv(l,2) = 0.0
241!        print *,'SUP1000: phi fact dth dq1 dq2',
242!    :  phi(l)/RG,fact,d_th_adv(l),d_q_adv(l,1),d_q_adv(l,2)
243       ELSE
244         d_th_adv(l) = 0.0
245         d_q_adv(l,1) = 0.0
246         d_q_adv(l,2) = 0.0
247!        print *,'SUP3000: phi dth dq1 dq2',
248!    :  phi(l)/RG,d_th_adv(l),d_q_adv(l,1),d_q_adv(l,2)
249       ENDIF
250      dt_cooling(l) = 0.0 
251!     print *,'Interp armcu: phi dth dq1 dq2',
252!    :  l,phi(l),d_th_adv(l),d_q_adv(l,1),d_q_adv(l,2)
253      enddo
254      endif ! forcing_armcu
255!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
256
Note: See TracBrowser for help on using the repository browser.