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

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

Merged trunk changes r1997:2055 into testing branch

File size: 25.1 KB
Line 
1!----------------------------------------------------------------------
2! forcing_les = .T. : Impose a constant cooling
3! forcing_radconv = .T. : Pure radiative-convective equilibrium:
4!----------------------------------------------------------------------
5
6
7      nq1=0
8      nq2=0
9
10      if (forcing_les .or. forcing_radconv                                      &
11     &    .or. forcing_GCSSold .or. forcing_fire) then
12
13      if (forcing_fire) then
14!----------------------------------------------------------------------
15!read fire forcings from fire.nc
16!----------------------------------------------------------------------
17      fich_fire='fire.nc'
18      call read_fire(fich_fire,nlev_fire,nt_fire                                &
19     &     ,height,tttprof,qtprof,uprof,vprof,e12prof                           &
20     &     ,ugprof,vgprof,wfls,dqtdxls                                          &
21     &     ,dqtdyls,dqtdtls,thlpcar)
22      write(*,*) 'Forcing FIRE lu'
23      kmax=120            ! nombre de niveaux dans les profils et forcages
24      else 
25!----------------------------------------------------------------------
26! Read profiles from files: prof.inp.001 and lscale.inp.001
27! (repris de readlesfiles)
28!----------------------------------------------------------------------
29
30      call readprofiles(nlev_max,kmax,nqtot,height,                             &
31     &           tttprof,qtprof,uprof,vprof,                                    &
32     &           e12prof,ugprof,vgprof,                                         &
33     &           wfls,dqtdxls,dqtdyls,dqtdtls,                                  &
34     &           thlpcar,qprof,nq1,nq2)
35      endif
36
37! compute altitudes of play levels.
38      zlay(1) =zsurf +  rd*tsurf*(psurf-play(1))/(rg*psurf)
39      do l = 2,llm
40        zlay(l) = zlay(l-1)+rd*tsurf*(psurf-play(1))/(rg*psurf)
41      enddo
42
43!----------------------------------------------------------------------
44! Interpolation of the profiles given on the input file to
45! model levels
46!----------------------------------------------------------------------
47      zlay(1) = zsurf +  rd*tsurf*(psurf-play(1))/(rg*psurf)
48      do l=1,llm
49        ! Above the max altutide of the input file
50
51        if (zlay(l)<height(kmax)) mxcalc=l
52
53        frac = (height(kmax)-zlay(l))/(height (kmax)-height(kmax-1))
54        ttt =tttprof(kmax)-frac*(tttprof(kmax)-tttprof(kmax-1))
55       if ((forcing_GCSSold .AND. tp_ini_GCSSold) .OR. forcing_fire)then ! pot. temp. in initial profile
56          temp(l) = ttt*(play(l)/pzero)**rkappa
57          teta(l) = ttt
58       else
59          temp(l) = ttt
60          teta(l) = ttt*(pzero/play(l))**rkappa
61       endif
62          print *,' temp,teta ',l,temp(l),teta(l)
63        q(l,1)  = qtprof(kmax)-frac*( qtprof(kmax)- qtprof(kmax-1))
64        u(l)    =  uprof(kmax)-frac*(  uprof(kmax)-  uprof(kmax-1))
65        v(l)    =  vprof(kmax)-frac*(  vprof(kmax)-  vprof(kmax-1))
66        ug(l)   = ugprof(kmax)-frac*( ugprof(kmax)- ugprof(kmax-1))
67        vg(l)   = vgprof(kmax)-frac*( vgprof(kmax)- vgprof(kmax-1))
68        IF (nq2>0) q(l,nq1:nq2)=qprof(kmax,nq1:nq2)                         &
69     &               -frac*(qprof(kmax,nq1:nq2)-qprof(kmax-1,nq1:nq2))
70        omega(l)=   wfls(kmax)-frac*(   wfls(kmax)-   wfls(kmax-1))
71
72        dq_dyn(l,1) = dqtdtls(kmax)-frac*(dqtdtls(kmax)-dqtdtls(kmax-1))
73        dt_cooling(l)=thlpcar(kmax)-frac*(thlpcar(kmax)-thlpcar(kmax-1))
74        do k=2,kmax
75          frac = (height(k)-zlay(l))/(height(k)-height(k-1))
76          if(l==1) print*,'k, height, tttprof',k,height(k),tttprof(k)
77          if(zlay(l)>height(k-1).and.zlay(l)<height(k)) then
78            ttt =tttprof(k)-frac*(tttprof(k)-tttprof(k-1))
79       if ((forcing_GCSSold .AND. tp_ini_GCSSold) .OR. forcing_fire)then ! pot. temp. in initial profile
80          temp(l) = ttt*(play(l)/pzero)**rkappa
81          teta(l) = ttt
82       else
83          temp(l) = ttt
84          teta(l) = ttt*(pzero/play(l))**rkappa
85       endif
86          print *,' temp,teta ',l,temp(l),teta(l)
87            q(l,1)  = qtprof(k)-frac*( qtprof(k)- qtprof(k-1))
88            u(l)    =  uprof(k)-frac*(  uprof(k)-  uprof(k-1))
89            v(l)    =  vprof(k)-frac*(  vprof(k)-  vprof(k-1))
90            ug(l)   = ugprof(k)-frac*( ugprof(k)- ugprof(k-1))
91            vg(l)   = vgprof(k)-frac*( vgprof(k)- vgprof(k-1))
92            IF (nq2>0) q(l,nq1:nq2)=qprof(k,nq1:nq2)                        &
93     &                   -frac*(qprof(k,nq1:nq2)-qprof(k-1,nq1:nq2))
94            omega(l)=   wfls(k)-frac*(   wfls(k)-   wfls(k-1))
95            dq_dyn(l,1)=dqtdtls(k)-frac*(dqtdtls(k)-dqtdtls(k-1))
96            dt_cooling(l)=thlpcar(k)-frac*(thlpcar(k)-thlpcar(k-1))
97          elseif(zlay(l)<height(1)) then ! profils uniformes pour z<height(1)
98            ttt =tttprof(1)
99       if ((forcing_GCSSold .AND. tp_ini_GCSSold) .OR. forcing_fire)then ! pot. temp. in initial profile
100          temp(l) = ttt*(play(l)/pzero)**rkappa
101          teta(l) = ttt
102       else
103          temp(l) = ttt
104          teta(l) = ttt*(pzero/play(l))**rkappa
105       endif
106            q(l,1)  = qtprof(1)
107            u(l)    =  uprof(1)
108            v(l)    =  vprof(1)
109            ug(l)   = ugprof(1)
110            vg(l)   = vgprof(1)
111            omega(l)=   wfls(1)
112            IF (nq2>0) q(l,nq1:nq2)=qprof(1,nq1:nq2)
113            dq_dyn(l,1)  =dqtdtls(1)
114            dt_cooling(l)=thlpcar(1)
115          endif
116        enddo
117
118        temp(l)=max(min(temp(l),350.),150.)
119        rho(l)  = play(l)/(rd*temp(l)*(1.+(rv/rd-1.)*q(l,1)))
120        if (l .lt. llm) then
121          zlay(l+1) = zlay(l) + (play(l)-play(l+1))/(rg*rho(l))
122        endif
123        omega2(l)=-rho(l)*omega(l)
124        omega(l)= omega(l)*(-rg*rho(l)) !en Pa/s
125        if (l>1) then
126        if(zlay(l-1)>height(kmax)) then
127           omega(l)=0.0
128           omega2(l)=0.0
129        endif   
130        endif
131        if(q(l,1)<0.) q(l,1)=0.0
132        q(l,2)  = 0.0
133      enddo
134
135      endif ! forcing_les .or. forcing_GCSSold .or. forcing_fire
136!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
137!---------------------------------------------------------------------
138! Forcing for GCSSold:
139!---------------------------------------------------------------------
140      if (forcing_GCSSold) then
141       fich_gcssold_ctl = './forcing.ctl'
142       fich_gcssold_dat = './forcing8.dat'
143       call copie(llm,play,psurf,fich_gcssold_ctl)
144       call get_uvd2(it,timestep,fich_gcssold_ctl,fich_gcssold_dat,         &
145     &               ht_gcssold,hq_gcssold,hw_gcssold,                      &
146     &               hu_gcssold,hv_gcssold,                                 &
147     &               hthturb_gcssold,hqturb_gcssold,Ts_gcssold,             &
148     &               imp_fcg_gcssold,ts_fcg_gcssold,                        &
149     &               Tp_fcg_gcssold,Turb_fcg_gcssold)
150       print *,' get_uvd2 -> hqturb_gcssold ',hqturb_gcssold
151      endif ! forcing_GCSSold
152!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
153!---------------------------------------------------------------------
154! Forcing for RICO:
155!---------------------------------------------------------------------
156      if (forcing_rico) then
157
158!       call writefield_phy('omega', omega,llm+1)
159      fich_rico = 'rico.txt'
160       call read_rico(fich_rico,nlev_rico,ps_rico,play                      &
161     &             ,ts_rico,t_rico,q_rico,u_rico,v_rico,w_rico              &
162     &             ,dth_rico,dqh_rico)
163        print*, ' on a lu et prepare RICO'
164
165       mxcalc=llm
166       print *, airefi, ' airefi '
167       do l = 1, llm
168       rho(l)  = play(l)/(rd*t_rico(l)*(1.+(rv/rd-1.)*q_rico(l)))
169       temp(l) = t_rico(l)
170       q(l,1) = q_rico(l)
171       q(l,2) = 0.0
172       u(l) = u_rico(l)
173       v(l) = v_rico(l)
174       ug(l)=u_rico(l)
175       vg(l)=v_rico(l)
176       omega(l) = -w_rico(l)*rg
177       omega2(l) = omega(l)/rg*airefi
178       enddo
179      endif
180!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
181!---------------------------------------------------------------------
182! Forcing from TOGA-COARE experiment (Ciesielski et al. 2002) :
183!---------------------------------------------------------------------
184
185      if (forcing_toga) then
186
187! read TOGA-COARE forcing (native vertical grid, nt_toga timesteps):
188      fich_toga = './d_toga/ifa_toga_coare_v21_dime.txt'
189      CALL read_togacoare(fich_toga,nlev_toga,nt_toga                       &
190     &         ,ts_toga,plev_toga,t_toga,q_toga,u_toga,v_toga,w_toga        &
191     &         ,ht_toga,vt_toga,hq_toga,vq_toga)
192
193       write(*,*) 'Forcing TOGA lu'
194
195! time interpolation for initial conditions:
196      write(*,*) 'AVT 1ere INTERPOLATION: day,day1 = ',day,day1
197      CALL interp_toga_time(daytime,day1,annee_ref                          &
198     &             ,year_ini_toga,day_ju_ini_toga,nt_toga,dt_toga           &
199     &             ,nlev_toga,ts_toga,plev_toga,t_toga,q_toga,u_toga        &
200     &             ,v_toga,w_toga,ht_toga,vt_toga,hq_toga,vq_toga           &
201     &             ,ts_prof,plev_prof,t_prof,q_prof,u_prof,v_prof,w_prof    &
202     &             ,ht_prof,vt_prof,hq_prof,vq_prof)
203
204! vertical interpolation:
205      CALL interp_toga_vertical(play,nlev_toga,plev_prof                    &
206     &         ,t_prof,q_prof,u_prof,v_prof,w_prof                          &
207     &         ,ht_prof,vt_prof,hq_prof,vq_prof                             &
208     &         ,t_mod,q_mod,u_mod,v_mod,w_mod                               &
209     &         ,ht_mod,vt_mod,hq_mod,vq_mod,mxcalc)
210       write(*,*) 'Profil initial forcing TOGA interpole'
211
212! initial and boundary conditions :
213      tsurf = ts_prof
214      write(*,*) 'SST initiale: ',tsurf
215      do l = 1, llm
216       temp(l) = t_mod(l)
217       q(l,1) = q_mod(l)
218       q(l,2) = 0.0
219       u(l) = u_mod(l)
220       v(l) = v_mod(l)
221       omega(l) = w_mod(l)
222       omega2(l)=omega(l)/rg*airefi ! flxmass_w calcule comme ds physiq
223!?       rho(l)  = play(l)/(rd*temp(l)*(1.+(rv/rd-1.)*q(l,1)))
224!?       omega2(l)=-rho(l)*omega(l)
225       alpha = rd*temp(l)*(1.+(rv/rd-1.)*q(l,1))/play(l)
226       d_th_adv(l) = alpha*omega(l)/rcpd-(ht_mod(l)+vt_mod(l))
227       d_q_adv(l,1) = -(hq_mod(l)+vq_mod(l))
228       d_q_adv(l,2) = 0.0
229      enddo
230
231      endif ! forcing_toga
232!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
233!---------------------------------------------------------------------
234! Forcing from TWPICE experiment (Shaocheng et al. 2010) :
235!---------------------------------------------------------------------
236
237      if (forcing_twpice) then
238!read TWP-ICE forcings
239     fich_twpice='d_twpi/twp180iopsndgvarana_v2.1_C3.c1.20060117.000000.cdf'
240      call read_twpice(fich_twpice,nlev_twpi,nt_twpi                        &
241     &     ,ts_twpi,plev_twpi,t_twpi,q_twpi,u_twpi,v_twpi,w_twpi            &
242     &     ,ht_twpi,vt_twpi,hq_twpi,vq_twpi)
243
244      write(*,*) 'Forcing TWP-ICE lu'
245!Time interpolation for initial conditions using TOGA interpolation routine
246         write(*,*) 'AVT 1ere INTERPOLATION: day,day1 = ',daytime,day1   
247      CALL interp_toga_time(daytime,day1,annee_ref                          &
248     &          ,year_ini_twpi,day_ju_ini_twpi,nt_twpi,dt_twpi,nlev_twpi    &
249     &             ,ts_twpi,plev_twpi,t_twpi,q_twpi,u_twpi,v_twpi,w_twpi    &
250     &             ,ht_twpi,vt_twpi,hq_twpi,vq_twpi                         &
251     &             ,ts_proftwp,plev_proftwp,t_proftwp,q_proftwp             &
252     &             ,u_proftwp,v_proftwp,w_proftwp                           &
253     &             ,ht_proftwp,vt_proftwp,hq_proftwp,vq_proftwp)
254
255! vertical interpolation using TOGA interpolation routine:
256!      write(*,*)'avant interp vert', t_proftwp
257      CALL interp_toga_vertical(play,nlev_twpi,plev_proftwp                 &
258     &         ,t_proftwp,q_proftwp,u_proftwp,v_proftwp,w_proftwp           &
259     &         ,ht_proftwp,vt_proftwp,hq_proftwp,vq_proftwp                 &
260     &         ,t_mod,q_mod,u_mod,v_mod,w_mod                               &
261     &         ,ht_mod,vt_mod,hq_mod,vq_mod,mxcalc)
262!       write(*,*) 'Profil initial forcing TWP-ICE interpole',t_mod
263
264! initial and boundary conditions :
265!      tsurf = ts_proftwp
266      write(*,*) 'SST initiale: ',tsurf
267      do l = 1, llm
268       temp(l) = t_mod(l)
269       q(l,1) = q_mod(l)
270       q(l,2) = 0.0
271       u(l) = u_mod(l)
272       v(l) = v_mod(l)
273       omega(l) = w_mod(l)
274       omega2(l)=omega(l)/rg*airefi ! flxmass_w calcule comme ds physiq
275
276       alpha = rd*temp(l)*(1.+(rv/rd-1.)*q(l,1))/play(l)
277!on applique le forcage total au premier pas de temps
278!attention: signe different de toga
279       d_th_adv(l) = alpha*omega(l)/rcpd+(ht_mod(l)+vt_mod(l))
280       d_q_adv(l,1) = (hq_mod(l)+vq_mod(l))
281       d_q_adv(l,2) = 0.0
282      enddo     
283       
284      endif !forcing_twpice
285
286!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
287!---------------------------------------------------------------------
288! Forcing from AMMA experiment (Couvreux et al. 2010) :
289!---------------------------------------------------------------------
290
291      if (forcing_amma) then
292!read AMMA forcings
293      fich_amma='amma.nc'
294      call read_amma(fich_amma,nlev_amma,nt_amma                            &
295     &     ,z_amma,plev_amma,th_amma,q_amma,u_amma,v_amma,vitw_amma         &
296     &     ,ht_amma,hq_amma,sens_amma,lat_amma)
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 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     &            ,year_ini_armcu,day_ju_ini_armcu,nt_armcu,dt_armcu        &
406     &            ,nlev_armcu,sens_armcu,flat_armcu,adv_theta_armcu         &
407     &            ,rad_theta_armcu,adv_qt_armcu,sens_prof,flat_prof         &
408     &            ,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     &             ,year_ini_sandu,day_ju_ini_sandu,nt_sandu,dt_sandu       &
500     &             ,nlev_sandu                                              &
501     &             ,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     &             ,year_ini_astex,day_ju_ini_astex,nt_astex,dt_astex       &
575     &             ,nlev_astex,div_astex,ts_astex,ug_astex,vg_astex         &
576     &             ,ufa_astex,vfa_astex,div_prof,ts_prof,ug_prof,vg_prof    &
577     &             ,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.