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

Last change on this file since 1907 was 1907, checked in by lguez, 10 years ago

Added a copyright property to every file of the distribution, except
for the fcm files (which have their own copyright). Use svn propget on
a file to see the copyright. For instance:

$ svn propget copyright libf/phylmd/physiq.F90
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

Also added the files defining the CeCILL version 2 license, in French
and English, at the top of the LMDZ tree.

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