source: LMDZ5/branches/testing/libf/phylmd/dyn1d/1D_read_forc_cases.h @ 2471

Last change on this file since 2471 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: 33.0 KB
Line 
1!
2! $Id: 1D_read_forc_cases.h 2408 2015-12-14 10:43:09Z fairhead $
3!
4!----------------------------------------------------------------------
5! forcing_les = .T. : Impose a constant cooling
6! forcing_radconv = .T. : Pure radiative-convective equilibrium:
7!----------------------------------------------------------------------
8
9
10      nq1=0
11      nq2=0
12
13      if (forcing_les .or. forcing_radconv                                      &
14     &    .or. forcing_GCSSold .or. forcing_fire) then
15
16      if (forcing_fire) then
17!----------------------------------------------------------------------
18!read fire forcings from fire.nc
19!----------------------------------------------------------------------
20      fich_fire='fire.nc'
21      call read_fire(fich_fire,nlev_fire,nt_fire                                &
22     &     ,height,tttprof,qtprof,uprof,vprof,e12prof                           &
23     &     ,ugprof,vgprof,wfls,dqtdxls                                          &
24     &     ,dqtdyls,dqtdtls,thlpcar)
25      write(*,*) 'Forcing FIRE lu'
26      kmax=120            ! nombre de niveaux dans les profils et forcages
27      else 
28!----------------------------------------------------------------------
29! Read profiles from files: prof.inp.001 and lscale.inp.001
30! (repris de readlesfiles)
31!----------------------------------------------------------------------
32
33      call readprofiles(nlev_max,kmax,nqtot,height,                             &
34     &           tttprof,qtprof,uprof,vprof,                                    &
35     &           e12prof,ugprof,vgprof,                                         &
36     &           wfls,dqtdxls,dqtdyls,dqtdtls,                                  &
37     &           thlpcar,qprof,nq1,nq2)
38      endif
39
40! compute altitudes of play levels.
41      zlay(1) =zsurf +  rd*tsurf*(psurf-play(1))/(rg*psurf)
42      do l = 2,llm
43        zlay(l) = zlay(l-1)+rd*tsurf*(psurf-play(1))/(rg*psurf)
44      enddo
45
46!----------------------------------------------------------------------
47! Interpolation of the profiles given on the input file to
48! model levels
49!----------------------------------------------------------------------
50      zlay(1) = zsurf +  rd*tsurf*(psurf-play(1))/(rg*psurf)
51      do l=1,llm
52        ! Above the max altutide of the input file
53
54        if (zlay(l)<height(kmax)) mxcalc=l
55
56        frac = (height(kmax)-zlay(l))/(height (kmax)-height(kmax-1))
57        ttt =tttprof(kmax)-frac*(tttprof(kmax)-tttprof(kmax-1))
58       if ((forcing_GCSSold .AND. tp_ini_GCSSold) .OR. forcing_fire)then ! pot. temp. in initial profile
59          temp(l) = ttt*(play(l)/pzero)**rkappa
60          teta(l) = ttt
61       else
62          temp(l) = ttt
63          teta(l) = ttt*(pzero/play(l))**rkappa
64       endif
65          print *,' temp,teta ',l,temp(l),teta(l)
66        q(l,1)  = qtprof(kmax)-frac*( qtprof(kmax)- qtprof(kmax-1))
67        u(l)    =  uprof(kmax)-frac*(  uprof(kmax)-  uprof(kmax-1))
68        v(l)    =  vprof(kmax)-frac*(  vprof(kmax)-  vprof(kmax-1))
69        ug(l)   = ugprof(kmax)-frac*( ugprof(kmax)- ugprof(kmax-1))
70        vg(l)   = vgprof(kmax)-frac*( vgprof(kmax)- vgprof(kmax-1))
71        IF (nq2>0) q(l,nq1:nq2)=qprof(kmax,nq1:nq2)                         &
72     &               -frac*(qprof(kmax,nq1:nq2)-qprof(kmax-1,nq1:nq2))
73        omega(l)=   wfls(kmax)-frac*(   wfls(kmax)-   wfls(kmax-1))
74
75        dq_dyn(l,1) = dqtdtls(kmax)-frac*(dqtdtls(kmax)-dqtdtls(kmax-1))
76        dt_cooling(l)=thlpcar(kmax)-frac*(thlpcar(kmax)-thlpcar(kmax-1))
77        do k=2,kmax
78          frac = (height(k)-zlay(l))/(height(k)-height(k-1))
79          if(l==1) print*,'k, height, tttprof',k,height(k),tttprof(k)
80          if(zlay(l)>height(k-1).and.zlay(l)<height(k)) then
81            ttt =tttprof(k)-frac*(tttprof(k)-tttprof(k-1))
82       if ((forcing_GCSSold .AND. tp_ini_GCSSold) .OR. forcing_fire)then ! pot. temp. in initial profile
83          temp(l) = ttt*(play(l)/pzero)**rkappa
84          teta(l) = ttt
85       else
86          temp(l) = ttt
87          teta(l) = ttt*(pzero/play(l))**rkappa
88       endif
89          print *,' temp,teta ',l,temp(l),teta(l)
90            q(l,1)  = qtprof(k)-frac*( qtprof(k)- qtprof(k-1))
91            u(l)    =  uprof(k)-frac*(  uprof(k)-  uprof(k-1))
92            v(l)    =  vprof(k)-frac*(  vprof(k)-  vprof(k-1))
93            ug(l)   = ugprof(k)-frac*( ugprof(k)- ugprof(k-1))
94            vg(l)   = vgprof(k)-frac*( vgprof(k)- vgprof(k-1))
95            IF (nq2>0) q(l,nq1:nq2)=qprof(k,nq1:nq2)                        &
96     &                   -frac*(qprof(k,nq1:nq2)-qprof(k-1,nq1:nq2))
97            omega(l)=   wfls(k)-frac*(   wfls(k)-   wfls(k-1))
98            dq_dyn(l,1)=dqtdtls(k)-frac*(dqtdtls(k)-dqtdtls(k-1))
99            dt_cooling(l)=thlpcar(k)-frac*(thlpcar(k)-thlpcar(k-1))
100          elseif(zlay(l)<height(1)) then ! profils uniformes pour z<height(1)
101            ttt =tttprof(1)
102       if ((forcing_GCSSold .AND. tp_ini_GCSSold) .OR. forcing_fire)then ! pot. temp. in initial profile
103          temp(l) = ttt*(play(l)/pzero)**rkappa
104          teta(l) = ttt
105       else
106          temp(l) = ttt
107          teta(l) = ttt*(pzero/play(l))**rkappa
108       endif
109            q(l,1)  = qtprof(1)
110            u(l)    =  uprof(1)
111            v(l)    =  vprof(1)
112            ug(l)   = ugprof(1)
113            vg(l)   = vgprof(1)
114            omega(l)=   wfls(1)
115            IF (nq2>0) q(l,nq1:nq2)=qprof(1,nq1:nq2)
116            dq_dyn(l,1)  =dqtdtls(1)
117            dt_cooling(l)=thlpcar(1)
118          endif
119        enddo
120
121        temp(l)=max(min(temp(l),350.),150.)
122        rho(l)  = play(l)/(rd*temp(l)*(1.+(rv/rd-1.)*q(l,1)))
123        if (l .lt. llm) then
124          zlay(l+1) = zlay(l) + (play(l)-play(l+1))/(rg*rho(l))
125        endif
126        omega2(l)=-rho(l)*omega(l)
127        omega(l)= omega(l)*(-rg*rho(l)) !en Pa/s
128        if (l>1) then
129        if(zlay(l-1)>height(kmax)) then
130           omega(l)=0.0
131           omega2(l)=0.0
132        endif   
133        endif
134        if(q(l,1)<0.) q(l,1)=0.0
135        q(l,2)  = 0.0
136      enddo
137
138      endif ! forcing_les .or. forcing_GCSSold .or. forcing_fire
139!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
140!---------------------------------------------------------------------
141! Forcing for GCSSold:
142!---------------------------------------------------------------------
143      if (forcing_GCSSold) then
144       fich_gcssold_ctl = './forcing.ctl'
145       fich_gcssold_dat = './forcing8.dat'
146       call copie(llm,play,psurf,fich_gcssold_ctl)
147       call get_uvd2(it,timestep,fich_gcssold_ctl,fich_gcssold_dat,         &
148     &               ht_gcssold,hq_gcssold,hw_gcssold,                      &
149     &               hu_gcssold,hv_gcssold,                                 &
150     &               hthturb_gcssold,hqturb_gcssold,Ts_gcssold,             &
151     &               imp_fcg_gcssold,ts_fcg_gcssold,                        &
152     &               Tp_fcg_gcssold,Turb_fcg_gcssold)
153       print *,' get_uvd2 -> hqturb_gcssold ',hqturb_gcssold
154      endif ! forcing_GCSSold
155!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
156!---------------------------------------------------------------------
157! Forcing for RICO:
158!---------------------------------------------------------------------
159      if (forcing_rico) then
160
161!       call writefield_phy('omega', omega,llm+1)
162      fich_rico = 'rico.txt'
163       call read_rico(fich_rico,nlev_rico,ps_rico,play                      &
164     &             ,ts_rico,t_rico,q_rico,u_rico,v_rico,w_rico              &
165     &             ,dth_rico,dqh_rico)
166        print*, ' on a lu et prepare RICO'
167
168       mxcalc=llm
169       print *, airefi, ' airefi '
170       do l = 1, llm
171       rho(l)  = play(l)/(rd*t_rico(l)*(1.+(rv/rd-1.)*q_rico(l)))
172       temp(l) = t_rico(l)
173       q(l,1) = q_rico(l)
174       q(l,2) = 0.0
175       u(l) = u_rico(l)
176       v(l) = v_rico(l)
177       ug(l)=u_rico(l)
178       vg(l)=v_rico(l)
179       omega(l) = -w_rico(l)*rg
180       omega2(l) = omega(l)/rg*airefi
181       enddo
182      endif
183!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
184!---------------------------------------------------------------------
185! Forcing from TOGA-COARE experiment (Ciesielski et al. 2002) :
186!---------------------------------------------------------------------
187
188      if (forcing_toga) then
189
190! read TOGA-COARE forcing (native vertical grid, nt_toga timesteps):
191      fich_toga = './d_toga/ifa_toga_coare_v21_dime.txt'
192      CALL read_togacoare(fich_toga,nlev_toga,nt_toga                       &
193     &         ,ts_toga,plev_toga,t_toga,q_toga,u_toga,v_toga,w_toga        &
194     &         ,ht_toga,vt_toga,hq_toga,vq_toga)
195
196       write(*,*) 'Forcing TOGA lu'
197
198! time interpolation for initial conditions:
199      write(*,*) 'AVT 1ere INTERPOLATION: day,day1 = ',day,day1
200      CALL interp_toga_time(daytime,day1,annee_ref                          &
201     &             ,year_ini_toga,day_ju_ini_toga,nt_toga,dt_toga           &
202     &             ,nlev_toga,ts_toga,plev_toga,t_toga,q_toga,u_toga        &
203     &             ,v_toga,w_toga,ht_toga,vt_toga,hq_toga,vq_toga           &
204     &             ,ts_prof,plev_prof,t_prof,q_prof,u_prof,v_prof,w_prof    &
205     &             ,ht_prof,vt_prof,hq_prof,vq_prof)
206
207! vertical interpolation:
208      CALL interp_toga_vertical(play,nlev_toga,plev_prof                    &
209     &         ,t_prof,q_prof,u_prof,v_prof,w_prof                          &
210     &         ,ht_prof,vt_prof,hq_prof,vq_prof                             &
211     &         ,t_mod,q_mod,u_mod,v_mod,w_mod                               &
212     &         ,ht_mod,vt_mod,hq_mod,vq_mod,mxcalc)
213       write(*,*) 'Profil initial forcing TOGA interpole'
214
215! initial and boundary conditions :
216      tsurf = ts_prof
217      write(*,*) 'SST initiale: ',tsurf
218      do l = 1, llm
219       temp(l) = t_mod(l)
220       q(l,1) = q_mod(l)
221       q(l,2) = 0.0
222       u(l) = u_mod(l)
223       v(l) = v_mod(l)
224       omega(l) = w_mod(l)
225       omega2(l)=omega(l)/rg*airefi ! flxmass_w calcule comme ds physiq
226!?       rho(l)  = play(l)/(rd*temp(l)*(1.+(rv/rd-1.)*q(l,1)))
227!?       omega2(l)=-rho(l)*omega(l)
228       alpha = rd*temp(l)*(1.+(rv/rd-1.)*q(l,1))/play(l)
229       d_th_adv(l) = alpha*omega(l)/rcpd-(ht_mod(l)+vt_mod(l))
230       d_q_adv(l,1) = -(hq_mod(l)+vq_mod(l))
231       d_q_adv(l,2) = 0.0
232      enddo
233
234      endif ! forcing_toga
235!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
236!---------------------------------------------------------------------
237! Forcing from TWPICE experiment (Shaocheng et al. 2010) :
238!---------------------------------------------------------------------
239
240      if (forcing_twpice) then
241!read TWP-ICE forcings
242     fich_twpice='d_twpi/twp180iopsndgvarana_v2.1_C3.c1.20060117.000000.cdf'
243      call read_twpice(fich_twpice,nlev_twpi,nt_twpi                        &
244     &     ,ts_twpi,plev_twpi,t_twpi,q_twpi,u_twpi,v_twpi,w_twpi            &
245     &     ,ht_twpi,vt_twpi,hq_twpi,vq_twpi)
246
247      write(*,*) 'Forcing TWP-ICE lu'
248!Time interpolation for initial conditions using TOGA interpolation routine
249         write(*,*) 'AVT 1ere INTERPOLATION: day,day1 = ',daytime,day1   
250      CALL interp_toga_time(daytime,day1,annee_ref                          &
251     &          ,year_ini_twpi,day_ju_ini_twpi,nt_twpi,dt_twpi,nlev_twpi    &
252     &             ,ts_twpi,plev_twpi,t_twpi,q_twpi,u_twpi,v_twpi,w_twpi    &
253     &             ,ht_twpi,vt_twpi,hq_twpi,vq_twpi                         &
254     &             ,ts_proftwp,plev_proftwp,t_proftwp,q_proftwp             &
255     &             ,u_proftwp,v_proftwp,w_proftwp                           &
256     &             ,ht_proftwp,vt_proftwp,hq_proftwp,vq_proftwp)
257
258! vertical interpolation using TOGA interpolation routine:
259!      write(*,*)'avant interp vert', t_proftwp
260      CALL interp_toga_vertical(play,nlev_twpi,plev_proftwp                 &
261     &         ,t_proftwp,q_proftwp,u_proftwp,v_proftwp,w_proftwp           &
262     &         ,ht_proftwp,vt_proftwp,hq_proftwp,vq_proftwp                 &
263     &         ,t_mod,q_mod,u_mod,v_mod,w_mod                               &
264     &         ,ht_mod,vt_mod,hq_mod,vq_mod,mxcalc)
265!       write(*,*) 'Profil initial forcing TWP-ICE interpole',t_mod
266
267! initial and boundary conditions :
268!      tsurf = ts_proftwp
269      write(*,*) 'SST initiale: ',tsurf
270      do l = 1, llm
271       temp(l) = t_mod(l)
272       q(l,1) = q_mod(l)
273       q(l,2) = 0.0
274       u(l) = u_mod(l)
275       v(l) = v_mod(l)
276       omega(l) = w_mod(l)
277       omega2(l)=omega(l)/rg*airefi ! flxmass_w calcule comme ds physiq
278
279       alpha = rd*temp(l)*(1.+(rv/rd-1.)*q(l,1))/play(l)
280!on applique le forcage total au premier pas de temps
281!attention: signe different de toga
282       d_th_adv(l) = alpha*omega(l)/rcpd+(ht_mod(l)+vt_mod(l))
283       d_q_adv(l,1) = (hq_mod(l)+vq_mod(l))
284       d_q_adv(l,2) = 0.0
285      enddo     
286       
287      endif !forcing_twpice
288
289!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
290!---------------------------------------------------------------------
291! Forcing from AMMA experiment (Couvreux et al. 2010) :
292!---------------------------------------------------------------------
293
294      if (forcing_amma) then
295
296      call read_1D_cases
297
298      write(*,*) 'Forcing AMMA lu'
299
300!champs initiaux:
301      do k=1,nlev_amma
302         th_ammai(k)=th_amma(k)
303         q_ammai(k)=q_amma(k)
304         u_ammai(k)=u_amma(k)
305         v_ammai(k)=v_amma(k)
306         vitw_ammai(k)=vitw_amma(k,12)
307         ht_ammai(k)=ht_amma(k,12)
308         hq_ammai(k)=hq_amma(k,12)
309         vt_ammai(k)=0.
310         vq_ammai(k)=0.
311      enddo   
312      omega(:)=0.     
313      omega2(:)=0.
314      rho(:)=0.
315! vertical interpolation using TOGA interpolation routine:
316!      write(*,*)'avant interp vert', t_proftwp
317      CALL interp_toga_vertical(play,nlev_amma,plev_amma                    &
318     &         ,th_ammai,q_ammai,u_ammai,v_ammai,vitw_ammai                 &
319     &         ,ht_ammai,vt_ammai,hq_ammai,vq_ammai                         &
320     &         ,t_mod,q_mod,u_mod,v_mod,w_mod                               &
321     &         ,ht_mod,vt_mod,hq_mod,vq_mod,mxcalc)
322!       write(*,*) 'Profil initial forcing TWP-ICE interpole',t_mod
323
324! initial and boundary conditions :
325!      tsurf = ts_proftwp
326      write(*,*) 'SST initiale mxcalc: ',tsurf,mxcalc
327      do l = 1, llm
328! Ligne du dessous ?? decommenter si on lit theta au lieu de temp
329!      temp(l) = t_mod(l)*(play(l)/pzero)**rkappa
330       temp(l) = t_mod(l) 
331       q(l,1) = q_mod(l)
332       q(l,2) = 0.0
333!      print *,'read_forc: l,temp,q=',l,temp(l),q(l,1)
334       u(l) = u_mod(l)
335       v(l) = v_mod(l)
336       rho(l)  = play(l)/(rd*temp(l)*(1.+(rv/rd-1.)*q(l,1)))
337       omega(l) = w_mod(l)*(-rg*rho(l))
338       omega2(l)=omega(l)/rg*airefi ! flxmass_w calcule comme ds physiq
339
340       alpha = rd*temp(l)*(1.+(rv/rd-1.)*q(l,1))/play(l)
341!on applique le forcage total au premier pas de temps
342!attention: signe different de toga
343       d_th_adv(l) = alpha*omega(l)/rcpd+ht_mod(l)
344!forcage en th
345!       d_th_adv(l) = ht_mod(l)
346       d_q_adv(l,1) = hq_mod(l)
347       d_q_adv(l,2) = 0.0
348       dt_cooling(l)=0.
349      enddo     
350       write(*,*) 'Prof initeforcing AMMA interpole temp39',temp(39)
351     
352
353!     ok_flux_surf=.false.
354      fsens=-1.*sens_amma(12)
355      flat=-1.*lat_amma(12)
356       
357      endif !forcing_amma
358
359
360!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
361!---------------------------------------------------------------------
362! Forcing from DICE experiment (see file DICE_protocol_vn2-3.pdf)
363!---------------------------------------------------------------------
364
365      if (forcing_dice) then
366!read DICE forcings
367      fich_dice='dice_driver.nc'
368      call read_dice(fich_dice,nlev_dice,nt_dice                    &
369     &     ,zz_dice,plev_dice,th_dice,qv_dice,u_dice,v_dice,o3_dice &
370     &     ,shf_dice,lhf_dice,lwup_dice,swup_dice,tg_dice,ustar_dice& 
371     &     ,psurf_dice,ug_dice,vg_dice,ht_dice,hq_dice              &
372     &     ,hu_dice,hv_dice,w_dice,omega_dice)
373
374      write(*,*) 'Forcing DICE lu'
375
376!champs initiaux:
377      do k=1,nlev_dice
378         th_dicei(k)=th_dice(k)
379         qv_dicei(k)=qv_dice(k)
380         u_dicei(k)=u_dice(k)
381         v_dicei(k)=v_dice(k)
382         o3_dicei(k)=o3_dice(k)
383         ht_dicei(k)=ht_dice(k,1)
384         hq_dicei(k)=hq_dice(k,1)
385         hu_dicei(k)=hu_dice(k,1)
386         hv_dicei(k)=hv_dice(k,1)
387         w_dicei(k)=w_dice(k,1)
388         omega_dicei(k)=omega_dice(k,1)
389      enddo   
390      omega(:)=0.     
391      omega2(:)=0.
392      rho(:)=0.
393! vertical interpolation using TOGA interpolation routine:
394!      write(*,*)'avant interp vert', t_proftwp
395!
396!     CALL interp_dice_time(daytime,day1,annee_ref
397!    i             ,year_ini_dice,day_ju_ini_dice,nt_dice,dt_dice
398!    i             ,nlev_dice,shf_dice,lhf_dice,lwup_dice,swup_dice
399!    i             ,tg_dice,ustar_dice,psurf_dice,ug_dice,vg_dice
400!    i             ,ht_dice,hq_dice,hu_dice,hv_dice,w_dice,omega_dice
401!    o             ,shf_prof,lhf_prof,lwup_prof,swup_prof,tg_prof
402!    o             ,ustar_prof,psurf_prof,ug_profd,vg_profd
403!    o             ,ht_profd,hq_profd,hu_profd,hv_profd,w_profd
404!    o             ,omega_profd)
405
406      CALL interp_dice_vertical(play,nlev_dice,nt_dice,plev_dice       &
407     &         ,th_dicei,qv_dicei,u_dicei,v_dicei,o3_dicei             &
408     &         ,ht_dicei,hq_dicei,hu_dicei,hv_dicei,w_dicei,omega_dicei&
409     &         ,th_mod,qv_mod,u_mod,v_mod,o3_mod                       &
410     &         ,ht_mod,hq_mod,hu_mod,hv_mod,w_mod,omega_mod,mxcalc)
411
412! Pour tester les advections horizontales de T et Q, on met w_mod et omega_mod ?? zero (MPL 20131108)
413!     w_mod(:,:)=0.
414!     omega_mod(:,:)=0.
415
416!       write(*,*) 'Profil initial forcing DICE interpole',t_mod
417! Les forcages DICE sont donnes /jour et non /seconde !
418      ht_mod(:)=ht_mod(:)/86400.
419      hq_mod(:)=hq_mod(:)/86400.
420      hu_mod(:)=hu_mod(:)/86400.
421      hv_mod(:)=hv_mod(:)/86400.
422
423! initial and boundary conditions :
424      write(*,*) 'SST initiale mxcalc: ',tsurf,mxcalc
425      do l = 1, llm
426! Ligne du dessous ?? decommenter si on lit theta au lieu de temp
427       temp(l) = th_mod(l)*(play(l)/pzero)**rkappa
428!      temp(l) = t_mod(l) 
429       q(l,1) = qv_mod(l)
430       q(l,2) = 0.0
431!      print *,'read_forc: l,temp,q=',l,temp(l),q(l,1)
432       u(l) = u_mod(l)
433       v(l) = v_mod(l)
434       ug(l)=ug_dice(1)
435       vg(l)=vg_dice(1)
436       rho(l)  = play(l)/(rd*temp(l)*(1.+(rv/rd-1.)*q(l,1)))
437!      omega(l) = w_mod(l)*(-rg*rho(l))
438       omega(l) = omega_mod(l)
439       omega2(l)=omega(l)/rg*airefi ! flxmass_w calcule comme ds physiq
440
441       alpha = rd*temp(l)*(1.+(rv/rd-1.)*q(l,1))/play(l)
442!on applique le forcage total au premier pas de temps
443!attention: signe different de toga
444       d_th_adv(l) = alpha*omega(l)/rcpd+ht_mod(l)
445!forcage en th
446!       d_th_adv(l) = ht_mod(l)
447       d_q_adv(l,1) = hq_mod(l)
448       d_q_adv(l,2) = 0.0
449       dt_cooling(l)=0.
450      enddo     
451       write(*,*) 'Profil initial forcing DICE interpole temp39',temp(39)
452     
453
454!     ok_flux_surf=.false.
455      fsens=-1.*shf_dice(1)
456      flat=-1.*lhf_dice(1)
457! Le cas Dice doit etre force avec ustar mais on peut simplifier en forcant par
458! le coefficient de trainee en surface cd**2=ustar*vent(k=1)
459! On commence ici a stocker ustar dans cdrag puis on terminera le calcul dans pbl_surface
460! MPL 05082013
461      ust=ustar_dice(1)
462      tg=tg_dice(1)
463      print *,'ust= ',ust
464      IF (tsurf .LE. 0.) THEN
465       tsurf= tg_dice(1)
466      ENDIF
467      psurf= psurf_dice(1)
468      solsw_in = (1.-albedo)/albedo*swup_dice(1)
469      sollw_in = (0.7*RSIGMA*temp(1)**4)-lwup_dice(1)
470      PRINT *,'1D_READ_FORC : solsw, sollw',solsw_in,sollw_in
471      endif !forcing_dice
472
473!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
474!---------------------------------------------------------------------
475! Forcing from Arm_Cu case                   
476! For this case, ifa_armcu.txt contains sensible, latent heat fluxes
477! large scale advective forcing,radiative forcing
478! and advective tendency of theta and qt to be applied
479!---------------------------------------------------------------------
480
481      if (forcing_armcu) then
482! read armcu forcing :
483       write(*,*) 'Avant lecture Forcing Arm_Cu'
484      fich_armcu = './ifa_armcu.txt'
485      CALL read_armcu(fich_armcu,nlev_armcu,nt_armcu,                       &
486     & sens_armcu,flat_armcu,adv_theta_armcu,                               &
487     & rad_theta_armcu,adv_qt_armcu)
488       write(*,*) 'Forcing Arm_Cu lu'
489
490!----------------------------------------------------------------------
491! Read profiles from file: prof.inp.19 or prof.inp.40 
492! For this case, profiles are given for two vertical resolution
493! 19 or 40 levels
494!
495! Comment from: http://www.knmi.nl/samenw/eurocs/ARM/profiles.html
496! Note that the initial profiles contain no liquid water! 
497! (so potential temperature can be interpreted as liquid water
498! potential temperature and water vapor as total water)
499! profiles are given at full levels
500!----------------------------------------------------------------------
501
502      call readprofile_armcu(nlev_max,kmax,height,play_mod,u_mod,           &
503     &           v_mod,theta_mod,t_mod,qv_mod,rv_mod,ap,bp)
504
505! time interpolation for initial conditions:
506      write(*,*) 'AVT 1ere INTERPOLATION: day,day1 = ',day,day1
507
508      print *,'Avant interp_armcu_time'
509      print *,'daytime=',daytime
510      print *,'day1=',day1
511      print *,'annee_ref=',annee_ref
512      print *,'year_ini_armcu=',year_ini_armcu
513      print *,'day_ju_ini_armcu=',day_ju_ini_armcu
514      print *,'nt_armcu=',nt_armcu
515      print *,'dt_armcu=',dt_armcu
516      print *,'nlev_armcu=',nlev_armcu
517      CALL interp_armcu_time(daytime,day1,annee_ref                         &
518     &            ,year_ini_armcu,day_ju_ini_armcu,nt_armcu,dt_armcu        &
519     &            ,nlev_armcu,sens_armcu,flat_armcu,adv_theta_armcu         &
520     &            ,rad_theta_armcu,adv_qt_armcu,sens_prof,flat_prof         &
521     &            ,adv_theta_prof,rad_theta_prof,adv_qt_prof)
522       write(*,*) 'Forcages interpoles dans temps'
523
524! No vertical interpolation if nlev imposed to 19 or 40
525! The vertical grid stops at 4000m # 600hPa
526      mxcalc=llm
527
528! initial and boundary conditions :
529!     tsurf = ts_prof
530! tsurf read in lmdz1d.def
531      write(*,*) 'Tsurf initiale: ',tsurf
532      do l = 1, llm
533       play(l)=play_mod(l)*100.
534       presnivs(l)=play(l)
535       zlay(l)=height(l)
536       temp(l) = t_mod(l)
537       teta(l)=theta_mod(l)
538       q(l,1) = qv_mod(l)/1000.
539! No liquid water in the initial profil
540       q(l,2) = 0.
541       u(l) = u_mod(l)
542       ug(l)= u_mod(l)
543       v(l) = v_mod(l)
544       vg(l)= v_mod(l)
545! Advective forcings are given in K or g/kg ... per HOUR
546!      IF(height(l).LT.1000) THEN
547!        d_th_adv(l) = (adv_theta_prof + rad_theta_prof)/3600.
548!        d_q_adv(l,1) = adv_qt_prof/1000./3600.
549!        d_q_adv(l,2) = 0.0
550!      ELSEIF (height(l).GE.1000.AND.height(l).LT.3000) THEN
551!        d_th_adv(l) = (adv_theta_prof + rad_theta_prof)*
552!    :               (1-(height(l)-1000.)/2000.)
553!        d_th_adv(l) = d_th_adv(l)/3600.
554!        d_q_adv(l,1) = adv_qt_prof*(1-(height(l)-1000.)/2000.)
555!        d_q_adv(l,1) = d_q_adv(l,1)/1000./3600.
556!        d_q_adv(l,2) = 0.0
557!      ELSE
558!        d_th_adv(l) = 0.0
559!        d_q_adv(l,1) = 0.0
560!        d_q_adv(l,2) = 0.0
561!      ENDIF
562      enddo
563! plev at half levels is given in proh.inp.19 or proh.inp.40 files
564      plev(1)= ap(llm+1)+bp(llm+1)*psurf
565      do l = 1, llm
566      plev(l+1) = ap(llm-l+1)+bp(llm-l+1)*psurf
567      print *,'Read_forc: l height play plev zlay temp',                    &
568     &   l,height(l),play(l),plev(l),zlay(l),temp(l)
569      enddo
570! For this case, fluxes are imposed
571       fsens=-1*sens_prof
572       flat=-1*flat_prof
573
574      endif ! forcing_armcu
575!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
576!---------------------------------------------------------------------
577! Forcing from transition case of Irina Sandu                 
578!---------------------------------------------------------------------
579
580      if (forcing_sandu) then
581       write(*,*) 'Avant lecture Forcing SANDU'
582
583! read sanduref forcing :
584      fich_sandu = './ifa_sanduref.txt'
585      CALL read_sandu(fich_sandu,nlev_sandu,nt_sandu,ts_sandu)
586
587       write(*,*) 'Forcing SANDU lu'
588
589!----------------------------------------------------------------------
590! Read profiles from file: prof.inp.001 
591!----------------------------------------------------------------------
592
593      call readprofile_sandu(nlev_max,kmax,height,plev_profs,t_profs,       &
594     &           thl_profs,q_profs,u_profs,v_profs,                         &
595     &           w_profs,omega_profs,o3mmr_profs)
596
597! time interpolation for initial conditions:
598      write(*,*) 'AVT 1ere INTERPOLATION: day,day1 = ',day,day1
599! ATTENTION, cet appel ne convient pas pour le cas SANDU !!
600! revoir 1DUTILS.h et les arguments
601
602      print *,'Avant interp_sandu_time'
603      print *,'daytime=',daytime
604      print *,'day1=',day1
605      print *,'annee_ref=',annee_ref
606      print *,'year_ini_sandu=',year_ini_sandu
607      print *,'day_ju_ini_sandu=',day_ju_ini_sandu
608      print *,'nt_sandu=',nt_sandu
609      print *,'dt_sandu=',dt_sandu
610      print *,'nlev_sandu=',nlev_sandu
611      CALL interp_sandu_time(daytime,day1,annee_ref                         &
612     &             ,year_ini_sandu,day_ju_ini_sandu,nt_sandu,dt_sandu       &
613     &             ,nlev_sandu                                              &
614     &             ,ts_sandu,ts_prof)
615
616! vertical interpolation:
617      print *,'Avant interp_vertical: nlev_sandu=',nlev_sandu
618      CALL interp_sandu_vertical(play,nlev_sandu,plev_profs                 &
619     &         ,t_profs,thl_profs,q_profs,u_profs,v_profs,w_profs           &
620     &         ,omega_profs,o3mmr_profs                                     &
621     &         ,t_mod,thl_mod,q_mod,u_mod,v_mod,w_mod                       &
622     &         ,omega_mod,o3mmr_mod,mxcalc)
623       write(*,*) 'Profil initial forcing SANDU interpole'
624
625! initial and boundary conditions :
626      tsurf = ts_prof
627      write(*,*) 'SST initiale: ',tsurf
628      do l = 1, llm
629       temp(l) = t_mod(l)
630       tetal(l)=thl_mod(l)
631       q(l,1) = q_mod(l)
632       q(l,2) = 0.0
633       u(l) = u_mod(l)
634       v(l) = v_mod(l)
635       w(l) = w_mod(l)
636       omega(l) = omega_mod(l)
637       omega2(l)=omega(l)/rg*airefi ! flxmass_w calcule comme ds physiq
638!?       rho(l)  = play(l)/(rd*temp(l)*(1.+(rv/rd-1.)*q(l,1)))
639!?       omega2(l)=-rho(l)*omega(l)
640       alpha = rd*temp(l)*(1.+(rv/rd-1.)*q(l,1))/play(l)
641!      d_th_adv(l) = alpha*omega(l)/rcpd+vt_mod(l)
642!      d_q_adv(l,1) = vq_mod(l)
643       d_th_adv(l) = alpha*omega(l)/rcpd
644       d_q_adv(l,1) = 0.0
645       d_q_adv(l,2) = 0.0
646      enddo
647
648      endif ! forcing_sandu
649!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
650!---------------------------------------------------------------------
651! Forcing from Astex case
652!---------------------------------------------------------------------
653
654      if (forcing_astex) then
655       write(*,*) 'Avant lecture Forcing Astex'
656
657! read astex forcing :
658      fich_astex = './ifa_astex.txt'
659      CALL read_astex(fich_astex,nlev_astex,nt_astex,div_astex,ts_astex,    &
660     &  ug_astex,vg_astex,ufa_astex,vfa_astex)
661
662       write(*,*) 'Forcing Astex lu'
663
664!----------------------------------------------------------------------
665! Read profiles from file: prof.inp.001
666!----------------------------------------------------------------------
667
668      call readprofile_astex(nlev_max,kmax,height,plev_profa,t_profa,       &
669     &           thl_profa,qv_profa,ql_profa,qt_profa,u_profa,v_profa,      &
670     &           w_profa,tke_profa,o3mmr_profa)
671
672! time interpolation for initial conditions:
673      write(*,*) 'AVT 1ere INTERPOLATION: day,day1 = ',day,day1
674! ATTENTION, cet appel ne convient pas pour le cas SANDU !!
675! revoir 1DUTILS.h et les arguments
676
677      print *,'Avant interp_astex_time'
678      print *,'daytime=',daytime
679      print *,'day1=',day1
680      print *,'annee_ref=',annee_ref
681      print *,'year_ini_astex=',year_ini_astex
682      print *,'day_ju_ini_astex=',day_ju_ini_astex
683      print *,'nt_astex=',nt_astex
684      print *,'dt_astex=',dt_astex
685      print *,'nlev_astex=',nlev_astex
686      CALL interp_astex_time(daytime,day1,annee_ref                         &
687     &             ,year_ini_astex,day_ju_ini_astex,nt_astex,dt_astex       &
688     &             ,nlev_astex,div_astex,ts_astex,ug_astex,vg_astex         &
689     &             ,ufa_astex,vfa_astex,div_prof,ts_prof,ug_prof,vg_prof    &
690     &             ,ufa_prof,vfa_prof)
691
692! vertical interpolation:
693      print *,'Avant interp_vertical: nlev_astex=',nlev_astex
694      CALL interp_astex_vertical(play,nlev_astex,plev_profa                 &
695     &         ,t_profa,thl_profa,qv_profa,ql_profa,qt_profa                &
696     &         ,u_profa,v_profa,w_profa,tke_profa,o3mmr_profa               &
697     &         ,t_mod,thl_mod,qv_mod,ql_mod,qt_mod,u_mod,v_mod,w_mod        &
698     &         ,tke_mod,o3mmr_mod,mxcalc)
699       write(*,*) 'Profil initial forcing Astex interpole'
700
701! initial and boundary conditions :
702      tsurf = ts_prof
703      write(*,*) 'SST initiale: ',tsurf
704      do l = 1, llm
705       temp(l) = t_mod(l)
706       tetal(l)=thl_mod(l)
707       q(l,1) = qv_mod(l)
708       q(l,2) = ql_mod(l)
709       u(l) = u_mod(l)
710       v(l) = v_mod(l)
711       w(l) = w_mod(l)
712       omega(l) = w_mod(l)
713!      omega2(l)=omega(l)/rg*airefi ! flxmass_w calcule comme ds physiq
714!      rho(l)  = play(l)/(rd*temp(l)*(1.+(rv/rd-1.)*q(l,1)))
715!      omega2(l)=-rho(l)*omega(l)
716       alpha = rd*temp(l)*(1.+(rv/rd-1.)*q(l,1))/play(l)
717!      d_th_adv(l) = alpha*omega(l)/rcpd+vt_mod(l)
718!      d_q_adv(l,1) = vq_mod(l)
719       d_th_adv(l) = alpha*omega(l)/rcpd
720       d_q_adv(l,1) = 0.0
721       d_q_adv(l,2) = 0.0
722      enddo
723
724      endif ! forcing_astex
725!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
726!---------------------------------------------------------------------
727! Forcing from standard case :
728!---------------------------------------------------------------------
729
730      if (forcing_case) then
731
732         write(*,*),'avant call read_1D_cas'
733         call read_1D_cas
734         write(*,*) 'Forcing read'
735
736!Time interpolation for initial conditions using TOGA interpolation routine
737         write(*,*) 'AVT 1ere INTERPOLATION: day,day1 = ',daytime,day1   
738      CALL interp_case_time(day,day1,annee_ref                                                              &
739!    &         ,year_ini_cas,day_ju_ini_cas,nt_cas,pdt_cas,nlev_cas                                         &
740     &         ,nt_cas,nlev_cas                                                                             &
741     &         ,ts_cas,plev_cas,t_cas,q_cas,u_cas,v_cas                                                     &
742     &         ,ug_cas,vg_cas,vitw_cas,du_cas,hu_cas,vu_cas                                                 &
743     &         ,dv_cas,hv_cas,vv_cas,dt_cas,ht_cas,vt_cas,dtrad_cas                                         &
744     &         ,dq_cas,hq_cas,vq_cas,lat_cas,sens_cas,ustar_cas                                             &
745     &         ,uw_cas,vw_cas,q1_cas,q2_cas                                                                 &
746     &         ,ts_prof_cas,plev_prof_cas,t_prof_cas,q_prof_cas,u_prof_cas,v_prof_cas                       &
747     &         ,ug_prof_cas,vg_prof_cas,vitw_prof_cas,du_prof_cas,hu_prof_cas,vu_prof_cas                   &
748     &         ,dv_prof_cas,hv_prof_cas,vv_prof_cas,dt_prof_cas,ht_prof_cas,vt_prof_cas,dtrad_prof_cas      &
749     &         ,dq_prof_cas,hq_prof_cas,vq_prof_cas,lat_prof_cas,sens_prof_cas,ustar_prof_cas               &
750     &         ,uw_prof_cas,vw_prof_cas,q1_prof_cas,q2_prof_cas)
751
752! vertical interpolation using TOGA interpolation routine:
753!      write(*,*)'avant interp vert', t_prof
754      CALL interp_case_vertical(play,nlev_cas,plev_prof_cas            &
755     &         ,t_prof_cas,q_prof_cas,u_prof_cas,v_prof_cas,ug_prof_cas,vg_prof_cas,vitw_prof_cas    &
756     &         ,du_prof_cas,hu_prof_cas,vu_prof_cas,dv_prof_cas,hv_prof_cas,vv_prof_cas           &
757     &         ,dt_prof_cas,ht_prof_cas,vt_prof_cas,dtrad_prof_cas,dq_prof_cas,hq_prof_cas,vq_prof_cas           &
758     &         ,t_mod_cas,q_mod_cas,u_mod_cas,v_mod_cas,ug_mod_cas,vg_mod_cas,w_mod_cas           &
759     &         ,du_mod_cas,hu_mod_cas,vu_mod_cas,dv_mod_cas,hv_mod_cas,vv_mod_cas               &
760     &         ,dt_mod_cas,ht_mod_cas,vt_mod_cas,dtrad_mod_cas,dq_mod_cas,hq_mod_cas,vq_mod_cas,mxcalc)
761!       write(*,*) 'Profil initial forcing case interpole',t_mod
762
763! initial and boundary conditions :
764!      tsurf = ts_prof_cas
765      ts_cur = ts_prof_cas
766      psurf=plev_prof_cas(1)
767      write(*,*) 'SST initiale: ',tsurf
768      do l = 1, llm
769       temp(l) = t_mod_cas(l)
770       q(l,1) = q_mod_cas(l)
771       q(l,2) = 0.0
772       u(l) = u_mod_cas(l)
773       v(l) = v_mod_cas(l)
774       omega(l) = w_mod_cas(l)
775       omega2(l)=omega(l)/rg*airefi ! flxmass_w calcule comme ds physiq
776
777       alpha = rd*temp(l)*(1.+(rv/rd-1.)*q(l,1))/play(l)
778!on applique le forcage total au premier pas de temps
779!attention: signe different de toga
780       d_th_adv(l) = alpha*omega(l)/rcpd+(ht_mod_cas(l)+vt_mod_cas(l))
781       d_q_adv(l,1) = (hq_mod_cas(l)+vq_mod_cas(l))
782       d_q_adv(l,2) = 0.0
783       d_u_adv(l) = (hu_mod_cas(l)+vu_mod_cas(l))
784       d_u_adv(l) = (hv_mod_cas(l)+vv_mod_cas(l))
785      enddo     
786
787! In case fluxes are imposed
788       IF (ok_flux_surf) THEN
789       fsens=sens_prof_cas
790       flat=lat_prof_cas
791       ENDIF
792       IF (ok_prescr_ust) THEN
793       ust=ustar_prof_cas
794       print *,'ust=',ust
795       ENDIF
796
797      endif !forcing_case
798!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
Note: See TracBrowser for help on using the repository browser.