source: LMDZ6/branches/Ocean_skin/libf/phylmd/dyn1d/mod_1D_cases_read_std.F90 @ 3605

Last change on this file since 3605 was 3605, checked in by lguez, 4 years ago

Merge revisions 3427:3600 of trunk into branch Ocean_skin

File size: 50.6 KB
Line 
1!
2! $Id: mod_1D_cases_read.F90 2373 2015-10-13 17:28:01Z jyg $
3!
4MODULE mod_1D_cases_read_std
5
6!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
7!Declarations specifiques au cas standard
8        character*80 :: fich_cas
9! Discr?tisation
10        integer nlev_cas, nt_cas
11
12
13!profils environnementaux
14        real, allocatable::  plev_cas(:,:),plevh_cas(:)
15        real, allocatable::  ap_cas(:),bp_cas(:)
16
17        real, allocatable::  z_cas(:,:),zh_cas(:)
18        real, allocatable::  t_cas(:,:),q_cas(:,:),qv_cas(:,:),ql_cas(:,:),qi_cas(:,:),rh_cas(:,:)
19        real, allocatable::  th_cas(:,:),thv_cas(:,:),thl_cas(:,:),rv_cas(:,:)
20        real, allocatable::  u_cas(:,:),v_cas(:,:),vitw_cas(:,:),omega_cas(:,:)
21
22!forcing
23        real, allocatable::  ht_cas(:,:),vt_cas(:,:),dt_cas(:,:),dtrad_cas(:,:)
24        real, allocatable::  hth_cas(:,:),vth_cas(:,:),dth_cas(:,:)
25        real, allocatable::  hq_cas(:,:),vq_cas(:,:),dq_cas(:,:)
26        real, allocatable::  hr_cas(:,:),vr_cas(:,:),dr_cas(:,:)
27        real, allocatable::  hu_cas(:,:),vu_cas(:,:),du_cas(:,:)
28        real, allocatable::  hv_cas(:,:),vv_cas(:,:),dv_cas(:,:)
29        real, allocatable::  ug_cas(:,:),vg_cas(:,:)
30        real, allocatable::  temp_nudg_cas(:,:),qv_nudg_cas(:,:),u_nudg_cas(:,:),v_nudg_cas(:,:)
31        real, allocatable::  lat_cas(:),sens_cas(:),ts_cas(:),ps_cas(:),ustar_cas(:)
32        real, allocatable::  uw_cas(:,:),vw_cas(:,:),q1_cas(:,:),q2_cas(:,:),tke_cas(:)
33
34!champs interpoles
35        real, allocatable::  plev_prof_cas(:)
36        real, allocatable::  t_prof_cas(:)
37        real, allocatable::  theta_prof_cas(:)
38        real, allocatable::  thl_prof_cas(:)
39        real, allocatable::  thv_prof_cas(:)
40        real, allocatable::  q_prof_cas(:)
41        real, allocatable::  qv_prof_cas(:)
42        real, allocatable::  ql_prof_cas(:)
43        real, allocatable::  qi_prof_cas(:)
44        real, allocatable::  rh_prof_cas(:)
45        real, allocatable::  rv_prof_cas(:)
46        real, allocatable::  u_prof_cas(:)
47        real, allocatable::  v_prof_cas(:)       
48        real, allocatable::  vitw_prof_cas(:)
49        real, allocatable::  omega_prof_cas(:)
50        real, allocatable::  ug_prof_cas(:)
51        real, allocatable::  vg_prof_cas(:)
52        real, allocatable::  temp_nudg_prof_cas(:),qv_nudg_prof_cas(:),u_nudg_prof_cas(:),v_nudg_prof_cas(:)
53        real, allocatable::  ht_prof_cas(:)
54        real, allocatable::  hth_prof_cas(:)
55        real, allocatable::  hq_prof_cas(:)
56        real, allocatable::  vt_prof_cas(:)
57        real, allocatable::  vth_prof_cas(:)
58        real, allocatable::  vq_prof_cas(:)
59        real, allocatable::  dt_prof_cas(:)
60        real, allocatable::  dth_prof_cas(:)
61        real, allocatable::  dtrad_prof_cas(:)
62        real, allocatable::  dq_prof_cas(:)
63        real, allocatable::  hu_prof_cas(:)
64        real, allocatable::  hv_prof_cas(:)
65        real, allocatable::  vu_prof_cas(:)
66        real, allocatable::  vv_prof_cas(:)
67        real, allocatable::  du_prof_cas(:)
68        real, allocatable::  dv_prof_cas(:)
69        real, allocatable::  uw_prof_cas(:)
70        real, allocatable::  vw_prof_cas(:)
71        real, allocatable::  q1_prof_cas(:)
72        real, allocatable::  q2_prof_cas(:)
73
74
75        real lat_prof_cas,sens_prof_cas,ts_prof_cas,ps_prof_cas,ustar_prof_cas,tke_prof_cas
76        real o3_cas,orog_cas,albedo_cas,emiss_cas,t_skin_cas,q_skin_cas,mom_rough,heat_rough,rugos_cas,sand_cas,clay_cas
77     
78
79
80CONTAINS
81
82
83!**********************************************************************************************
84SUBROUTINE read_SCM_cas
85      implicit none
86
87#include "netcdf.inc"
88#include "date_cas.h"
89
90      INTEGER nid,rid,ierr
91      INTEGER ii,jj,timeid
92      REAL, ALLOCATABLE :: time_val(:)
93
94      print*,'ON EST VRAIMENT LA'
95      fich_cas='cas.nc'
96      print*,'fich_cas ',fich_cas
97      ierr = NF_OPEN(fich_cas,NF_NOWRITE,nid)
98      print*,'fich_cas,NF_NOWRITE,nid ',fich_cas,NF_NOWRITE,nid
99      if (ierr.NE.NF_NOERR) then
100         write(*,*) 'ERROR: GROS Pb opening forcings nc file '
101         write(*,*) NF_STRERROR(ierr)
102         stop ""
103      endif
104!.......................................................................
105      ierr=NF_INQ_DIMID(nid,'lat',rid)
106      IF (ierr.NE.NF_NOERR) THEN
107         print*, 'Oh probleme lecture dimension lat'
108      ENDIF
109      ierr=NF_INQ_DIMLEN(nid,rid,ii)
110      print*,'OK1 read2: nid,rid,lat',nid,rid,ii
111!.......................................................................
112      ierr=NF_INQ_DIMID(nid,'lon',rid)
113      IF (ierr.NE.NF_NOERR) THEN
114         print*, 'Oh probleme lecture dimension lon'
115      ENDIF
116      ierr=NF_INQ_DIMLEN(nid,rid,jj)
117      print*,'OK2 read2: nid,rid,lat',nid,rid,jj
118!.......................................................................
119      ierr=NF_INQ_DIMID(nid,'lev',rid)
120      IF (ierr.NE.NF_NOERR) THEN
121         print*, 'Oh probleme lecture dimension nlev'
122      ENDIF
123      ierr=NF_INQ_DIMLEN(nid,rid,nlev_cas)
124      print*,'OK3 read2: nid,rid,nlev_cas',nid,rid,nlev_cas
125      IF ( .NOT. ( nlev_cas > 10 .AND. nlev_cas < 1000 )) THEN
126              print*,'Valeur de nlev_cas peu probable'
127              STOP
128      ENDIF
129!.......................................................................
130      ierr=NF_INQ_DIMID(nid,'time',rid)
131      nt_cas=0
132      IF (ierr.NE.NF_NOERR) THEN
133        stop 'Oh probleme lecture dimension time'
134      ENDIF
135      ierr=NF_INQ_DIMLEN(nid,rid,nt_cas)
136      print*,'OK4 read2: nid,rid,nt_cas',nid,rid,nt_cas
137! Lecture de l'axe des temps
138      print*,'LECTURE DU TEMPS'
139      ierr=NF_INQ_VARID(nid,'time',timeid)
140         if(ierr/=NF_NOERR) then
141           print *,'Variable time manquante dans cas.nc:'
142           ierr=NF_NOERR
143         else
144                 allocate(time_val(nt_cas))
145#ifdef NC_DOUBLE
146         ierr = NF_GET_VAR_DOUBLE(nid,timeid,time_val)
147#else
148           ierr = NF_GET_VAR_REAL(nid,timeid,time_val)
149#endif
150           if(ierr/=NF_NOERR) then
151              print *,'Pb a la lecture de time cas.nc: '
152           endif
153   endif
154   IF (nt_cas>1) THEN
155           pdt_cas=time_val(2)-time_val(1)
156   ELSE
157           pdt_cas=0.
158   ENDIF
159
160
161!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
162!profils moyens:
163        allocate(plev_cas(nlev_cas,nt_cas),plevh_cas(nlev_cas+1))       
164        allocate(z_cas(nlev_cas,nt_cas),zh_cas(nlev_cas+1))
165        allocate(ap_cas(nlev_cas+1),bp_cas(nt_cas+1))
166        allocate(t_cas(nlev_cas,nt_cas),q_cas(nlev_cas,nt_cas),qv_cas(nlev_cas,nt_cas),ql_cas(nlev_cas,nt_cas), &
167             qi_cas(nlev_cas,nt_cas),rh_cas(nlev_cas,nt_cas))
168        allocate(th_cas(nlev_cas,nt_cas),thl_cas(nlev_cas,nt_cas),thv_cas(nlev_cas,nt_cas),rv_cas(nlev_cas,nt_cas))
169        allocate(u_cas(nlev_cas,nt_cas),v_cas(nlev_cas,nt_cas),vitw_cas(nlev_cas,nt_cas),omega_cas(nlev_cas,nt_cas))
170
171!forcing
172        allocate(ht_cas(nlev_cas,nt_cas),vt_cas(nlev_cas,nt_cas),dt_cas(nlev_cas,nt_cas),dtrad_cas(nlev_cas,nt_cas))
173        allocate(hq_cas(nlev_cas,nt_cas),vq_cas(nlev_cas,nt_cas),dq_cas(nlev_cas,nt_cas))
174        allocate(hth_cas(nlev_cas,nt_cas),vth_cas(nlev_cas,nt_cas),dth_cas(nlev_cas,nt_cas))
175        allocate(hr_cas(nlev_cas,nt_cas),vr_cas(nlev_cas,nt_cas),dr_cas(nlev_cas,nt_cas))
176        allocate(hu_cas(nlev_cas,nt_cas),vu_cas(nlev_cas,nt_cas),du_cas(nlev_cas,nt_cas))
177        allocate(hv_cas(nlev_cas,nt_cas),vv_cas(nlev_cas,nt_cas),dv_cas(nlev_cas,nt_cas))
178        allocate(ug_cas(nlev_cas,nt_cas),vg_cas(nlev_cas,nt_cas))
179        allocate(temp_nudg_cas(nlev_cas,nt_cas),qv_nudg_cas(nlev_cas,nt_cas))
180        allocate(u_nudg_cas(nlev_cas,nt_cas),v_nudg_cas(nlev_cas,nt_cas))
181        allocate(lat_cas(nt_cas),sens_cas(nt_cas),ts_cas(nt_cas),ps_cas(nt_cas),ustar_cas(nt_cas),tke_cas(nt_cas))
182        allocate(uw_cas(nlev_cas,nt_cas),vw_cas(nlev_cas,nt_cas),q1_cas(nlev_cas,nt_cas),q2_cas(nlev_cas,nt_cas))
183
184
185
186!champs interpoles
187        allocate(plev_prof_cas(nlev_cas))
188        allocate(t_prof_cas(nlev_cas))
189        allocate(theta_prof_cas(nlev_cas))
190        allocate(thl_prof_cas(nlev_cas))
191        allocate(thv_prof_cas(nlev_cas))
192        allocate(q_prof_cas(nlev_cas))
193        allocate(qv_prof_cas(nlev_cas))
194        allocate(ql_prof_cas(nlev_cas))
195        allocate(qi_prof_cas(nlev_cas))
196        allocate(rh_prof_cas(nlev_cas))
197        allocate(rv_prof_cas(nlev_cas))
198        allocate(u_prof_cas(nlev_cas))
199        allocate(v_prof_cas(nlev_cas))
200        allocate(vitw_prof_cas(nlev_cas))
201        allocate(omega_prof_cas(nlev_cas))
202        allocate(ug_prof_cas(nlev_cas))
203        allocate(vg_prof_cas(nlev_cas))
204        allocate(temp_nudg_prof_cas(nlev_cas),qv_nudg_prof_cas(nlev_cas))
205        allocate(u_nudg_prof_cas(nlev_cas),v_nudg_prof_cas(nlev_cas))
206        allocate(ht_prof_cas(nlev_cas))
207        allocate(hth_prof_cas(nlev_cas))
208        allocate(hq_prof_cas(nlev_cas))
209        allocate(hu_prof_cas(nlev_cas))
210        allocate(hv_prof_cas(nlev_cas))
211        allocate(vt_prof_cas(nlev_cas))
212        allocate(vth_prof_cas(nlev_cas))
213        allocate(vq_prof_cas(nlev_cas))
214        allocate(vu_prof_cas(nlev_cas))
215        allocate(vv_prof_cas(nlev_cas))
216        allocate(dt_prof_cas(nlev_cas))
217        allocate(dth_prof_cas(nlev_cas))
218        allocate(dtrad_prof_cas(nlev_cas))
219        allocate(dq_prof_cas(nlev_cas))
220        allocate(du_prof_cas(nlev_cas))
221        allocate(dv_prof_cas(nlev_cas))
222        allocate(uw_prof_cas(nlev_cas))
223        allocate(vw_prof_cas(nlev_cas))
224        allocate(q1_prof_cas(nlev_cas))
225        allocate(q2_prof_cas(nlev_cas))
226
227        print*,'Allocations OK'
228        CALL read_SCM (nid,nlev_cas,nt_cas,                                                                     &
229     &     ap_cas,bp_cas,z_cas,plev_cas,zh_cas,plevh_cas,t_cas,th_cas,thv_cas,thl_cas,qv_cas,                   &
230     &     ql_cas,qi_cas,rh_cas,rv_cas,u_cas,v_cas,vitw_cas,omega_cas,ug_cas,vg_cas,                            &
231     &     temp_nudg_cas,qv_nudg_cas,u_nudg_cas,v_nudg_cas,                                                     &
232     &     du_cas,hu_cas,vu_cas,                                                                                &
233     &     dv_cas,hv_cas,vv_cas,dt_cas,ht_cas,vt_cas,dq_cas,hq_cas,vq_cas,dth_cas,hth_cas,vth_cas,               &
234     &     dr_cas,hr_cas,vr_cas,dtrad_cas,sens_cas,lat_cas,ts_cas,ps_cas,ustar_cas,tke_cas,                      &
235     &     uw_cas,vw_cas,q1_cas,q2_cas,orog_cas,albedo_cas,emiss_cas,t_skin_cas,q_skin_cas,mom_rough,heat_rough, &
236     &     o3_cas,rugos_cas,clay_cas,sand_cas)
237        print*,'read_SCM cas OK'
238        do ii=1,nlev_cas
239        print*,'apres read2_SCM, plev_cas=',ii,plev_cas(ii,1)
240        !print*,'apres read_SCM, plev_cas=',ii,omega_cas(ii,nt_cas/2+1)
241        enddo
242
243
244END SUBROUTINE read_SCM_cas
245
246
247!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
248SUBROUTINE deallocate2_1D_cases
249!profils environnementaux:
250        deallocate(plev_cas,plevh_cas)
251       
252        deallocate(z_cas,zh_cas)
253        deallocate(ap_cas,bp_cas)
254        deallocate(t_cas,q_cas,qv_cas,ql_cas,qi_cas,rh_cas)
255        deallocate(th_cas,thl_cas,thv_cas,rv_cas)
256        deallocate(u_cas,v_cas,vitw_cas,omega_cas)
257       
258!forcing
259        deallocate(ht_cas,vt_cas,dt_cas,dtrad_cas)
260        deallocate(hq_cas,vq_cas,dq_cas)
261        deallocate(hth_cas,vth_cas,dth_cas)
262        deallocate(hr_cas,vr_cas,dr_cas)
263        deallocate(hu_cas,vu_cas,du_cas)
264        deallocate(hv_cas,vv_cas,dv_cas)
265        deallocate(ug_cas)
266        deallocate(vg_cas)
267        deallocate(lat_cas,sens_cas,ts_cas,ps_cas,ustar_cas,tke_cas,uw_cas,vw_cas,q1_cas,q2_cas)
268
269!champs interpoles
270        deallocate(plev_prof_cas)
271        deallocate(t_prof_cas)
272        deallocate(theta_prof_cas)
273        deallocate(thl_prof_cas)
274        deallocate(thv_prof_cas)
275        deallocate(q_prof_cas)
276        deallocate(qv_prof_cas)
277        deallocate(ql_prof_cas)
278        deallocate(qi_prof_cas)
279        deallocate(rh_prof_cas)
280        deallocate(rv_prof_cas)
281        deallocate(u_prof_cas)
282        deallocate(v_prof_cas)
283        deallocate(vitw_prof_cas)
284        deallocate(omega_prof_cas)
285        deallocate(ug_prof_cas)
286        deallocate(vg_prof_cas)
287        deallocate(temp_nudg_prof_cas,qv_nudg_prof_cas,u_nudg_prof_cas,v_nudg_prof_cas)
288        deallocate(ht_prof_cas)
289        deallocate(hq_prof_cas)
290        deallocate(hu_prof_cas)
291        deallocate(hv_prof_cas)
292        deallocate(vt_prof_cas)
293        deallocate(vq_prof_cas)
294        deallocate(vu_prof_cas)
295        deallocate(vv_prof_cas)
296        deallocate(dt_prof_cas)
297        deallocate(dtrad_prof_cas)
298        deallocate(dq_prof_cas)
299        deallocate(du_prof_cas)
300        deallocate(dv_prof_cas)
301        deallocate(t_prof_cas)
302        deallocate(u_prof_cas)
303        deallocate(v_prof_cas)
304        deallocate(uw_prof_cas)
305        deallocate(vw_prof_cas)
306        deallocate(q1_prof_cas)
307        deallocate(q2_prof_cas)
308
309END SUBROUTINE deallocate2_1D_cases
310
311
312!=====================================================================
313      SUBROUTINE read_SCM(nid,nlevel,ntime,                                       &
314     &     ap,bp,zz,pp,zzh,pph,temp,theta,thv,thl,qv,ql,qi,rh,rv,u,v,vitw,omega,ug,vg,&
315     &     temp_nudg,qv_nudg,u_nudg,v_nudg,                                        &
316     &     du,hu,vu,dv,hv,vv,dt,ht,vt,dq,hq,vq,                                    &
317     &     dth,hth,vth,dr,hr,vr,dtrad,sens,flat,ts,ps,ustar,tke,uw,vw,q1,q2,       &
318     &     orog_cas,albedo_cas,emiss_cas,t_skin_cas,q_skin_cas,mom_rough,          &
319     &     heat_rough,o3_cas,rugos_cas,clay_cas,sand_cas)
320
321!program reading forcing of the case study
322      implicit none
323#include "netcdf.inc"
324#include "compar1d.h"
325
326      integer ntime,nlevel,k,t
327
328      real ap(nlevel+1),bp(nlevel+1)
329      real zz(nlevel,ntime),zzh(nlevel+1)
330      real pp(nlevel,ntime),pph(nlevel+1)
331!profils initiaux
332      real temp0(nlevel),qv0(nlevel),ql0(nlevel),qi0(nlevel),u0(nlevel),v0(nlevel),tke0(nlevel)
333      real pp0(nlevel)   
334      real temp(nlevel,ntime),qv(nlevel,ntime),ql(nlevel,ntime),qi(nlevel,ntime),rh(nlevel,ntime)
335      real theta(nlevel,ntime),thv(nlevel,ntime),thl(nlevel,ntime),rv(nlevel,ntime)
336      real u(nlevel,ntime),v(nlevel,ntime),tke(nlevel,ntime)
337      real temp_nudg(nlevel,ntime),qv_nudg(nlevel,ntime),u_nudg(nlevel,ntime),v_nudg(nlevel,ntime)
338      real ug(nlevel,ntime),vg(nlevel,ntime)
339      real vitw(nlevel,ntime),omega(nlevel,ntime)
340      real du(nlevel,ntime),hu(nlevel,ntime),vu(nlevel,ntime)
341      real dv(nlevel,ntime),hv(nlevel,ntime),vv(nlevel,ntime)
342      real dt(nlevel,ntime),ht(nlevel,ntime),vt(nlevel,ntime)
343      real dtrad(nlevel,ntime)
344      real dq(nlevel,ntime),hq(nlevel,ntime),vq(nlevel,ntime)
345      real dth(nlevel,ntime),hth(nlevel,ntime),vth(nlevel,ntime),hthl(nlevel,ntime)
346      real dr(nlevel,ntime),hr(nlevel,ntime),vr(nlevel,ntime)
347      real flat(ntime),sens(ntime),ustar(ntime)
348      real uw(nlevel,ntime),vw(nlevel,ntime),q1(nlevel,ntime),q2(nlevel,ntime)
349      real ts(ntime),ps(ntime)
350      real orog_cas,albedo_cas,emiss_cas,t_skin_cas,q_skin_cas,mom_rough,heat_rough,o3_cas,rugos_cas,clay_cas,sand_cas
351      real apbp(nlevel+1),resul(nlevel,ntime),resul1(nlevel),resul2(ntime),resul3
352
353
354      integer nid, ierr,ierr1,ierr2,rid,i
355      integer nbvar3d
356      parameter(nbvar3d=74)
357      integer var3didin(nbvar3d),missing_var(nbvar3d)
358      character*13 name_var(1:nbvar3d)
359
360
361      data name_var/ &
362     ! coordonnees pression (n+1 niveaux) #4
363     & 'coor_par_a','coor_par_b','height_h','pressure_h',& ! #1-#4
364     ! coordonnees pression (n niveaux) #8
365     &'temp','qv','ql','qi','u','v','tke','pressure',& ! #5-#12
366     ! coordonnees pression + temps #42
367     &'w','omega','ug','vg','uadv','uadvh','uadvv','vadv','vadvh','vadvv','tadv','tadvh','tadvv',& !  #13 - #25
368     &'qvadv','qvadvh','qvadvv','thadv','thadvh','thadvv','thladvh',                             & ! #26 - #33
369     & 'radv','radvh','radvv','radcool','q1','q2','ustress','vstress',                           & ! #34 - #41
370     & 'rh','temp_nudg','qv_nudg','u_nudg','v_nudg',&
371     &'height_f','pressure_forc','tempt','theta','thv','thl','qvt','qlt','qit','rv','ut','vt','tket',&
372     ! coordonnees temps #12
373     &'sfc_sens_flx','sfc_lat_flx','ts','ps','ustar',&
374     &'orog','albedo','emiss','t_skin','q_skin','mom_rough','heat_rough',&
375     ! scalaires #4
376     &'o3','rugos','clay','sand'/
377
378      do i=1,nbvar3d
379        missing_var(i)=0.
380      enddo
381
382!-----------------------------------------------------------------------
383
384       do i=1,nbvar3d
385         ierr=NF_INQ_VARID(nid,name_var(i),var3didin(i))
386         if(ierr/=NF_NOERR) then
387           print *,'Variable manquante dans cas.nc:',i,name_var(i)
388           ierr=NF_NOERR
389           missing_var(i)=1
390         else
391
392!-----------------------------------------------------------------------
393! Activation de quelques cles en fonction des variables disponibles
394!-----------------------------------------------------------------------
395if ( 1 == 1 ) THEN
396            if ( name_var(i) == 'temp_nudg' .and. nint(nudging_t)==0) stop 'Nudging inconsistency temp'
397            if ( name_var(i) == 'qv_nudg' .and. nint(nudging_qv)==0) stop 'Nudging inconsistency qv'
398            if ( name_var(i) == 'u_nudg' .and. nint(nudging_u)==0) stop 'Nudging inconsistency u'
399            if ( name_var(i) == 'v_nudg' .and. nint(nudging_u)==0) stop 'Nudging inconsistency v'
400    ELSE
401             print*,'GUIDAGE : CONSISTENCY CHECK DEACTIVATED FOR TESTS of SANDU/REF'
402    ENDIF
403
404!-----------------------------------------------------------------------
405           if(i.LE.4) then     ! Lecture des coord pression en (nlevelp1,lat,lon)
406#ifdef NC_DOUBLE
407           ierr = NF_GET_VAR_DOUBLE(nid,var3didin(i),apbp)
408#else
409           ierr = NF_GET_VAR_REAL(nid,var3didin(i),apbp)
410#endif
411           print *,'read2_cas(apbp), on a lu ',i,name_var(i)
412           if(ierr/=NF_NOERR) then
413              print *,'Pb a la lecture de cas.nc: ',name_var(i)
414              stop "getvarup"
415           endif
416!-----------------------------------------------------------------------
417           else if(i.gt.4.and.i.LE.12) then   ! Lecture des variables en (time,nlevel,lat,lon)
418#ifdef NC_DOUBLE
419           ierr = NF_GET_VAR_DOUBLE(nid,var3didin(i),resul1)
420#else
421           ierr = NF_GET_VAR_REAL(nid,var3didin(i),resul1)
422#endif
423           print *,'read2_cas(resul1), on a lu ',i,name_var(i)
424           if(ierr/=NF_NOERR) then
425              print *,'Pb a la lecture de cas.nc: ',name_var(i)
426              stop "getvarup"
427           endif
428         print*,'Lecture de la variable #i ',i,name_var(i),minval(resul1),maxval(resul1)
429!-----------------------------------------------------------------------
430           else if(i.gt.12.and.i.LE.54) then   ! Lecture des variables en (time,nlevel,lat,lon)
431#ifdef NC_DOUBLE
432           ierr = NF_GET_VAR_DOUBLE(nid,var3didin(i),resul)
433#else
434           ierr = NF_GET_VAR_REAL(nid,var3didin(i),resul)
435#endif
436           print *,'read2_cas(resul), on a lu ',i,name_var(i)
437           if(ierr/=NF_NOERR) then
438              print *,'Pb a la lecture de cas.nc: ',name_var(i)
439              stop "getvarup"
440           endif
441
442         print*,'Lecture de la variable #i ',i,name_var(i),minval(resul),maxval(resul)
443!-----------------------------------------------------------------------
444           else if (i.gt.54.and.i.LE.65) then   ! Lecture des variables en (time,lat,lon)
445#ifdef NC_DOUBLE
446           ierr = NF_GET_VAR_DOUBLE(nid,var3didin(i),resul2)
447#else
448           ierr = NF_GET_VAR_REAL(nid,var3didin(i),resul2)
449#endif
450           print *,'read2_cas(resul2), on a lu ',i,name_var(i)
451           if(ierr/=NF_NOERR) then
452              print *,'Pb a la lecture de cas.nc: ',name_var(i)
453              stop "getvarup"
454           endif
455         print*,'Lecture de la variable #i  ',i,name_var(i),minval(resul2),maxval(resul2)
456!-----------------------------------------------------------------------
457           else     ! Lecture des constantes (lat,lon)
458#ifdef NC_DOUBLE
459           ierr = NF_GET_VAR_DOUBLE(nid,var3didin(i),resul3)
460#else
461           ierr = NF_GET_VAR_REAL(nid,var3didin(i),resul3)
462#endif
463           print *,'read2_cas(resul3), on a lu ',i,name_var(i)
464           if(ierr/=NF_NOERR) then
465              print *,'Pb a la lecture de cas.nc: ',name_var(i)
466              stop "getvarup"
467           endif
468         print*,'Lecture de la variable #i ',i,name_var(i),resul3
469           endif
470         endif
471!-----------------------------------------------------------------------
472         select case(i)
473         !case(1) ; ap=apbp       ! donnees indexees en nlevel+1
474         ! case(2) ; bp=apbp
475           case(3) ; zzh=apbp
476           case(4) ; pph=apbp
477           case(5) ; temp0=resul1    ! donnees initiales
478           case(6) ; qv0=resul1
479           case(7) ; ql0=resul1
480           case(8) ; qi0=resul1
481           case(9) ; u0=resul1
482           case(10) ; v0=resul1
483           case(11) ; tke0=resul1
484           case(12) ; pp0=resul1
485           case(13) ; vitw=resul    ! donnees indexees en nlevel,time
486           case(14) ; omega=resul
487           case(15) ; ug=resul
488           case(16) ; vg=resul
489           case(17) ; du=resul
490           case(18) ; hu=resul
491           case(19) ; vu=resul
492           case(20) ; dv=resul
493           case(21) ; hv=resul
494           case(22) ; vv=resul
495           case(23) ; dt=resul
496           case(24) ; ht=resul
497           case(25) ; vt=resul
498           case(26) ; dq=resul
499           case(27) ; hq=resul
500           case(28) ; vq=resul
501           case(29) ; dth=resul
502           case(30) ; hth=resul
503           case(31) ; vth=resul
504           case(32) ; hthl=resul
505           case(33) ; dr=resul
506           case(34) ; hr=resul
507           case(35) ; vr=resul
508           case(36) ; dtrad=resul
509           case(37) ; q1=resul
510           case(38) ; q2=resul
511           case(39) ; uw=resul
512           case(40) ; vw=resul
513           case(41) ; rh=resul
514           case(42) ; temp_nudg=resul
515           case(43) ; qv_nudg=resul
516           case(44) ; u_nudg=resul
517           case(45) ; v_nudg=resul
518           case(46) ; zz=resul      ! donnees en time,nlevel pour profil initial
519           case(47) ; pp=resul
520           case(48) ; temp=resul
521           case(49) ; theta=resul
522           case(50) ; thv=resul
523           case(51) ; thl=resul
524           case(52) ; qv=resul
525           case(53) ; ql=resul
526           case(54) ; qi=resul
527           case(55) ; rv=resul
528           case(56) ; u=resul
529           case(57) ; v=resul
530           case(58) ; tke=resul
531           case(59) ; sens=resul2   ! donnees indexees en time
532           case(60) ; flat=resul2
533           case(61) ; ts=resul2
534           case(62) ; ps=resul2
535           case(63) ; ustar=resul2
536           case(64) ; orog_cas=resul3      ! constantes
537           case(65) ; albedo_cas=resul3
538           case(66) ; emiss_cas=resul3
539           case(67) ; t_skin_cas=resul3
540           case(68) ; q_skin_cas=resul3
541           case(69) ; mom_rough=resul3
542           case(70) ; heat_rough=resul3
543           case(71) ; o3_cas=resul3       
544           case(72) ; rugos_cas=resul3
545           case(73) ; clay_cas=resul3
546           case(74) ; sand_cas=resul3
547         end select
548         resul=0.
549         resul1=0.
550         resul2=0.
551         resul3=0.
552       enddo
553         print*,'Lecture de la variable APRES ,sens ',minval(sens),maxval(sens)
554         print*,'Lecture de la variable APRES ,flat ',minval(flat),maxval(flat)
555
556!CR:ATTENTION EN ATTENTE DE REGLER LA QUESTION DU PAS DE TEMPS INITIAL
557       do t=1,ntime
558          do k=1,nlevel
559             temp(k,t)=temp0(k)
560             qv(k,t)=qv0(k)
561             ql(k,t)=ql0(k)
562             qi(k,t)=qi0(k)
563             u(k,t)=u0(k)
564             v(k,t)=v0(k)
565             tke(k,t)=tke0(k)
566          enddo
567       enddo
568       !!!! TRAVAIL : EN FONCTION DES DECISIONS SUR LA SPECIFICATION DE W
569       !!!omega=-vitw*pres*rg/(rd*temp)
570!-----------------------------------------------------------------------
571
572         return
573         END SUBROUTINE read_SCM
574!======================================================================
575
576!======================================================================
577
578!**********************************************************************************************
579        SUBROUTINE interp_case_time_std(day,day1,annee_ref                           &
580!    &         ,year_cas,day_cas,nt_cas,pdt_forc,nlev_cas                         &
581     &         ,nt_cas,nlev_cas                                                   &
582     &         ,ts_cas,ps_cas,plev_cas,t_cas,theta_cas,thv_cas,thl_cas            &
583     &         ,qv_cas,ql_cas,qi_cas,u_cas,v_cas                                  &
584     &         ,ug_cas,vg_cas,temp_nudg_cas,qv_nudg_cas,u_nudg_cas,v_nudg_cas     &
585     &         ,vitw_cas,omega_cas,du_cas,hu_cas,vu_cas             &
586     &         ,dv_cas,hv_cas,vv_cas,dt_cas,ht_cas,vt_cas,dtrad_cas               &
587     &         ,dq_cas,hq_cas,vq_cas,dth_cas,hth_cas,vth_cas                      &
588     &         ,lat_cas,sens_cas,ustar_cas                                        &
589     &         ,uw_cas,vw_cas,q1_cas,q2_cas,tke_cas                               &
590!
591     &         ,ts_prof_cas,ps_prof_cas,plev_prof_cas,t_prof_cas,theta_prof_cas               &
592     &         ,thv_prof_cas,thl_prof_cas,qv_prof_cas,ql_prof_cas,qi_prof_cas     &
593     &         ,u_prof_cas,v_prof_cas,ug_prof_cas,vg_prof_cas                     &
594     &         ,temp_nudg_prof_cas,qv_nudg_prof_cas,u_nudg_prof_cas,v_nudg_prof_cas     &
595     &         ,vitw_prof_cas,omega_prof_cas,du_prof_cas,hu_prof_cas,vu_prof_cas  &
596     &         ,dv_prof_cas,hv_prof_cas,vv_prof_cas,dt_prof_cas                   &
597     &         ,ht_prof_cas,vt_prof_cas,dtrad_prof_cas,dq_prof_cas                &
598     &         ,hq_prof_cas,vq_prof_cas,dth_prof_cas,hth_prof_cas,vth_prof_cas    &
599     &         ,lat_prof_cas,sens_prof_cas                                        &
600     &         ,ustar_prof_cas,uw_prof_cas,vw_prof_cas,q1_prof_cas,q2_prof_cas,tke_prof_cas)
601         
602
603        implicit none
604
605!---------------------------------------------------------------------------------------
606! Time interpolation of a 2D field to the timestep corresponding to day
607!
608! day: current julian day (e.g. 717538.2)
609! day1: first day of the simulation
610! nt_cas: total nb of data in the forcing
611! pdt_cas: total time interval (in sec) between 2 forcing data
612!---------------------------------------------------------------------------------------
613
614#include "compar1d.h"
615#include "date_cas.h"
616
617! inputs:
618        integer annee_ref
619        integer nt_cas,nlev_cas
620        real day, day1,day_cas
621        real ts_cas(nt_cas),ps_cas(nt_cas)
622        real plev_cas(nlev_cas,nt_cas)
623        real t_cas(nlev_cas,nt_cas),theta_cas(nlev_cas,nt_cas),thv_cas(nlev_cas,nt_cas),thl_cas(nlev_cas,nt_cas)
624        real qv_cas(nlev_cas,nt_cas),ql_cas(nlev_cas,nt_cas),qi_cas(nlev_cas,nt_cas)
625        real u_cas(nlev_cas,nt_cas),v_cas(nlev_cas,nt_cas)
626        real ug_cas(nlev_cas,nt_cas),vg_cas(nlev_cas,nt_cas)
627        real temp_nudg_cas(nlev_cas,nt_cas),qv_nudg_cas(nlev_cas,nt_cas)
628        real u_nudg_cas(nlev_cas,nt_cas),v_nudg_cas(nlev_cas,nt_cas)
629
630        real vitw_cas(nlev_cas,nt_cas),omega_cas(nlev_cas,nt_cas)
631        real du_cas(nlev_cas,nt_cas),hu_cas(nlev_cas,nt_cas),vu_cas(nlev_cas,nt_cas)
632        real dv_cas(nlev_cas,nt_cas),hv_cas(nlev_cas,nt_cas),vv_cas(nlev_cas,nt_cas)
633        real dt_cas(nlev_cas,nt_cas),ht_cas(nlev_cas,nt_cas),vt_cas(nlev_cas,nt_cas)
634        real dth_cas(nlev_cas,nt_cas),hth_cas(nlev_cas,nt_cas),vth_cas(nlev_cas,nt_cas)
635        real dtrad_cas(nlev_cas,nt_cas)
636        real dq_cas(nlev_cas,nt_cas),hq_cas(nlev_cas,nt_cas),vq_cas(nlev_cas,nt_cas)
637        real lat_cas(nt_cas),sens_cas(nt_cas),tke_cas(nt_cas)
638        real ustar_cas(nt_cas),uw_cas(nlev_cas,nt_cas),vw_cas(nlev_cas,nt_cas)
639        real q1_cas(nlev_cas,nt_cas),q2_cas(nlev_cas,nt_cas)
640
641! outputs:
642        real plev_prof_cas(nlev_cas)
643        real t_prof_cas(nlev_cas),theta_prof_cas(nlev_cas),thl_prof_cas(nlev_cas),thv_prof_cas(nlev_cas)
644        real qv_prof_cas(nlev_cas),ql_prof_cas(nlev_cas),qi_prof_cas(nlev_cas)
645        real u_prof_cas(nlev_cas),v_prof_cas(nlev_cas)
646        real ug_prof_cas(nlev_cas),vg_prof_cas(nlev_cas)
647        real temp_nudg_prof_cas(nlev_cas),qv_nudg_prof_cas(nlev_cas)
648        real u_nudg_prof_cas(nlev_cas),v_nudg_prof_cas(nlev_cas)
649
650        real vitw_prof_cas(nlev_cas),omega_prof_cas(nlev_cas)
651        real du_prof_cas(nlev_cas),hu_prof_cas(nlev_cas),vu_prof_cas(nlev_cas)
652        real dv_prof_cas(nlev_cas),hv_prof_cas(nlev_cas),vv_prof_cas(nlev_cas)
653        real dt_prof_cas(nlev_cas),ht_prof_cas(nlev_cas),vt_prof_cas(nlev_cas)
654        real dth_prof_cas(nlev_cas),hth_prof_cas(nlev_cas),vth_prof_cas(nlev_cas)
655        real dtrad_prof_cas(nlev_cas)
656        real dq_prof_cas(nlev_cas),hq_prof_cas(nlev_cas),vq_prof_cas(nlev_cas)
657        real lat_prof_cas,sens_prof_cas,tke_prof_cas,ts_prof_cas,ps_prof_cas,ustar_prof_cas
658        real uw_prof_cas(nlev_cas),vw_prof_cas(nlev_cas),q1_prof_cas(nlev_cas),q2_prof_cas(nlev_cas)
659! local:
660        integer it_cas1, it_cas2,k
661        real timeit,time_cas1,time_cas2,frac
662
663
664        print*,'Check time',day1,day_ju_ini_cas,day_deb+1,pdt_cas
665!       do k=1,nlev_cas
666!       print*,'debut de interp2_case_time, plev_cas=',k,plev_cas(k,1)
667!       enddo
668
669! On teste si la date du cas AMMA est correcte.
670! C est pour memoire car en fait les fichiers .def
671! sont censes etre corrects.
672! A supprimer a terme (MPL 20150623)
673!     if ((forcing_type.eq.10).and.(1.eq.0)) then
674! Check that initial day of the simulation consistent with AMMA case:
675!      if (annee_ref.ne.2006) then
676!       print*,'Pour AMMA, annee_ref doit etre 2006'
677!       print*,'Changer annee_ref dans run.def'
678!       stop
679!      endif
680!      if (annee_ref.eq.2006 .and. day1.lt.day_cas) then
681!       print*,'AMMA a debute le 10 juillet 2006',day1,day_cas
682!       print*,'Changer dayref dans run.def'
683!       stop
684!      endif
685!      if (annee_ref.eq.2006 .and. day1.gt.day_cas+1) then
686!       print*,'AMMA a fini le 11 juillet'
687!       print*,'Changer dayref ou nday dans run.def'
688!       stop
689!      endif
690!      endif
691
692! Determine timestep relative to the 1st day:
693!       timeit=(day-day1)*86400.
694!       if (annee_ref.eq.1992) then
695!        timeit=(day-day_cas)*86400.
696!       else
697!        timeit=(day+61.-1.)*86400. ! 61 days between Nov01 and Dec31 1992
698!       endif
699      timeit=(day-day_ju_ini_cas)*86400
700      print *,'day=',day
701      print *,'day_ju_ini_cas=',day_ju_ini_cas
702      print *,'pdt_cas=',pdt_cas
703      print *,'timeit=',timeit
704      print *,'nt_cas=',nt_cas
705
706! Determine the closest observation times:
707!       it_cas1=INT(timeit/pdt_cas)+1
708!       it_cas2=it_cas1 + 1
709!       time_cas1=(it_cas1-1)*pdt_cas
710!       time_cas2=(it_cas2-1)*pdt_cas
711
712       it_cas1=INT(timeit/pdt_cas)+1
713       IF (it_cas1 .EQ. nt_cas) THEN
714       it_cas2=it_cas1
715       ELSE
716       it_cas2=it_cas1 + 1
717       ENDIF
718       time_cas1=(it_cas1-1)*pdt_cas
719       time_cas2=(it_cas2-1)*pdt_cas
720!     print *,'timeit,pdt_cas,nt_cas=',timeit,pdt_cas,nt_cas
721!     print *,'it_cas1,it_cas2,time_cas1,time_cas2=',it_cas1,it_cas2,time_cas1,time_cas2
722
723       if (it_cas1 .gt. nt_cas) then
724        write(*,*) 'PB-stop: day, day_ju_ini_cas,it_cas1, it_cas2, timeit: '            &
725     &        ,day,day_ju_ini_cas,it_cas1,it_cas2,timeit
726        stop
727       endif
728
729! time interpolation:
730       IF (it_cas1 .EQ. it_cas2) THEN
731          frac=0.
732       ELSE
733          frac=(time_cas2-timeit)/(time_cas2-time_cas1)
734          frac=max(frac,0.0)
735       ENDIF
736
737       lat_prof_cas = lat_cas(it_cas2)                                   &
738     &          -frac*(lat_cas(it_cas2)-lat_cas(it_cas1))
739       sens_prof_cas = sens_cas(it_cas2)                                 &
740     &          -frac*(sens_cas(it_cas2)-sens_cas(it_cas1))
741       tke_prof_cas = tke_cas(it_cas2)                                   &
742     &          -frac*(tke_cas(it_cas2)-tke_cas(it_cas1))
743       ts_prof_cas = ts_cas(it_cas2)                                     &
744     &          -frac*(ts_cas(it_cas2)-ts_cas(it_cas1))
745       ps_prof_cas = ps_cas(it_cas2)                                     &
746     &          -frac*(ps_cas(it_cas2)-ps_cas(it_cas1))
747       ustar_prof_cas = ustar_cas(it_cas2)                               &
748     &          -frac*(ustar_cas(it_cas2)-ustar_cas(it_cas1))
749
750       do k=1,nlev_cas
751        plev_prof_cas(k) = plev_cas(k,it_cas2)                           &     
752     &          -frac*(plev_cas(k,it_cas2)-plev_cas(k,it_cas1))
753        t_prof_cas(k) = t_cas(k,it_cas2)                                 &       
754     &          -frac*(t_cas(k,it_cas2)-t_cas(k,it_cas1))
755        !print *,'k,frac,plev_cas1,plev_cas2=',k,frac,plev_cas(k,it_cas1),plev_cas(k,it_cas2)
756        theta_prof_cas(k) = theta_cas(k,it_cas2)                         &                     
757     &          -frac*(theta_cas(k,it_cas2)-theta_cas(k,it_cas1))
758        thv_prof_cas(k) = thv_cas(k,it_cas2)                             &         
759     &          -frac*(thv_cas(k,it_cas2)-thv_cas(k,it_cas1))
760        thl_prof_cas(k) = thl_cas(k,it_cas2)                             &             
761     &          -frac*(thl_cas(k,it_cas2)-thl_cas(k,it_cas1))
762        qv_prof_cas(k) = qv_cas(k,it_cas2)                               &
763     &          -frac*(qv_cas(k,it_cas2)-qv_cas(k,it_cas1))
764        ql_prof_cas(k) = ql_cas(k,it_cas2)                               &
765     &          -frac*(ql_cas(k,it_cas2)-ql_cas(k,it_cas1))
766        qi_prof_cas(k) = qi_cas(k,it_cas2)                               &
767     &          -frac*(qi_cas(k,it_cas2)-qi_cas(k,it_cas1))
768        u_prof_cas(k) = u_cas(k,it_cas2)                                 &
769     &          -frac*(u_cas(k,it_cas2)-u_cas(k,it_cas1))
770        v_prof_cas(k) = v_cas(k,it_cas2)                                 &
771     &          -frac*(v_cas(k,it_cas2)-v_cas(k,it_cas1))
772        ug_prof_cas(k) = ug_cas(k,it_cas2)                               &
773     &          -frac*(ug_cas(k,it_cas2)-ug_cas(k,it_cas1))
774        vg_prof_cas(k) = vg_cas(k,it_cas2)                               &
775     &          -frac*(vg_cas(k,it_cas2)-vg_cas(k,it_cas1))
776        temp_nudg_prof_cas(k) = temp_nudg_cas(k,it_cas2)                    &
777     &          -frac*(temp_nudg_cas(k,it_cas2)-temp_nudg_cas(k,it_cas1))
778        qv_nudg_prof_cas(k) = qv_nudg_cas(k,it_cas2)                        &
779     &          -frac*(qv_nudg_cas(k,it_cas2)-qv_nudg_cas(k,it_cas1))
780        u_nudg_prof_cas(k) = u_nudg_cas(k,it_cas2)                          &
781     &          -frac*(u_nudg_cas(k,it_cas2)-u_nudg_cas(k,it_cas1))
782        v_nudg_prof_cas(k) = v_nudg_cas(k,it_cas2)                          &
783     &          -frac*(v_nudg_cas(k,it_cas2)-v_nudg_cas(k,it_cas1))
784        vitw_prof_cas(k) = vitw_cas(k,it_cas2)                           &
785     &          -frac*(vitw_cas(k,it_cas2)-vitw_cas(k,it_cas1))
786        omega_prof_cas(k) = omega_cas(k,it_cas2)                         &
787     &          -frac*(omega_cas(k,it_cas2)-omega_cas(k,it_cas1))
788        du_prof_cas(k) = du_cas(k,it_cas2)                               &
789     &          -frac*(du_cas(k,it_cas2)-du_cas(k,it_cas1))
790        hu_prof_cas(k) = hu_cas(k,it_cas2)                               &
791     &          -frac*(hu_cas(k,it_cas2)-hu_cas(k,it_cas1))
792        vu_prof_cas(k) = vu_cas(k,it_cas2)                               &
793     &          -frac*(vu_cas(k,it_cas2)-vu_cas(k,it_cas1))
794        dv_prof_cas(k) = dv_cas(k,it_cas2)                               &
795     &          -frac*(dv_cas(k,it_cas2)-dv_cas(k,it_cas1))
796        hv_prof_cas(k) = hv_cas(k,it_cas2)                               &
797     &          -frac*(hv_cas(k,it_cas2)-hv_cas(k,it_cas1))
798        vv_prof_cas(k) = vv_cas(k,it_cas2)                               &
799     &          -frac*(vv_cas(k,it_cas2)-vv_cas(k,it_cas1))
800        dt_prof_cas(k) = dt_cas(k,it_cas2)                               &
801     &          -frac*(dt_cas(k,it_cas2)-dt_cas(k,it_cas1))
802        ht_prof_cas(k) = ht_cas(k,it_cas2)                               &
803     &          -frac*(ht_cas(k,it_cas2)-ht_cas(k,it_cas1))
804        vt_prof_cas(k) = vt_cas(k,it_cas2)                               &
805     &          -frac*(vt_cas(k,it_cas2)-vt_cas(k,it_cas1))
806        dth_prof_cas(k) = dth_cas(k,it_cas2)                             &
807     &          -frac*(dth_cas(k,it_cas2)-dth_cas(k,it_cas1))
808        hth_prof_cas(k) = hth_cas(k,it_cas2)                             &
809     &          -frac*(hth_cas(k,it_cas2)-hth_cas(k,it_cas1))
810        vth_prof_cas(k) = vth_cas(k,it_cas2)                             &
811     &          -frac*(vth_cas(k,it_cas2)-vth_cas(k,it_cas1))
812        dtrad_prof_cas(k) = dtrad_cas(k,it_cas2)                         &
813     &          -frac*(dtrad_cas(k,it_cas2)-dtrad_cas(k,it_cas1))
814        dq_prof_cas(k) = dq_cas(k,it_cas2)                               &
815     &          -frac*(dq_cas(k,it_cas2)-dq_cas(k,it_cas1))
816        hq_prof_cas(k) = hq_cas(k,it_cas2)                               &
817     &          -frac*(hq_cas(k,it_cas2)-hq_cas(k,it_cas1))
818        vq_prof_cas(k) = vq_cas(k,it_cas2)                               &
819     &          -frac*(vq_cas(k,it_cas2)-vq_cas(k,it_cas1))
820       uw_prof_cas(k) = uw_cas(k,it_cas2)                                &
821     &          -frac*(uw_cas(k,it_cas2)-uw_cas(k,it_cas1))
822       vw_prof_cas(k) = vw_cas(k,it_cas2)                                &
823     &          -frac*(vw_cas(k,it_cas2)-vw_cas(k,it_cas1))
824       q1_prof_cas(k) = q1_cas(k,it_cas2)                                &
825     &          -frac*(q1_cas(k,it_cas2)-q1_cas(k,it_cas1))
826       q2_prof_cas(k) = q2_cas(k,it_cas2)                                &
827     &          -frac*(q2_cas(k,it_cas2)-q2_cas(k,it_cas1))
828        enddo
829
830        return
831        END SUBROUTINE interp_case_time_std
832
833!**********************************************************************************************
834!=====================================================================
835       SUBROUTINE interp2_case_vertical_std(play,nlev_cas,plev_prof_cas                                &
836     &         ,t_prof_cas,th_prof_cas,thv_prof_cas,thl_prof_cas                                       &
837     &         ,qv_prof_cas,ql_prof_cas,qi_prof_cas,u_prof_cas,v_prof_cas                              &
838     &         ,ug_prof_cas,vg_prof_cas                                                                &
839     &         ,temp_nudg_prof_cas,qv_nudg_prof_cas,u_nudg_prof_cas,v_nudg_prof_cas                    &
840     &         ,vitw_prof_cas,omega_prof_cas                                                           &
841     &         ,du_prof_cas,hu_prof_cas,vu_prof_cas,dv_prof_cas,hv_prof_cas,vv_prof_cas                &
842     &         ,dt_prof_cas,ht_prof_cas,vt_prof_cas,dtrad_prof_cas,dq_prof_cas,hq_prof_cas,vq_prof_cas &
843     &         ,dth_prof_cas,hth_prof_cas,vth_prof_cas                                                 &
844!
845     &         ,t_mod_cas,theta_mod_cas,thv_mod_cas,thl_mod_cas                                        &
846     &         ,qv_mod_cas,ql_mod_cas,qi_mod_cas,u_mod_cas,v_mod_cas                                   &
847     &         ,ug_mod_cas,vg_mod_cas                                                                  &
848     &         ,temp_nudg_mod_cas,qv_nudg_mod_cas,u_nudg_mod_cas,v_nudg_mod_cas                        &
849     &         ,w_mod_cas,omega_mod_cas                                                                &
850     &         ,du_mod_cas,hu_mod_cas,vu_mod_cas,dv_mod_cas,hv_mod_cas,vv_mod_cas                      &
851     &         ,dt_mod_cas,ht_mod_cas,vt_mod_cas,dtrad_mod_cas,dq_mod_cas,hq_mod_cas,vq_mod_cas        &
852     &         ,dth_mod_cas,hth_mod_cas,vth_mod_cas,mxcalc)
853 
854       implicit none
855 
856#include "YOMCST.h"
857#include "dimensions.h"
858
859!-------------------------------------------------------------------------
860! Vertical interpolation of generic case forcing data onto mod_casel levels
861!-------------------------------------------------------------------------
862 
863       integer nlevmax
864       parameter (nlevmax=41)
865       integer nlev_cas,mxcalc
866!       real play(llm), plev_prof(nlevmax)
867!       real t_prof(nlevmax),q_prof(nlevmax)
868!       real u_prof(nlevmax),v_prof(nlevmax), w_prof(nlevmax)
869!       real ht_prof(nlevmax),vt_prof(nlevmax)
870!       real hq_prof(nlevmax),vq_prof(nlevmax)
871 
872       real play(llm), plev_prof_cas(nlev_cas)
873       real t_prof_cas(nlev_cas),th_prof_cas(nlev_cas),thv_prof_cas(nlev_cas),thl_prof_cas(nlev_cas)
874       real qv_prof_cas(nlev_cas),ql_prof_cas(nlev_cas),qi_prof_cas(nlev_cas)
875       real u_prof_cas(nlev_cas),v_prof_cas(nlev_cas)
876       real ug_prof_cas(nlev_cas),vg_prof_cas(nlev_cas), vitw_prof_cas(nlev_cas),omega_prof_cas(nlev_cas)
877       real temp_nudg_prof_cas(nlev_cas),qv_nudg_prof_cas(nlev_cas)
878       real u_nudg_prof_cas(nlev_cas),v_nudg_prof_cas(nlev_cas)
879
880       real du_prof_cas(nlev_cas),hu_prof_cas(nlev_cas),vu_prof_cas(nlev_cas)
881       real dv_prof_cas(nlev_cas),hv_prof_cas(nlev_cas),vv_prof_cas(nlev_cas)
882       real dt_prof_cas(nlev_cas),ht_prof_cas(nlev_cas),vt_prof_cas(nlev_cas),dtrad_prof_cas(nlev_cas)
883       real dth_prof_cas(nlev_cas),hth_prof_cas(nlev_cas),vth_prof_cas(nlev_cas)
884       real dq_prof_cas(nlev_cas),hq_prof_cas(nlev_cas),vq_prof_cas(nlev_cas)
885 
886       real t_mod_cas(llm),theta_mod_cas(llm),thv_mod_cas(llm),thl_mod_cas(llm)
887       real qv_mod_cas(llm),ql_mod_cas(llm),qi_mod_cas(llm)
888       real u_mod_cas(llm),v_mod_cas(llm)
889       real ug_mod_cas(llm),vg_mod_cas(llm), w_mod_cas(llm),omega_mod_cas(llm)
890       real temp_nudg_mod_cas(llm),qv_nudg_mod_cas(llm)
891       real u_nudg_mod_cas(llm),v_nudg_mod_cas(llm)
892       real du_mod_cas(llm),hu_mod_cas(llm),vu_mod_cas(llm)
893       real dv_mod_cas(llm),hv_mod_cas(llm),vv_mod_cas(llm)
894       real dt_mod_cas(llm),ht_mod_cas(llm),vt_mod_cas(llm),dtrad_mod_cas(llm)
895       real dth_mod_cas(llm),hth_mod_cas(llm),vth_mod_cas(llm)
896       real dq_mod_cas(llm),hq_mod_cas(llm),vq_mod_cas(llm)
897 
898       integer l,k,k1,k2
899       real frac,frac1,frac2,fact
900 
901!       do l = 1, llm
902!       print *,'debut interp2, play=',l,play(l)
903!       enddo
904!      do l = 1, nlev_cas
905!      print *,'debut interp2, plev_prof_cas=',l,play(l),plev_prof_cas(l)
906!      enddo
907
908       do l = 1, llm
909
910        if (play(l).ge.plev_prof_cas(nlev_cas)) then
911 
912        mxcalc=l
913!        print *,'debut interp2, mxcalc=',mxcalc
914         k1=0
915         k2=0
916
917         if (play(l).le.plev_prof_cas(1)) then
918
919         do k = 1, nlev_cas-1
920          if (play(l).le.plev_prof_cas(k).and. play(l).gt.plev_prof_cas(k+1)) then
921            k1=k
922            k2=k+1
923          endif
924         enddo
925
926         if (k1.eq.0 .or. k2.eq.0) then
927          write(*,*) 'PB! k1, k2 = ',k1,k2
928          write(*,*) 'l,play(l) = ',l,play(l)/100
929         do k = 1, nlev_cas-1
930          write(*,*) 'k,plev_prof_cas(k) = ',k,plev_prof_cas(k)/100
931         enddo
932         endif
933
934         frac = (plev_prof_cas(k2)-play(l))/(plev_prof_cas(k2)-plev_prof_cas(k1))
935         t_mod_cas(l)= t_prof_cas(k2) - frac*(t_prof_cas(k2)-t_prof_cas(k1))
936         theta_mod_cas(l)= th_prof_cas(k2) - frac*(th_prof_cas(k2)-th_prof_cas(k1))
937         if(theta_mod_cas(l).NE.0) t_mod_cas(l)= theta_mod_cas(l)*(play(l)/100000.)**(RD/RCPD)
938         thv_mod_cas(l)= thv_prof_cas(k2) - frac*(thv_prof_cas(k2)-thv_prof_cas(k1))
939         thl_mod_cas(l)= thl_prof_cas(k2) - frac*(thl_prof_cas(k2)-thl_prof_cas(k1))
940         qv_mod_cas(l)= qv_prof_cas(k2) - frac*(qv_prof_cas(k2)-qv_prof_cas(k1))
941         ql_mod_cas(l)= ql_prof_cas(k2) - frac*(ql_prof_cas(k2)-ql_prof_cas(k1))
942         qi_mod_cas(l)= qi_prof_cas(k2) - frac*(qi_prof_cas(k2)-qi_prof_cas(k1))
943         u_mod_cas(l)= u_prof_cas(k2) - frac*(u_prof_cas(k2)-u_prof_cas(k1))
944         v_mod_cas(l)= v_prof_cas(k2) - frac*(v_prof_cas(k2)-v_prof_cas(k1))
945         ug_mod_cas(l)= ug_prof_cas(k2) - frac*(ug_prof_cas(k2)-ug_prof_cas(k1))
946         vg_mod_cas(l)= vg_prof_cas(k2) - frac*(vg_prof_cas(k2)-vg_prof_cas(k1))
947         temp_nudg_mod_cas(l)= temp_nudg_prof_cas(k2) - frac*(temp_nudg_prof_cas(k2)-temp_nudg_prof_cas(k1))
948         qv_nudg_mod_cas(l)= qv_nudg_prof_cas(k2) - frac*(qv_nudg_prof_cas(k2)-qv_nudg_prof_cas(k1))
949         u_nudg_mod_cas(l)= u_nudg_prof_cas(k2) - frac*(u_nudg_prof_cas(k2)-u_nudg_prof_cas(k1))
950         v_nudg_mod_cas(l)= v_nudg_prof_cas(k2) - frac*(v_nudg_prof_cas(k2)-v_nudg_prof_cas(k1))
951         w_mod_cas(l)= vitw_prof_cas(k2) - frac*(vitw_prof_cas(k2)-vitw_prof_cas(k1))
952         omega_mod_cas(l)= omega_prof_cas(k2) - frac*(omega_prof_cas(k2)-omega_prof_cas(k1))
953         du_mod_cas(l)= du_prof_cas(k2) - frac*(du_prof_cas(k2)-du_prof_cas(k1))
954         hu_mod_cas(l)= hu_prof_cas(k2) - frac*(hu_prof_cas(k2)-hu_prof_cas(k1))
955         vu_mod_cas(l)= vu_prof_cas(k2) - frac*(vu_prof_cas(k2)-vu_prof_cas(k1))
956         dv_mod_cas(l)= dv_prof_cas(k2) - frac*(dv_prof_cas(k2)-dv_prof_cas(k1))
957         hv_mod_cas(l)= hv_prof_cas(k2) - frac*(hv_prof_cas(k2)-hv_prof_cas(k1))
958         vv_mod_cas(l)= vv_prof_cas(k2) - frac*(vv_prof_cas(k2)-vv_prof_cas(k1))
959         dt_mod_cas(l)= dt_prof_cas(k2) - frac*(dt_prof_cas(k2)-dt_prof_cas(k1))
960         ht_mod_cas(l)= ht_prof_cas(k2) - frac*(ht_prof_cas(k2)-ht_prof_cas(k1))
961         vt_mod_cas(l)= vt_prof_cas(k2) - frac*(vt_prof_cas(k2)-vt_prof_cas(k1))
962         dth_mod_cas(l)= dth_prof_cas(k2) - frac*(dth_prof_cas(k2)-dth_prof_cas(k1))
963         hth_mod_cas(l)= hth_prof_cas(k2) - frac*(hth_prof_cas(k2)-hth_prof_cas(k1))
964         vth_mod_cas(l)= vth_prof_cas(k2) - frac*(vth_prof_cas(k2)-vth_prof_cas(k1))
965         dq_mod_cas(l)= dq_prof_cas(k2) - frac*(dq_prof_cas(k2)-dq_prof_cas(k1))
966         hq_mod_cas(l)= hq_prof_cas(k2) - frac*(hq_prof_cas(k2)-hq_prof_cas(k1))
967         vq_mod_cas(l)= vq_prof_cas(k2) - frac*(vq_prof_cas(k2)-vq_prof_cas(k1))
968         dtrad_mod_cas(l)= dtrad_prof_cas(k2) - frac*(dtrad_prof_cas(k2)-dtrad_prof_cas(k1))
969     
970         else !play>plev_prof_cas(1)
971
972         k1=1
973         k2=2
974         print *,'interp2_vert, k1,k2=',plev_prof_cas(k1),plev_prof_cas(k2)
975         frac1 = (play(l)-plev_prof_cas(k2))/(plev_prof_cas(k1)-plev_prof_cas(k2))
976         frac2 = (play(l)-plev_prof_cas(k1))/(plev_prof_cas(k1)-plev_prof_cas(k2))
977         t_mod_cas(l)= frac1*t_prof_cas(k1) - frac2*t_prof_cas(k2)
978         theta_mod_cas(l)= frac1*th_prof_cas(k1) - frac2*th_prof_cas(k2)
979         if(theta_mod_cas(l).NE.0) t_mod_cas(l)= theta_mod_cas(l)*(play(l)/100000.)**(RD/RCPD)
980         thv_mod_cas(l)= frac1*thv_prof_cas(k1) - frac2*thv_prof_cas(k2)
981         thl_mod_cas(l)= frac1*thl_prof_cas(k1) - frac2*thl_prof_cas(k2)
982         qv_mod_cas(l)= frac1*qv_prof_cas(k1) - frac2*qv_prof_cas(k2)
983         ql_mod_cas(l)= frac1*ql_prof_cas(k1) - frac2*ql_prof_cas(k2)
984         qi_mod_cas(l)= frac1*qi_prof_cas(k1) - frac2*qi_prof_cas(k2)
985         u_mod_cas(l)= frac1*u_prof_cas(k1) - frac2*u_prof_cas(k2)
986         v_mod_cas(l)= frac1*v_prof_cas(k1) - frac2*v_prof_cas(k2)
987         ug_mod_cas(l)= frac1*ug_prof_cas(k1) - frac2*ug_prof_cas(k2)
988         vg_mod_cas(l)= frac1*vg_prof_cas(k1) - frac2*vg_prof_cas(k2)
989         temp_nudg_mod_cas(l)= frac1*temp_nudg_prof_cas(k1) - frac2*temp_nudg_prof_cas(k2)
990         qv_nudg_mod_cas(l)= frac1*qv_nudg_prof_cas(k1) - frac2*qv_nudg_prof_cas(k2)
991         u_nudg_mod_cas(l)= frac1*u_nudg_prof_cas(k1) - frac2*u_nudg_prof_cas(k2)
992         v_nudg_mod_cas(l)= frac1*v_nudg_prof_cas(k1) - frac2*v_nudg_prof_cas(k2)
993         w_mod_cas(l)= frac1*vitw_prof_cas(k1) - frac2*vitw_prof_cas(k2)
994         omega_mod_cas(l)= frac1*omega_prof_cas(k1) - frac2*omega_prof_cas(k2)
995         du_mod_cas(l)= frac1*du_prof_cas(k1) - frac2*du_prof_cas(k2)
996         hu_mod_cas(l)= frac1*hu_prof_cas(k1) - frac2*hu_prof_cas(k2)
997         vu_mod_cas(l)= frac1*vu_prof_cas(k1) - frac2*vu_prof_cas(k2)
998         dv_mod_cas(l)= frac1*dv_prof_cas(k1) - frac2*dv_prof_cas(k2)
999         hv_mod_cas(l)= frac1*hv_prof_cas(k1) - frac2*hv_prof_cas(k2)
1000         vv_mod_cas(l)= frac1*vv_prof_cas(k1) - frac2*vv_prof_cas(k2)
1001         dt_mod_cas(l)= frac1*dt_prof_cas(k1) - frac2*dt_prof_cas(k2)
1002         ht_mod_cas(l)= frac1*ht_prof_cas(k1) - frac2*ht_prof_cas(k2)
1003         vt_mod_cas(l)= frac1*vt_prof_cas(k1) - frac2*vt_prof_cas(k2)
1004         dth_mod_cas(l)= frac1*dth_prof_cas(k1) - frac2*dth_prof_cas(k2)
1005         hth_mod_cas(l)= frac1*hth_prof_cas(k1) - frac2*hth_prof_cas(k2)
1006         vth_mod_cas(l)= frac1*vth_prof_cas(k1) - frac2*vth_prof_cas(k2)
1007         dq_mod_cas(l)= frac1*dq_prof_cas(k1) - frac2*dq_prof_cas(k2)
1008         hq_mod_cas(l)= frac1*hq_prof_cas(k1) - frac2*hq_prof_cas(k2)
1009         vq_mod_cas(l)= frac1*vq_prof_cas(k1) - frac2*vq_prof_cas(k2)
1010         dtrad_mod_cas(l)= frac1*dtrad_prof_cas(k1) - frac2*dtrad_prof_cas(k2)
1011
1012         endif ! play.le.plev_prof_cas(1)
1013
1014        else ! above max altitude of forcing file
1015 
1016!jyg
1017         fact=20.*(plev_prof_cas(nlev_cas)-play(l))/plev_prof_cas(nlev_cas) !jyg
1018         fact = max(fact,0.)                                           !jyg
1019         fact = exp(-fact)                                             !jyg
1020         t_mod_cas(l)= t_prof_cas(nlev_cas)                            !jyg
1021         theta_mod_cas(l)= th_prof_cas(nlev_cas)                       !jyg
1022         thv_mod_cas(l)= thv_prof_cas(nlev_cas)                        !jyg
1023         thl_mod_cas(l)= thl_prof_cas(nlev_cas)                        !jyg
1024         qv_mod_cas(l)= qv_prof_cas(nlev_cas)*fact                     !jyg
1025         ql_mod_cas(l)= ql_prof_cas(nlev_cas)*fact                     !jyg
1026         qi_mod_cas(l)= qi_prof_cas(nlev_cas)*fact                     !jyg
1027         u_mod_cas(l)= u_prof_cas(nlev_cas)*fact                       !jyg
1028         v_mod_cas(l)= v_prof_cas(nlev_cas)*fact                       !jyg
1029         ug_mod_cas(l)= ug_prof_cas(nlev_cas)                          !jyg
1030         vg_mod_cas(l)= vg_prof_cas(nlev_cas)                          !jyg
1031         temp_nudg_mod_cas(l)= temp_nudg_prof_cas(nlev_cas)                          !jyg
1032         qv_nudg_mod_cas(l)= qv_nudg_prof_cas(nlev_cas)                          !jyg
1033         u_nudg_mod_cas(l)= u_nudg_prof_cas(nlev_cas)                          !jyg
1034         v_nudg_mod_cas(l)= v_nudg_prof_cas(nlev_cas)                          !jyg
1035         thv_mod_cas(l)= thv_prof_cas(nlev_cas)                        !jyg
1036         w_mod_cas(l)= 0.0                                             !jyg
1037         omega_mod_cas(l)= 0.0                                         !jyg
1038         du_mod_cas(l)= du_prof_cas(nlev_cas)*fact
1039         hu_mod_cas(l)= hu_prof_cas(nlev_cas)*fact                     !jyg
1040         vu_mod_cas(l)= vu_prof_cas(nlev_cas)*fact                     !jyg
1041         dv_mod_cas(l)= dv_prof_cas(nlev_cas)*fact
1042         hv_mod_cas(l)= hv_prof_cas(nlev_cas)*fact                     !jyg
1043         vv_mod_cas(l)= vv_prof_cas(nlev_cas)*fact                     !jyg
1044         dt_mod_cas(l)= dt_prof_cas(nlev_cas)
1045         ht_mod_cas(l)= ht_prof_cas(nlev_cas)                          !jyg
1046         vt_mod_cas(l)= vt_prof_cas(nlev_cas)                          !jyg
1047         dth_mod_cas(l)= dth_prof_cas(nlev_cas)
1048         hth_mod_cas(l)= hth_prof_cas(nlev_cas)                        !jyg
1049         vth_mod_cas(l)= vth_prof_cas(nlev_cas)                        !jyg
1050         dq_mod_cas(l)= dq_prof_cas(nlev_cas)*fact
1051         hq_mod_cas(l)= hq_prof_cas(nlev_cas)*fact                     !jyg
1052         vq_mod_cas(l)= vq_prof_cas(nlev_cas)*fact                     !jyg
1053         dtrad_mod_cas(l)= dtrad_prof_cas(nlev_cas)*fact               !jyg
1054 
1055        endif ! play
1056 
1057       enddo ! l
1058
1059          return
1060          end
1061!*****************************************************************************
1062
1063
1064
1065
1066
1067END MODULE mod_1D_cases_read_std
Note: See TracBrowser for help on using the repository browser.