source: LMDZ5/trunk/libf/phy1d/1D_read_forc_cases.h @ 1948

Last change on this file since 1948 was 1948, checked in by idelkadi, 11 years ago
  • Option pour tourner sans thermiques ni ajustement sec si ifalg_thermals<0 (phylmd/physiq.F90)
  • Modifications permettant d'imposer des profils initiaux de traceurs

lus dans un tracer.inp.001 (phylmd/1DUTILS.h, 1D_read_forc_cases.h et lmdz1d.F)

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
File size: 23.6 KB
Line 
1!----------------------------------------------------------------------
2! forcing_les = .T. : Impose a constant cooling
3! forcing_radconv = .T. : Pure radiative-convective equilibrium:
4!----------------------------------------------------------------------
5
6      if (forcing_les .or. forcing_radconv
7     :    .or. forcing_GCSSold .or. forcing_fire) then
8
9      if (forcing_fire) then
10!----------------------------------------------------------------------
11!read fire forcings from fire.nc
12!----------------------------------------------------------------------
13      fich_fire='fire.nc'
14      call read_fire(fich_fire,nlev_fire,nt_fire
15     :     ,height,tttprof,qtprof,uprof,vprof,e12prof
16     :     ,ugprof,vgprof,wfls,dqtdxls
17     :     ,dqtdyls,dqtdtls,thlpcar)
18      write(*,*) 'Forcing FIRE lu'
19      kmax=120            ! nombre de niveaux dans les profils et forcages
20      else 
21!----------------------------------------------------------------------
22! Read profiles from files: prof.inp.001 and lscale.inp.001
23! (repris de readlesfiles)
24!----------------------------------------------------------------------
25
26      call readprofiles(nlev_max,kmax,nqtot,height,
27     .           tttprof,qtprof,uprof,vprof,
28     .           e12prof,ugprof,vgprof,
29     .           wfls,dqtdxls,dqtdyls,dqtdtls,
30     .           thlpcar,qprof,nq1,nq2)
31      endif
32
33! compute altitudes of play levels.
34      zlay(1) =zsurf +  rd*tsurf*(psurf-play(1))/(rg*psurf)
35      do l = 2,llm
36        zlay(l) = zlay(l-1)+rd*tsurf*(psurf-play(1))/(rg*psurf)
37      enddo
38
39!----------------------------------------------------------------------
40! Interpolation of the profiles given on the input file to
41! model levels
42!----------------------------------------------------------------------
43      zlay(1) = zsurf +  rd*tsurf*(psurf-play(1))/(rg*psurf)
44      do l=1,llm
45        ! Above the max altutide of the input file
46
47        if (zlay(l)<height(kmax)) mxcalc=l
48
49        frac = (height(kmax)-zlay(l))/(height (kmax)-height(kmax-1))
50        ttt =tttprof(kmax)-frac*(tttprof(kmax)-tttprof(kmax-1))
51       if ((forcing_GCSSold .AND. tp_ini_GCSSold) .OR. forcing_fire)then ! pot. temp. in initial profile
52          temp(l) = ttt*(play(l)/pzero)**rkappa
53          teta(l) = ttt
54       else
55          temp(l) = ttt
56          teta(l) = ttt*(pzero/play(l))**rkappa
57       endif
58          print *,' temp,teta ',l,temp(l),teta(l)
59        q(l,1)  = qtprof(kmax)-frac*( qtprof(kmax)- qtprof(kmax-1))
60        u(l)    =  uprof(kmax)-frac*(  uprof(kmax)-  uprof(kmax-1))
61        v(l)    =  vprof(kmax)-frac*(  vprof(kmax)-  vprof(kmax-1))
62        ug(l)   = ugprof(kmax)-frac*( ugprof(kmax)- ugprof(kmax-1))
63        vg(l)   = vgprof(kmax)-frac*( vgprof(kmax)- vgprof(kmax-1))
64        q(l,nq1:nq2)=qprof(kmax,nq1:nq2)
65     s               -frac*(qprof(kmax,nq1:nq2)-qprof(kmax-1,nq1:nq2))
66        omega(l)=   wfls(kmax)-frac*(   wfls(kmax)-   wfls(kmax-1))
67
68        dq_dyn(l,1) = dqtdtls(kmax)-frac*(dqtdtls(kmax)-dqtdtls(kmax-1))
69        dt_cooling(l)
70     .          =thlpcar(kmax)-frac*(thlpcar(kmax)-thlpcar(kmax-1))
71        do k=2,kmax
72          frac = (height(k)-zlay(l))/(height(k)-height(k-1))
73          if(l==1) print*,'k, height, tttprof',k,height(k),tttprof(k)
74          if(zlay(l)>height(k-1).and.zlay(l)<height(k)) then
75            ttt =tttprof(k)-frac*(tttprof(k)-tttprof(k-1))
76       if ((forcing_GCSSold .AND. tp_ini_GCSSold) .OR. forcing_fire)then ! pot. temp. in initial profile
77          temp(l) = ttt*(play(l)/pzero)**rkappa
78          teta(l) = ttt
79       else
80          temp(l) = ttt
81          teta(l) = ttt*(pzero/play(l))**rkappa
82       endif
83          print *,' temp,teta ',l,temp(l),teta(l)
84            q(l,1)  = qtprof(k)-frac*( qtprof(k)- qtprof(k-1))
85            u(l)    =  uprof(k)-frac*(  uprof(k)-  uprof(k-1))
86            v(l)    =  vprof(k)-frac*(  vprof(k)-  vprof(k-1))
87            ug(l)   = ugprof(k)-frac*( ugprof(k)- ugprof(k-1))
88            vg(l)   = vgprof(k)-frac*( vgprof(k)- vgprof(k-1))
89            q(l,nq1:nq2)=qprof(k,nq1:nq2)
90     s                   -frac*(qprof(k,nq1:nq2)-qprof(k-1,nq1:nq2))
91            omega(l)=   wfls(k)-frac*(   wfls(k)-   wfls(k-1))
92            dq_dyn(l,1)=dqtdtls(k)-frac*(dqtdtls(k)-dqtdtls(k-1))
93            dt_cooling(l)
94     .              =thlpcar(k)-frac*(thlpcar(k)-thlpcar(k-1))
95          elseif(zlay(l)<height(1)) then ! profils uniformes pour z<height(1)
96            ttt =tttprof(1)
97       if ((forcing_GCSSold .AND. tp_ini_GCSSold) .OR. forcing_fire)then ! pot. temp. in initial profile
98          temp(l) = ttt*(play(l)/pzero)**rkappa
99          teta(l) = ttt
100       else
101          temp(l) = ttt
102          teta(l) = ttt*(pzero/play(l))**rkappa
103       endif
104            q(l,1)  = qtprof(1)
105            u(l)    =  uprof(1)
106            v(l)    =  vprof(1)
107            ug(l)   = ugprof(1)
108            vg(l)   = vgprof(1)
109            omega(l)=   wfls(1)
110            q(l,nq1:nq2)=qprof(1,nq1:nq2)
111            dq_dyn(l,1)  =dqtdtls(1)
112            dt_cooling(l)=thlpcar(1)
113          endif
114        enddo
115
116        temp(l)=max(min(temp(l),350.),150.)
117        rho(l)  = play(l)/(rd*temp(l)*(1.+(rv/rd-1.)*q(l,1)))
118        if (l .lt. llm) then
119          zlay(l+1) = zlay(l) + (play(l)-play(l+1))/(rg*rho(l))
120        endif
121        omega2(l)=-rho(l)*omega(l)
122        omega(l)= omega(l)*(-rg*rho(l)) !en Pa/s
123        if (l>1) then
124        if(zlay(l-1)>height(kmax)) then
125           omega(l)=0.0
126           omega2(l)=0.0
127        endif   
128        endif
129        if(q(l,1)<0.) q(l,1)=0.0
130        q(l,2)  = 0.0
131      enddo
132
133      endif ! forcing_les .or. forcing_GCSSold .or. forcing_fire
134!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
135!---------------------------------------------------------------------
136! Forcing for GCSSold:
137!---------------------------------------------------------------------
138      if (forcing_GCSSold) then
139       fich_gcssold_ctl = './forcing.ctl'
140       fich_gcssold_dat = './forcing8.dat'
141       call copie(llm,play,psurf,fich_gcssold_ctl)
142       call get_uvd2(it,timestep,fich_gcssold_ctl,fich_gcssold_dat,
143     :               ht_gcssold,hq_gcssold,hw_gcssold,
144     :               hu_gcssold,hv_gcssold,
145     :               hthturb_gcssold,hqturb_gcssold,Ts_gcssold,
146     :               imp_fcg_gcssold,ts_fcg_gcssold,
147     :               Tp_fcg_gcssold,Turb_fcg_gcssold)
148       print *,' get_uvd2 -> hqturb_gcssold ',hqturb_gcssold
149      endif ! forcing_GCSSold
150!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
151!---------------------------------------------------------------------
152! Forcing for RICO:
153!---------------------------------------------------------------------
154      if (forcing_rico) then
155
156!       call writefield_phy('omega', omega,llm+1)
157      fich_rico = 'rico.txt'
158       call read_rico(fich_rico,nlev_rico,ps_rico,play
159     :             ,ts_rico,t_rico,q_rico,u_rico,v_rico,w_rico
160     :             ,dth_rico,dqh_rico)
161        print*, ' on a lu et prepare RICO'
162
163       mxcalc=llm
164       print *, airefi, ' airefi '
165       do l = 1, llm
166       rho(l)  = play(l)/(rd*t_rico(l)*(1.+(rv/rd-1.)*q_rico(l)))
167       temp(l) = t_rico(l)
168       q(l,1) = q_rico(l)
169       q(l,2) = 0.0
170       u(l) = u_rico(l)
171       v(l) = v_rico(l)
172       ug(l)=u_rico(l)
173       vg(l)=v_rico(l)
174       omega(l) = -w_rico(l)*rg
175       omega2(l) = omega(l)/rg*airefi
176       enddo
177      endif
178!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
179!---------------------------------------------------------------------
180! Forcing from TOGA-COARE experiment (Ciesielski et al. 2002) :
181!---------------------------------------------------------------------
182
183      if (forcing_toga) then
184
185! read TOGA-COARE forcing (native vertical grid, nt_toga timesteps):
186      fich_toga = './d_toga/ifa_toga_coare_v21_dime.txt'
187      CALL read_togacoare(fich_toga,nlev_toga,nt_toga
188     :         ,ts_toga,plev_toga,t_toga,q_toga,u_toga,v_toga,w_toga
189     :         ,ht_toga,vt_toga,hq_toga,vq_toga)
190
191       write(*,*) 'Forcing TOGA lu'
192
193! time interpolation for initial conditions:
194      write(*,*) 'AVT 1ere INTERPOLATION: day,day1 = ',day,day1
195      CALL interp_toga_time(daytime,day1,annee_ref
196     i             ,year_ini_toga,day_ju_ini_toga,nt_toga,dt_toga
197     i             ,nlev_toga,ts_toga,plev_toga,t_toga,q_toga,u_toga
198     i             ,v_toga,w_toga,ht_toga,vt_toga,hq_toga,vq_toga
199     o             ,ts_prof,plev_prof,t_prof,q_prof,u_prof,v_prof,w_prof
200     o             ,ht_prof,vt_prof,hq_prof,vq_prof)
201
202! vertical interpolation:
203      CALL interp_toga_vertical(play,nlev_toga,plev_prof
204     :         ,t_prof,q_prof,u_prof,v_prof,w_prof
205     :         ,ht_prof,vt_prof,hq_prof,vq_prof
206     :         ,t_mod,q_mod,u_mod,v_mod,w_mod
207     :         ,ht_mod,vt_mod,hq_mod,vq_mod,mxcalc)
208       write(*,*) 'Profil initial forcing TOGA interpole'
209
210! initial and boundary conditions :
211      tsurf = ts_prof
212      write(*,*) 'SST initiale: ',tsurf
213      do l = 1, llm
214       temp(l) = t_mod(l)
215       q(l,1) = q_mod(l)
216       q(l,2) = 0.0
217       u(l) = u_mod(l)
218       v(l) = v_mod(l)
219       omega(l) = w_mod(l)
220       omega2(l)=omega(l)/rg*airefi ! flxmass_w calcule comme ds physiq
221!?       rho(l)  = play(l)/(rd*temp(l)*(1.+(rv/rd-1.)*q(l,1)))
222!?       omega2(l)=-rho(l)*omega(l)
223       alpha = rd*temp(l)*(1.+(rv/rd-1.)*q(l,1))/play(l)
224       d_th_adv(l) = alpha*omega(l)/rcpd-(ht_mod(l)+vt_mod(l))
225       d_q_adv(l,1) = -(hq_mod(l)+vq_mod(l))
226       d_q_adv(l,2) = 0.0
227      enddo
228
229      endif ! forcing_toga
230!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
231!---------------------------------------------------------------------
232! Forcing from TWPICE experiment (Shaocheng et al. 2010) :
233!---------------------------------------------------------------------
234
235      if (forcing_twpice) then
236!read TWP-ICE forcings
237      fich_twpice=
238     : 'd_twpi/twp180iopsndgvarana_v2.1_C3.c1.20060117.000000.cdf'
239      call read_twpice(fich_twpice,nlev_twpi,nt_twpi
240     :     ,ts_twpi,plev_twpi,t_twpi,q_twpi,u_twpi,v_twpi,w_twpi
241     :     ,ht_twpi,vt_twpi,hq_twpi,vq_twpi)
242
243      write(*,*) 'Forcing TWP-ICE lu'
244!Time interpolation for initial conditions using TOGA interpolation routine
245         write(*,*) 'AVT 1ere INTERPOLATION: day,day1 = ',daytime,day1   
246      CALL interp_toga_time(daytime,day1,annee_ref
247     i          ,year_ini_twpi,day_ju_ini_twpi,nt_twpi,dt_twpi,nlev_twpi
248     i             ,ts_twpi,plev_twpi,t_twpi,q_twpi,u_twpi,v_twpi,w_twpi
249     i             ,ht_twpi,vt_twpi,hq_twpi,vq_twpi
250     o             ,ts_proftwp,plev_proftwp,t_proftwp,q_proftwp
251     o             ,u_proftwp,v_proftwp,w_proftwp
252     o             ,ht_proftwp,vt_proftwp,hq_proftwp,vq_proftwp)
253
254! vertical interpolation using TOGA interpolation routine:
255!      write(*,*)'avant interp vert', t_proftwp
256      CALL interp_toga_vertical(play,nlev_twpi,plev_proftwp
257     :         ,t_proftwp,q_proftwp,u_proftwp,v_proftwp,w_proftwp
258     :         ,ht_proftwp,vt_proftwp,hq_proftwp,vq_proftwp
259     :         ,t_mod,q_mod,u_mod,v_mod,w_mod
260     :         ,ht_mod,vt_mod,hq_mod,vq_mod,mxcalc)
261!       write(*,*) 'Profil initial forcing TWP-ICE interpole',t_mod
262
263! initial and boundary conditions :
264!      tsurf = ts_proftwp
265      write(*,*) 'SST initiale: ',tsurf
266      do l = 1, llm
267       temp(l) = t_mod(l)
268       q(l,1) = q_mod(l)
269       q(l,2) = 0.0
270       u(l) = u_mod(l)
271       v(l) = v_mod(l)
272       omega(l) = w_mod(l)
273       omega2(l)=omega(l)/rg*airefi ! flxmass_w calcule comme ds physiq
274
275       alpha = rd*temp(l)*(1.+(rv/rd-1.)*q(l,1))/play(l)
276!on applique le forcage total au premier pas de temps
277!attention: signe different de toga
278       d_th_adv(l) = alpha*omega(l)/rcpd+(ht_mod(l)+vt_mod(l))
279       d_q_adv(l,1) = (hq_mod(l)+vq_mod(l))
280       d_q_adv(l,2) = 0.0
281      enddo     
282       
283      endif !forcing_twpice
284
285!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
286!---------------------------------------------------------------------
287! Forcing from AMMA experiment (Couvreux et al. 2010) :
288!---------------------------------------------------------------------
289
290      if (forcing_amma) then
291!read AMMA forcings
292      fich_amma='amma.nc'
293      call read_amma(fich_amma,nlev_amma,nt_amma
294     :     ,z_amma,plev_amma,th_amma,q_amma,u_amma,v_amma,vitw_amma
295     :     ,ht_amma,hq_amma,sens_amma,lat_amma)
296
297      write(*,*) 'Forcing AMMA lu'
298
299!champs initiaux:
300      do k=1,nlev_amma
301         th_ammai(k)=th_amma(k)
302         q_ammai(k)=q_amma(k)
303         u_ammai(k)=u_amma(k)
304         v_ammai(k)=v_amma(k)
305         vitw_ammai(k)=vitw_amma(k,12)
306         ht_ammai(k)=ht_amma(k,12)
307         hq_ammai(k)=hq_amma(k,12)
308         vt_ammai(k)=0.
309         vq_ammai(k)=0.
310      enddo   
311      omega(:)=0.     
312      omega2(:)=0.
313      rho(:)=0.
314! vertical interpolation using TOGA interpolation routine:
315!      write(*,*)'avant interp vert', t_proftwp
316      CALL interp_toga_vertical(play,nlev_amma,plev_amma
317     :         ,th_ammai,q_ammai,u_ammai,v_ammai,vitw_ammai
318     :         ,ht_ammai,vt_ammai,hq_ammai,vq_ammai
319     :         ,t_mod,q_mod,u_mod,v_mod,w_mod
320     :         ,ht_mod,vt_mod,hq_mod,vq_mod,mxcalc)
321!       write(*,*) 'Profil initial forcing TWP-ICE interpole',t_mod
322
323! initial and boundary conditions :
324!      tsurf = ts_proftwp
325      write(*,*) 'SST initiale mxcalc: ',tsurf,mxcalc
326      do l = 1, llm
327! Ligne du dessous à decommenter si on lit theta au lieu de temp
328!      temp(l) = t_mod(l)*(play(l)/pzero)**rkappa
329       temp(l) = t_mod(l) 
330       q(l,1) = q_mod(l)
331       q(l,2) = 0.0
332!      print *,'read_forc: l,temp,q=',l,temp(l),q(l,1)
333       u(l) = u_mod(l)
334       v(l) = v_mod(l)
335       rho(l)  = play(l)/(rd*temp(l)*(1.+(rv/rd-1.)*q(l,1)))
336       omega(l) = w_mod(l)*(-rg*rho(l))
337       omega2(l)=omega(l)/rg*airefi ! flxmass_w calcule comme ds physiq
338
339       alpha = rd*temp(l)*(1.+(rv/rd-1.)*q(l,1))/play(l)
340!on applique le forcage total au premier pas de temps
341!attention: signe different de toga
342       d_th_adv(l) = alpha*omega(l)/rcpd+ht_mod(l)
343!forcage en th
344!       d_th_adv(l) = ht_mod(l)
345       d_q_adv(l,1) = hq_mod(l)
346       d_q_adv(l,2) = 0.0
347       dt_cooling(l)=0.
348      enddo     
349       write(*,*) 'Profil initial forcing AMMA interpole temp39',
350     &           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 Arm_Cu case                   
363! For this case, ifa_armcu.txt contains sensible, latent heat fluxes
364! large scale advective forcing,radiative forcing
365! and advective tendency of theta and qt to be applied
366!---------------------------------------------------------------------
367
368      if (forcing_armcu) then
369! read armcu forcing :
370       write(*,*) 'Avant lecture Forcing Arm_Cu'
371      fich_armcu = './ifa_armcu.txt'
372      CALL read_armcu(fich_armcu,nlev_armcu,nt_armcu,
373     : sens_armcu,flat_armcu,adv_theta_armcu,
374     : rad_theta_armcu,adv_qt_armcu)
375       write(*,*) 'Forcing Arm_Cu lu'
376
377!----------------------------------------------------------------------
378! Read profiles from file: prof.inp.19 or prof.inp.40 
379! For this case, profiles are given for two vertical resolution
380! 19 or 40 levels
381!
382! Comment from: http://www.knmi.nl/samenw/eurocs/ARM/profiles.html
383! Note that the initial profiles contain no liquid water! 
384! (so potential temperature can be interpreted as liquid water
385! potential temperature and water vapor as total water)
386! profiles are given at full levels
387!----------------------------------------------------------------------
388
389      call readprofile_armcu(nlev_max,kmax,height,play_mod,u_mod,
390     .           v_mod,theta_mod,t_mod,qv_mod,rv_mod,ap,bp)
391
392! time interpolation for initial conditions:
393      write(*,*) 'AVT 1ere INTERPOLATION: day,day1 = ',day,day1
394
395      print *,'Avant interp_armcu_time'
396      print *,'daytime=',daytime
397      print *,'day1=',day1
398      print *,'annee_ref=',annee_ref
399      print *,'year_ini_armcu=',year_ini_armcu
400      print *,'day_ju_ini_armcu=',day_ju_ini_armcu
401      print *,'nt_armcu=',nt_armcu
402      print *,'dt_armcu=',dt_armcu
403      print *,'nlev_armcu=',nlev_armcu
404      CALL interp_armcu_time(daytime,day1,annee_ref
405     i            ,year_ini_armcu,day_ju_ini_armcu,nt_armcu,dt_armcu
406     i            ,nlev_armcu,sens_armcu,flat_armcu,adv_theta_armcu
407     i            ,rad_theta_armcu,adv_qt_armcu,sens_prof,flat_prof
408     i            ,adv_theta_prof,rad_theta_prof,adv_qt_prof)
409       write(*,*) 'Forcages interpoles dans temps'
410
411! No vertical interpolation if nlev imposed to 19 or 40
412! The vertical grid stops at 4000m # 600hPa
413      mxcalc=llm
414
415! initial and boundary conditions :
416!     tsurf = ts_prof
417! tsurf read in lmdz1d.def
418      write(*,*) 'Tsurf initiale: ',tsurf
419      do l = 1, llm
420       play(l)=play_mod(l)*100.
421       presnivs(l)=play(l)
422       zlay(l)=height(l)
423       temp(l) = t_mod(l)
424       teta(l)=theta_mod(l)
425       q(l,1) = qv_mod(l)/1000.
426! No liquid water in the initial profil
427       q(l,2) = 0.
428       u(l) = u_mod(l)
429       ug(l)= u_mod(l)
430       v(l) = v_mod(l)
431       vg(l)= v_mod(l)
432! Advective forcings are given in K or g/kg ... per HOUR
433!      IF(height(l).LT.1000) THEN
434!        d_th_adv(l) = (adv_theta_prof + rad_theta_prof)/3600.
435!        d_q_adv(l,1) = adv_qt_prof/1000./3600.
436!        d_q_adv(l,2) = 0.0
437!      ELSEIF (height(l).GE.1000.AND.height(l).LT.3000) THEN
438!        d_th_adv(l) = (adv_theta_prof + rad_theta_prof)*
439!    :               (1-(height(l)-1000.)/2000.)
440!        d_th_adv(l) = d_th_adv(l)/3600.
441!        d_q_adv(l,1) = adv_qt_prof*(1-(height(l)-1000.)/2000.)
442!        d_q_adv(l,1) = d_q_adv(l,1)/1000./3600.
443!        d_q_adv(l,2) = 0.0
444!      ELSE
445!        d_th_adv(l) = 0.0
446!        d_q_adv(l,1) = 0.0
447!        d_q_adv(l,2) = 0.0
448!      ENDIF
449      enddo
450! plev at half levels is given in proh.inp.19 or proh.inp.40 files
451      plev(1)= ap(llm+1)+bp(llm+1)*psurf
452      do l = 1, llm
453      plev(l+1) = ap(llm-l+1)+bp(llm-l+1)*psurf
454      print *,'Read_forc: l height play plev zlay temp',
455     :   l,height(l),play(l),plev(l),zlay(l),temp(l)
456      enddo
457! For this case, fluxes are imposed
458       fsens=-1*sens_prof
459       flat=-1*flat_prof
460
461      endif ! forcing_armcu
462!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
463!---------------------------------------------------------------------
464! Forcing from transition case of Irina Sandu                 
465!---------------------------------------------------------------------
466
467      if (forcing_sandu) then
468       write(*,*) 'Avant lecture Forcing SANDU'
469
470! read sanduref forcing :
471      fich_sandu = './ifa_sanduref.txt'
472      CALL read_sandu(fich_sandu,nlev_sandu,nt_sandu,ts_sandu)
473
474       write(*,*) 'Forcing SANDU lu'
475
476!----------------------------------------------------------------------
477! Read profiles from file: prof.inp.001 
478!----------------------------------------------------------------------
479
480      call readprofile_sandu(nlev_max,kmax,height,plev_profs,t_profs,
481     .           thl_profs,q_profs,u_profs,v_profs,
482     .           w_profs,omega_profs,o3mmr_profs)
483
484! time interpolation for initial conditions:
485      write(*,*) 'AVT 1ere INTERPOLATION: day,day1 = ',day,day1
486! ATTENTION, cet appel ne convient pas pour le cas SANDU !!
487! revoir 1DUTILS.h et les arguments
488
489      print *,'Avant interp_sandu_time'
490      print *,'daytime=',daytime
491      print *,'day1=',day1
492      print *,'annee_ref=',annee_ref
493      print *,'year_ini_sandu=',year_ini_sandu
494      print *,'day_ju_ini_sandu=',day_ju_ini_sandu
495      print *,'nt_sandu=',nt_sandu
496      print *,'dt_sandu=',dt_sandu
497      print *,'nlev_sandu=',nlev_sandu
498      CALL interp_sandu_time(daytime,day1,annee_ref
499     i             ,year_ini_sandu,day_ju_ini_sandu,nt_sandu,dt_sandu
500     i             ,nlev_sandu
501     i             ,ts_sandu,ts_prof)
502
503! vertical interpolation:
504      print *,'Avant interp_vertical: nlev_sandu=',nlev_sandu
505      CALL interp_sandu_vertical(play,nlev_sandu,plev_profs
506     :         ,t_profs,thl_profs,q_profs,u_profs,v_profs,w_profs
507     :         ,omega_profs,o3mmr_profs
508     :         ,t_mod,thl_mod,q_mod,u_mod,v_mod,w_mod
509     :         ,omega_mod,o3mmr_mod,mxcalc)
510       write(*,*) 'Profil initial forcing SANDU interpole'
511
512! initial and boundary conditions :
513      tsurf = ts_prof
514      write(*,*) 'SST initiale: ',tsurf
515      do l = 1, llm
516       temp(l) = t_mod(l)
517       tetal(l)=thl_mod(l)
518       q(l,1) = q_mod(l)
519       q(l,2) = 0.0
520       u(l) = u_mod(l)
521       v(l) = v_mod(l)
522       w(l) = w_mod(l)
523       omega(l) = omega_mod(l)
524       omega2(l)=omega(l)/rg*airefi ! flxmass_w calcule comme ds physiq
525!?       rho(l)  = play(l)/(rd*temp(l)*(1.+(rv/rd-1.)*q(l,1)))
526!?       omega2(l)=-rho(l)*omega(l)
527       alpha = rd*temp(l)*(1.+(rv/rd-1.)*q(l,1))/play(l)
528!      d_th_adv(l) = alpha*omega(l)/rcpd+vt_mod(l)
529!      d_q_adv(l,1) = vq_mod(l)
530       d_th_adv(l) = alpha*omega(l)/rcpd
531       d_q_adv(l,1) = 0.0
532       d_q_adv(l,2) = 0.0
533      enddo
534
535      endif ! forcing_sandu
536!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
537!---------------------------------------------------------------------
538! Forcing from Astex case
539!---------------------------------------------------------------------
540
541      if (forcing_astex) then
542       write(*,*) 'Avant lecture Forcing Astex'
543
544! read astex forcing :
545      fich_astex = './ifa_astex.txt'
546      CALL read_astex(fich_astex,nlev_astex,nt_astex,div_astex,ts_astex,
547     :  ug_astex,vg_astex,ufa_astex,vfa_astex)
548
549       write(*,*) 'Forcing Astex lu'
550
551!----------------------------------------------------------------------
552! Read profiles from file: prof.inp.001
553!----------------------------------------------------------------------
554
555      call readprofile_astex(nlev_max,kmax,height,plev_profa,t_profa,
556     .           thl_profa,qv_profa,ql_profa,qt_profa,u_profa,v_profa,
557     .           w_profa,tke_profa,o3mmr_profa)
558
559! time interpolation for initial conditions:
560      write(*,*) 'AVT 1ere INTERPOLATION: day,day1 = ',day,day1
561! ATTENTION, cet appel ne convient pas pour le cas SANDU !!
562! revoir 1DUTILS.h et les arguments
563
564      print *,'Avant interp_astex_time'
565      print *,'daytime=',daytime
566      print *,'day1=',day1
567      print *,'annee_ref=',annee_ref
568      print *,'year_ini_astex=',year_ini_astex
569      print *,'day_ju_ini_astex=',day_ju_ini_astex
570      print *,'nt_astex=',nt_astex
571      print *,'dt_astex=',dt_astex
572      print *,'nlev_astex=',nlev_astex
573      CALL interp_astex_time(daytime,day1,annee_ref
574     i             ,year_ini_astex,day_ju_ini_astex,nt_astex,dt_astex
575     i             ,nlev_astex,div_astex,ts_astex,ug_astex,vg_astex
576     i             ,ufa_astex,vfa_astex,div_prof,ts_prof,ug_prof,vg_prof
577     i             ,ufa_prof,vfa_prof)
578
579! vertical interpolation:
580      print *,'Avant interp_vertical: nlev_astex=',nlev_astex
581      CALL interp_astex_vertical(play,nlev_astex,plev_profa
582     :         ,t_profa,thl_profa,qv_profa,ql_profa,qt_profa
583     :         ,u_profa,v_profa,w_profa,tke_profa,o3mmr_profa
584     :         ,t_mod,thl_mod,qv_mod,ql_mod,qt_mod,u_mod,v_mod,w_mod
585     :         ,tke_mod,o3mmr_mod,mxcalc)
586       write(*,*) 'Profil initial forcing Astex interpole'
587
588! initial and boundary conditions :
589      tsurf = ts_prof
590      write(*,*) 'SST initiale: ',tsurf
591      do l = 1, llm
592       temp(l) = t_mod(l)
593       tetal(l)=thl_mod(l)
594       q(l,1) = qv_mod(l)
595       q(l,2) = ql_mod(l)
596       u(l) = u_mod(l)
597       v(l) = v_mod(l)
598       w(l) = w_mod(l)
599       omega(l) = w_mod(l)
600!      omega2(l)=omega(l)/rg*airefi ! flxmass_w calcule comme ds physiq
601!      rho(l)  = play(l)/(rd*temp(l)*(1.+(rv/rd-1.)*q(l,1)))
602!      omega2(l)=-rho(l)*omega(l)
603       alpha = rd*temp(l)*(1.+(rv/rd-1.)*q(l,1))/play(l)
604!      d_th_adv(l) = alpha*omega(l)/rcpd+vt_mod(l)
605!      d_q_adv(l,1) = vq_mod(l)
606       d_th_adv(l) = alpha*omega(l)/rcpd
607       d_q_adv(l,1) = 0.0
608       d_q_adv(l,2) = 0.0
609      enddo
610
611      endif ! forcing_astex
612
Note: See TracBrowser for help on using the repository browser.