source: LMDZ6/trunk/libf/phylmd/dyn1d/1DUTILS.h @ 5308

Last change on this file since 5308 was 5302, checked in by abarral, 39 hours ago

Turn compar1d.h date_cas.h into module
Move fcg_racmo.h to obsolete

  • Property svn:keywords set to Id
File size: 61.1 KB
Line 
1
2      SUBROUTINE conf_unicol
3!
4      use IOIPSL
5
6      USE print_control_mod, ONLY: lunout
7      USE tsoilnudge_mod_h
8      USE fcg_gcssold_mod_h
9      USE flux_arp_mod_h
10      USE compar1d_mod_h
11      IMPLICIT NONE
12!-----------------------------------------------------------------------
13!     Auteurs :   A. Lahellec  .
14!
15!   Declarations :
16!   --------------
17
18
19!
20!
21!   local:
22!   ------
23
24!      CHARACTER ch1*72,ch2*72,ch3*72,ch4*12
25
26!
27!  -------------------------------------------------------------------
28!
29!      .........    Initilisation parametres du lmdz1D      ..........
30!
31!---------------------------------------------------------------------
32!   initialisations:
33!   ----------------
34
35!Config  Key  = lunout
36!Config  Desc = unite de fichier pour les impressions
37!Config  Def  = 6
38!Config  Help = unite de fichier pour les impressions
39!Config         (defaut sortie standard = 6)
40      lunout=6
41!      CALL getin('lunout', lunout)
42      IF (lunout /= 5 .and. lunout /= 6) THEN
43        OPEN(lunout,FILE='lmdz.out')
44      ENDIF
45
46!Config  Key  = prt_level
47!Config  Desc = niveau d'impressions de debogage
48!Config  Def  = 0
49!Config  Help = Niveau d'impression pour le debogage
50!Config         (0 = minimum d'impression)
51!      prt_level = 0
52!      CALL getin('prt_level',prt_level)
53
54!-----------------------------------------------------------------------
55!  Parametres de controle du run:
56!-----------------------------------------------------------------------
57
58!Config  Key  = restart
59!Config  Desc = on repart des startphy et start1dyn
60!Config  Def  = false
61!Config  Help = les fichiers restart doivent etre renomme en start
62       restart =.false.
63       CALL getin('restart',restart)
64
65!Config  Key  = forcing_type
66!Config  Desc = defines the way the SCM is forced:
67!Config  Def  = 0
68!!Config  Help = 0 ==> forcing_les = .true.
69!             initial profiles from file prof.inp.001
70!             no forcing by LS convergence ;
71!             surface temperature imposed ;
72!             radiative cooling may be imposed (iflag_radia=0 in physiq.def)
73!         = 1 ==> forcing_radconv = .true.
74!             idem forcing_type = 0, but the imposed radiative cooling
75!             is set to 0 (hence, if iflag_radia=0 in physiq.def,
76!             then there is no radiative cooling at all)
77!         = 2 ==> forcing_toga = .true.
78!             initial profiles from TOGA-COARE IFA files
79!             LS convergence and SST imposed from TOGA-COARE IFA files
80!         = 3 ==> forcing_GCM2SCM = .true.
81!             initial profiles from the GCM output
82!             LS convergence imposed from the GCM output
83!         = 4 ==> forcing_twpi = .true.
84!             initial profiles from TWPICE nc files
85!             LS convergence and SST imposed from TWPICE nc files
86!         = 5 ==> forcing_rico = .true.
87!             initial profiles from RICO idealized
88!             LS convergence imposed from  RICO (cst)
89!         = 6 ==> forcing_amma = .true.
90!         = 10 ==> forcing_case = .true.
91!             initial profiles from case.nc file
92!         = 40 ==> forcing_GCSSold = .true.
93!             initial profile from GCSS file
94!             LS convergence imposed from GCSS file
95!         = 50 ==> forcing_fire = .true.
96!         = 59 ==> forcing_sandu = .true.
97!             initial profiles from sanduref file: see prof.inp.001
98!             SST varying with time and divergence constante: see ifa_sanduref.txt file
99!             Radiation has to be computed interactively
100!         = 60 ==> forcing_astex = .true.
101!             initial profiles from file: see prof.inp.001
102!             SST,divergence,ug,vg,ufa,vfa varying with time : see ifa_astex.txt file
103!             Radiation has to be computed interactively
104!         = 61 ==> forcing_armcu = .true.
105!             initial profiles from file: see prof.inp.001
106!             sensible and latent heat flux imposed: see ifa_arm_cu_1.txt
107!             large scale advective forcing & radiative tendencies applied below 1000m: see ifa_arm_cu_2.txt
108!             use geostrophic wind ug=10m/s vg=0m/s. Duration of the case 53100s
109!             Radiation to be switched off
110!         > 100 ==> forcing_case = .true. or forcing_case2 = .true.
111!             initial profiles from case.nc file
112!
113       forcing_type = 0
114       CALL getin('forcing_type',forcing_type)
115         imp_fcg_gcssold   = .false.
116         ts_fcg_gcssold    = .false.
117         Tp_fcg_gcssold    = .false.
118         Tp_ini_gcssold    = .false.
119         xTurb_fcg_gcssold = .false.
120        IF (forcing_type .eq.40) THEN
121          CALL getin('imp_fcg',imp_fcg_gcssold)
122          CALL getin('ts_fcg',ts_fcg_gcssold)
123          CALL getin('tp_fcg',Tp_fcg_gcssold)
124          CALL getin('tp_ini',Tp_ini_gcssold)
125          CALL getin('turb_fcg',xTurb_fcg_gcssold)
126        ENDIF
127
128!Parametres de forcage
129!Config  Key  = tend_t
130!Config  Desc = forcage ou non par advection de T
131!Config  Def  = false
132!Config  Help = forcage ou non par advection de T
133       tend_t =0
134       CALL getin('tend_t',tend_t)
135
136!Config  Key  = tend_q
137!Config  Desc = forcage ou non par advection de q
138!Config  Def  = false
139!Config  Help = forcage ou non par advection de q
140       tend_q =0
141       CALL getin('tend_q',tend_q)
142
143!Config  Key  = tend_u
144!Config  Desc = forcage ou non par advection de u
145!Config  Def  = false
146!Config  Help = forcage ou non par advection de u
147       tend_u =0
148       CALL getin('tend_u',tend_u)
149
150!Config  Key  = tend_v
151!Config  Desc = forcage ou non par advection de v
152!Config  Def  = false
153!Config  Help = forcage ou non par advection de v
154       tend_v =0
155       CALL getin('tend_v',tend_v)
156
157!Config  Key  = tend_w
158!Config  Desc = forcage ou non par vitesse verticale
159!Config  Def  = false
160!Config  Help = forcage ou non par vitesse verticale
161       tend_w =0
162       CALL getin('tend_w',tend_w)
163
164!Config  Key  = tend_rayo
165!Config  Desc = forcage ou non par dtrad
166!Config  Def  = false
167!Config  Help = forcage ou non par dtrad
168       tend_rayo =0
169       CALL getin('tend_rayo',tend_rayo)
170
171
172!Config  Key  = nudge_t
173!Config  Desc = constante de nudging de T
174!Config  Def  = false
175!Config  Help = constante de nudging de T
176       nudge_t =0.
177       CALL getin('nudge_t',nudge_t)
178
179!Config  Key  = nudge_q
180!Config  Desc = constante de nudging de q
181!Config  Def  = false
182!Config  Help = constante de nudging de q
183       nudge_q =0.
184       CALL getin('nudge_q',nudge_q)
185
186!Config  Key  = nudge_u
187!Config  Desc = constante de nudging de u
188!Config  Def  = false
189!Config  Help = constante de nudging de u
190       nudge_u =0.
191       CALL getin('nudge_u',nudge_u)
192
193!Config  Key  = nudge_v
194!Config  Desc = constante de nudging de v
195!Config  Def  = false
196!Config  Help = constante de nudging de v
197       nudge_v =0.
198       CALL getin('nudge_v',nudge_v)
199
200!Config  Key  = nudge_w
201!Config  Desc = constante de nudging de w
202!Config  Def  = false
203!Config  Help = constante de nudging de w
204       nudge_w =0.
205       CALL getin('nudge_w',nudge_w)
206
207
208!Config  Key  = iflag_nudge
209!Config  Desc = atmospheric nudging ttype (decimal code)
210!Config  Def  = 0
211!Config  Help = 0 ==> no nudging
212!  If digit number n of iflag_nudge is set, then nudging of type n is on
213!  If digit number n of iflag_nudge is not set, then nudging of type n is off
214!   (digits are numbered from the right)
215       iflag_nudge = 0
216       CALL getin('iflag_nudge',iflag_nudge)
217
218!Config  Key  = ok_flux_surf
219!Config  Desc = forcage ou non par les flux de surface
220!Config  Def  = false
221!Config  Help = forcage ou non par les flux de surface
222       ok_flux_surf =.false.
223       CALL getin('ok_flux_surf',ok_flux_surf)
224
225!Config  Key  = ok_forc_tsurf
226!Config  Desc = forcage ou non par la Ts
227!Config  Def  = false
228!Config  Help = forcage ou non par la Ts
229       ok_forc_tsurf=.false.
230       CALL getin('ok_forc_tsurf',ok_forc_tsurf)
231
232!Config  Key  = ok_prescr_ust
233!Config  Desc = ustar impose ou non
234!Config  Def  = false
235!Config  Help = ustar impose ou non
236       ok_prescr_ust = .false.
237       CALL getin('ok_prescr_ust',ok_prescr_ust)
238
239
240!Config  Key  = ok_prescr_beta
241!Config  Desc = betaevap impose ou non
242!Config  Def  = false
243!Config  Help = betaevap impose ou non
244       ok_prescr_beta = .false.
245       CALL getin('ok_prescr_beta',ok_prescr_beta)
246
247!Config  Key  = ok_old_disvert
248!Config  Desc = utilisation de l ancien programme disvert0 (dans 1DUTILS.h)
249!Config  Def  = false
250!Config  Help = utilisation de l ancien programme disvert0 (dans 1DUTILS.h)
251       ok_old_disvert = .FALSE.
252       CALL getin('ok_old_disvert',ok_old_disvert)
253
254!Config  Key  = time_ini
255!Config  Desc = meaningless in this  case
256!Config  Def  = 0.
257!Config  Help =
258       time_ini = 0.
259       CALL getin('time_ini',time_ini)
260
261!Config  Key  = rlat et rlon
262!Config  Desc = latitude et longitude
263!Config  Def  = 0.0  0.0
264!Config  Help = fixe la position de la colonne
265       xlat = 0.
266       xlon = 0.
267       CALL getin('rlat',xlat)
268       CALL getin('rlon',xlon)
269
270!Config  Key  = airephy
271!Config  Desc = Grid cell area
272!Config  Def  = 1.e11
273!Config  Help =
274       airefi = 1.e11
275       CALL getin('airephy',airefi)
276
277!Config  Key  = nat_surf
278!Config  Desc = surface type
279!Config  Def  = 0 (ocean)
280!Config  Help = 0=ocean,1=land,2=glacier,3=banquise
281       nat_surf = 0.
282       CALL getin('nat_surf',nat_surf)
283
284!Config  Key  = tsurf
285!Config  Desc = surface temperature
286!Config  Def  = 290.
287!Config  Help = surface temperature
288       tsurf = 290.
289       CALL getin('tsurf',tsurf)
290
291!Config  Key  = psurf
292!Config  Desc = surface pressure
293!Config  Def  = 102400.
294!Config  Help =
295       psurf = 102400.
296       CALL getin('psurf',psurf)
297
298!Config  Key  = zsurf
299!Config  Desc = surface altitude
300!Config  Def  = 0.
301!Config  Help =
302       zsurf = 0.
303       CALL getin('zsurf',zsurf)
304! EV pour accord avec format standard
305       CALL getin('zorog',zsurf)
306
307
308!Config  Key  = rugos
309!Config  Desc = coefficient de frottement
310!Config  Def  = 0.0001
311!Config  Help = calcul du Cdrag
312       rugos = 0.0001
313       CALL getin('rugos',rugos)
314! FH/2020/04/08/confinement: Pour le nouveau format standard, la rugosite s'appelle z0
315       CALL getin('z0',rugos)
316
317!Config  Key  = rugosh
318!Config  Desc = coefficient de frottement
319!Config  Def  = rugos
320!Config  Help = calcul du Cdrag
321       rugosh = rugos
322       CALL getin('rugosh',rugosh)
323
324
325
326!Config  Key  = snowmass
327!Config  Desc = mass de neige de la surface en kg/m2
328!Config  Def  = 0.0000
329!Config  Help = snowmass
330       snowmass = 0.0000
331       CALL getin('snowmass',snowmass)
332
333!Config  Key  = wtsurf et wqsurf
334!Config  Desc = ???
335!Config  Def  = 0.0 0.0
336!Config  Help =
337       wtsurf = 0.0
338       wqsurf = 0.0
339       CALL getin('wtsurf',wtsurf)
340       CALL getin('wqsurf',wqsurf)
341
342!Config  Key  = albedo
343!Config  Desc = albedo
344!Config  Def  = 0.09
345!Config  Help =
346       albedo = 0.09
347       CALL getin('albedo',albedo)
348
349!Config  Key  = agesno
350!Config  Desc = age de la neige
351!Config  Def  = 30.0
352!Config  Help =
353       xagesno = 30.0
354       CALL getin('agesno',xagesno)
355
356!Config  Key  = restart_runoff
357!Config  Desc = age de la neige
358!Config  Def  = 30.0
359!Config  Help =
360       restart_runoff = 0.0
361       CALL getin('restart_runoff',restart_runoff)
362
363!Config  Key  = qsolinp
364!Config  Desc = initial bucket water content (kg/m2) when land (5std)
365!Config  Def  = 30.0
366!Config  Help =
367       qsolinp = 1.
368       CALL getin('qsolinp',qsolinp)
369
370
371
372!Config  Key  = betaevap
373!Config  Desc = beta for actual evaporation when prescribed
374!Config  Def  = 1.0
375!Config  Help =
376       betaevap = 1.
377       CALL getin('betaevap',betaevap)
378
379!Config  Key  = zpicinp
380!Config  Desc = denivellation orographie
381!Config  Def  = 0.
382!Config  Help =  input brise
383       zpicinp = 0.
384       CALL getin('zpicinp',zpicinp)
385!Config key = nudge_tsoil
386!Config  Desc = activation of soil temperature nudging
387!Config  Def  = .FALSE.
388!Config  Help = ...
389
390       nudge_tsoil=.FALSE.
391       CALL getin('nudge_tsoil',nudge_tsoil)
392
393!Config key = isoil_nudge
394!Config  Desc = level number where soil temperature is nudged
395!Config  Def  = 3
396!Config  Help = ...
397
398       isoil_nudge=3
399       CALL getin('isoil_nudge',isoil_nudge)
400
401!Config key = Tsoil_nudge
402!Config  Desc = target temperature for tsoil(isoil_nudge)
403!Config  Def  = 300.
404!Config  Help = ...
405
406       Tsoil_nudge=300.
407       CALL getin('Tsoil_nudge',Tsoil_nudge)
408
409!Config key = tau_soil_nudge
410!Config  Desc = nudging relaxation time for tsoil
411!Config  Def  = 3600.
412!Config  Help = ...
413
414       tau_soil_nudge=3600.
415       CALL getin('tau_soil_nudge',tau_soil_nudge)
416
417!----------------------------------------------------------
418! Param??tres de for??age pour les forcages communs:
419! Pour les forcages communs: ces entiers valent 0 ou 1
420! tadv= advection tempe, tadvv= adv tempe verticale, tadvh= adv tempe horizontale
421! qadv= advection q, qadvv= adv q verticale, qadvh= adv q horizontale
422! trad= 0 (rayonnement actif) ou 1 (prescrit par tend_rad) ou adv (prescir et contenu dans les tadv)
423! forcages en omega, w, vent geostrophique ou ustar
424! Parametres de nudging en u,v,t,q valent 0 ou 1 ou le temps de nudging
425!----------------------------------------------------------
426
427!Config  Key  = tadv
428!Config  Desc = forcage ou non par advection totale de T
429!Config  Def  = false
430!Config  Help = forcage ou non par advection totale de T
431       tadv =0
432       CALL getin('tadv',tadv)
433
434!Config  Key  = tadvv
435!Config  Desc = forcage ou non par advection verticale de T
436!Config  Def  = false
437!Config  Help = forcage ou non par advection verticale de T
438       tadvv =0
439       CALL getin('tadvv',tadvv)
440
441!Config  Key  = tadvh
442!Config  Desc = forcage ou non par advection horizontale de T
443!Config  Def  = false
444!Config  Help = forcage ou non par advection horizontale de T
445       tadvh =0
446       CALL getin('tadvh',tadvh)
447
448!Config  Key  = thadv
449!Config  Desc = forcage ou non par advection totale de Theta
450!Config  Def  = false
451!Config  Help = forcage ou non par advection totale de Theta
452       thadv =0
453       CALL getin('thadv',thadv)
454
455!Config  Key  = thadvv
456!Config  Desc = forcage ou non par advection verticale de Theta
457!Config  Def  = false
458!Config  Help = forcage ou non par advection verticale de Theta
459       thadvv =0
460       CALL getin('thadvv',thadvv)
461
462!Config  Key  = thadvh
463!Config  Desc = forcage ou non par advection horizontale de Theta
464!Config  Def  = false
465!Config  Help = forcage ou non par advection horizontale de Theta
466       thadvh =0
467       CALL getin('thadvh',thadvh)
468
469!Config  Key  = qadv
470!Config  Desc = forcage ou non par advection totale de Q
471!Config  Def  = false
472!Config  Help = forcage ou non par advection totale de Q
473       qadv =0
474       CALL getin('qadv',qadv)
475
476!Config  Key  = qadvv
477!Config  Desc = forcage ou non par advection verticale de Q
478!Config  Def  = false
479!Config  Help = forcage ou non par advection verticale de Q
480       qadvv =0
481       CALL getin('qadvv',qadvv)
482
483!Config  Key  = qadvh
484!Config  Desc = forcage ou non par advection horizontale de Q
485!Config  Def  = false
486!Config  Help = forcage ou non par advection horizontale de Q
487       qadvh =0
488       CALL getin('qadvh',qadvh)
489
490!Config  Key  = trad
491!Config  Desc = forcage ou non par tendance radiative
492!Config  Def  = false
493!Config  Help = forcage ou non par tendance radiative
494       trad =0
495       CALL getin('trad',trad)
496
497!Config  Key  = forc_omega
498!Config  Desc = forcage ou non par omega
499!Config  Def  = false
500!Config  Help = forcage ou non par omega
501       forc_omega =0
502       CALL getin('forc_omega',forc_omega)
503
504!Config  Key  = forc_u
505!Config  Desc = forcage ou non par u
506!Config  Def  = false
507!Config  Help = forcage ou non par u
508       forc_u =0
509       CALL getin('forc_u',forc_u)
510
511!Config  Key  = forc_v
512!Config  Desc = forcage ou non par v
513!Config  Def  = false
514!Config  Help = forcage ou non par v
515       forc_v =0
516       CALL getin('forc_v',forc_v)
517!Config  Key  = forc_w
518!Config  Desc = forcage ou non par w
519!Config  Def  = false
520!Config  Help = forcage ou non par w
521       forc_w =0
522       CALL getin('forc_w',forc_w)
523
524!Config  Key  = forc_geo
525!Config  Desc = forcage ou non par geo
526!Config  Def  = false
527!Config  Help = forcage ou non par geo
528       forc_geo =0
529       CALL getin('forc_geo',forc_geo)
530
531! Meme chose que ok_precr_ust
532!Config  Key  = forc_ustar
533!Config  Desc = forcage ou non par ustar
534!Config  Def  = false
535!Config  Help = forcage ou non par ustar
536       forc_ustar =0
537       CALL getin('forc_ustar',forc_ustar)
538       IF (forc_ustar .EQ. 1) ok_prescr_ust=.true.
539
540
541!Config  Key  = nudging_u
542!Config  Desc = forcage ou non par nudging sur u
543!Config  Def  = false
544!Config  Help = forcage ou non par nudging sur u
545       nudging_u =0
546       CALL getin('nudging_u',nudging_u)
547
548!Config  Key  = nudging_v
549!Config  Desc = forcage ou non par nudging sur v
550!Config  Def  = false
551!Config  Help = forcage ou non par nudging sur v
552       nudging_v =0
553       CALL getin('nudging_v',nudging_v)
554
555!Config  Key  = nudging_w
556!Config  Desc = forcage ou non par nudging sur w
557!Config  Def  = false
558!Config  Help = forcage ou non par nudging sur w
559       nudging_w =0
560       CALL getin('nudging_w',nudging_w)
561
562! RELIQUE ANCIENS FORMAT. ECRASE PAR LE SUIVANT
563!Config  Key  = nudging_q
564!Config  Desc = forcage ou non par nudging sur q
565!Config  Def  = false
566!Config  Help = forcage ou non par nudging sur q
567       nudging_qv =0
568       CALL getin('nudging_q',nudging_qv)
569       CALL getin('nudging_qv',nudging_qv)
570
571       p_nudging_u=11000.
572       p_nudging_v=11000.
573       p_nudging_t=11000.
574       p_nudging_qv=11000.
575       CALL getin('p_nudging_u',p_nudging_u)
576       CALL getin('p_nudging_v',p_nudging_v)
577       CALL getin('p_nudging_t',p_nudging_t)
578       CALL getin('p_nudging_qv',p_nudging_qv)
579
580!Config  Key  = nudging_t
581!Config  Desc = forcage ou non par nudging sur t
582!Config  Def  = false
583!Config  Help = forcage ou non par nudging sur t
584       nudging_t =0
585       CALL getin('nudging_t',nudging_t)
586
587
588
589      write(lunout,*)' +++++++++++++++++++++++++++++++++++++++'
590      write(lunout,*)' Configuration des parametres du gcm1D: '
591      write(lunout,*)' +++++++++++++++++++++++++++++++++++++++'
592      write(lunout,*)' restart = ', restart
593      write(lunout,*)' forcing_type = ', forcing_type
594      write(lunout,*)' time_ini = ', time_ini
595      write(lunout,*)' rlat = ', xlat
596      write(lunout,*)' rlon = ', xlon
597      write(lunout,*)' airephy = ', airefi
598      write(lunout,*)' nat_surf = ', nat_surf
599      write(lunout,*)' tsurf = ', tsurf
600      write(lunout,*)' psurf = ', psurf
601      write(lunout,*)' zsurf = ', zsurf
602      write(lunout,*)' rugos = ', rugos
603      write(lunout,*)' snowmass=', snowmass
604      write(lunout,*)' wtsurf = ', wtsurf
605      write(lunout,*)' wqsurf = ', wqsurf
606      write(lunout,*)' albedo = ', albedo
607      write(lunout,*)' xagesno = ', xagesno
608      write(lunout,*)' restart_runoff = ', restart_runoff
609      write(lunout,*)' qsolinp = ', qsolinp
610      write(lunout,*)' zpicinp = ', zpicinp
611      write(lunout,*)' nudge_tsoil = ', nudge_tsoil
612      write(lunout,*)' isoil_nudge = ', isoil_nudge
613      write(lunout,*)' Tsoil_nudge = ', Tsoil_nudge
614      write(lunout,*)' tau_soil_nudge = ', tau_soil_nudge
615      write(lunout,*)' tadv =      ', tadv
616      write(lunout,*)' tadvv =     ', tadvv
617      write(lunout,*)' tadvh =     ', tadvh
618      write(lunout,*)' thadv =     ', thadv
619      write(lunout,*)' thadvv =    ', thadvv
620      write(lunout,*)' thadvh =    ', thadvh
621      write(lunout,*)' qadv =      ', qadv
622      write(lunout,*)' qadvv =     ', qadvv
623      write(lunout,*)' qadvh =     ', qadvh
624      write(lunout,*)' trad =      ', trad
625      write(lunout,*)' forc_omega = ', forc_omega
626      write(lunout,*)' forc_w     = ', forc_w
627      write(lunout,*)' forc_geo   = ', forc_geo
628      write(lunout,*)' forc_ustar = ', forc_ustar
629      write(lunout,*)' nudging_u  = ', nudging_u
630      write(lunout,*)' nudging_v  = ', nudging_v
631      write(lunout,*)' nudging_t  = ', nudging_t
632      write(lunout,*)' nudging_qv  = ', nudging_qv
633      IF (forcing_type .eq.40) THEN
634        write(lunout,*) '--- Forcing type GCSS Old --- with:'
635        write(lunout,*)'imp_fcg',imp_fcg_gcssold
636        write(lunout,*)'ts_fcg',ts_fcg_gcssold
637        write(lunout,*)'tp_fcg',Tp_fcg_gcssold
638        write(lunout,*)'tp_ini',Tp_ini_gcssold
639        write(lunout,*)'xturb_fcg',xTurb_fcg_gcssold
640      ENDIF
641
642      write(lunout,*)' +++++++++++++++++++++++++++++++++++++++'
643      write(lunout,*)
644!
645      RETURN
646      END
647!
648! $Id: dyn1deta0.F 1279 2010/07/30 A Lahellec$
649!
650!
651      SUBROUTINE dyn1deta0(fichnom,plev,play,phi,phis,presnivs,                 &
652     &                          ucov,vcov,temp,q,omega2)
653      USE dimphy
654      USE mod_grid_phy_lmdz
655      USE mod_phys_lmdz_para
656      USE iophy
657      USE phys_state_var_mod
658      USE iostart
659      USE write_field_phy
660      USE infotrac
661      use control_mod
662      USE comconst_mod, ONLY: im, jm, lllm
663      USE logic_mod, ONLY: fxyhypb, ysinus
664      USE temps_mod, ONLY: annee_ref, day_ini, day_ref, itau_dyn
665
666      USE dimensions_mod, ONLY: iim, jjm, llm, ndm
667IMPLICIT NONE
668!=======================================================
669! Ecriture du fichier de redemarrage sous format NetCDF
670!=======================================================
671!   Declarations:
672!   -------------
673
674!!INCLUDE "control.h"
675
676!   Arguments:
677!   ----------
678      CHARACTER*(*) fichnom
679!Al1 plev tronque pour .nc mais plev(klev+1):=0
680      real :: plev(klon,klev+1),play (klon,klev),phi(klon,klev)
681      real :: presnivs(klon,klev)
682      real :: ucov(klon,klev),vcov(klon,klev),temp(klon,klev)
683      real :: q(klon,klev,nqtot),omega2(klon,klev)
684!      real :: ug(klev),vg(klev),fcoriolis
685      real :: phis(klon)
686
687!   Variables locales pour NetCDF:
688!   ------------------------------
689      INTEGER iq
690      INTEGER length
691      PARAMETER (length = 100)
692      REAL tab_cntrl(length) ! tableau des parametres du run
693      character*4 nmq(nqtot)
694      character*12 modname
695      character*80 abort_message
696      LOGICAL found
697
698      modname = 'dyn1deta0 : '
699!!      nmq(1)="vap"
700!!      nmq(2)="cond"
701!!      do iq=3,nqtot
702!!        write(nmq(iq),'("tra",i1)') iq-2
703!!      enddo
704      DO iq = 1,nqtot
705        nmq(iq) = trim(tracers(iq)%name)
706      ENDDO
707      print*,'in dyn1deta0 ',fichnom,klon,klev,nqtot
708      CALL open_startphy(fichnom)
709      print*,'after open startphy ',fichnom,nmq
710
711!
712! Lecture des parametres de controle:
713!
714      CALL get_var("controle",tab_cntrl)
715
716
717      im         = tab_cntrl(1)
718      jm         = tab_cntrl(2)
719      lllm       = tab_cntrl(3)
720      day_ref    = tab_cntrl(4)
721      annee_ref  = tab_cntrl(5)
722!      rad        = tab_cntrl(6)
723!      omeg       = tab_cntrl(7)
724!      g          = tab_cntrl(8)
725!      cpp        = tab_cntrl(9)
726!      kappa      = tab_cntrl(10)
727!      daysec     = tab_cntrl(11)
728!      dtvr       = tab_cntrl(12)
729!      etot0      = tab_cntrl(13)
730!      ptot0      = tab_cntrl(14)
731!      ztot0      = tab_cntrl(15)
732!      stot0      = tab_cntrl(16)
733!      ang0       = tab_cntrl(17)
734!      pa         = tab_cntrl(18)
735!      preff      = tab_cntrl(19)
736!
737!      clon       = tab_cntrl(20)
738!      clat       = tab_cntrl(21)
739!      grossismx  = tab_cntrl(22)
740!      grossismy  = tab_cntrl(23)
741!
742      IF ( tab_cntrl(24).EQ.1. )  THEN
743        fxyhypb  =.true.
744!        dzoomx   = tab_cntrl(25)
745!        dzoomy   = tab_cntrl(26)
746!        taux     = tab_cntrl(28)
747!        tauy     = tab_cntrl(29)
748      ELSE
749        fxyhypb = .false.
750        ysinus  = .false.
751        IF( tab_cntrl(27).EQ.1. ) ysinus =.true.
752      ENDIF
753
754      day_ini = tab_cntrl(30)
755      itau_dyn = tab_cntrl(31)
756!   .................................................................
757!
758!
759!      PRINT*,'rad,omeg,g,cpp,kappa',rad,omeg,g,cpp,kappa
760!Al1
761       Print*,'day_ref,annee_ref,day_ini,itau_dyn',                         &
762     &              day_ref,annee_ref,day_ini,itau_dyn
763
764!  Lecture des champs
765!
766      CALL get_field("play",play,found)
767      IF (.NOT. found) PRINT*, modname//'Le champ <Play> est absent'
768      CALL get_field("phi",phi,found)
769      IF (.NOT. found) PRINT*, modname//'Le champ <Phi> est absent'
770      CALL get_field("phis",phis,found)
771      IF (.NOT. found) PRINT*, modname//'Le champ <Phis> est absent'
772      CALL get_field("presnivs",presnivs,found)
773      IF (.NOT. found) PRINT*, modname//'Le champ <Presnivs> est absent'
774      CALL get_field("ucov",ucov,found)
775      IF (.NOT. found) PRINT*, modname//'Le champ <ucov> est absent'
776      CALL get_field("vcov",vcov,found)
777      IF (.NOT. found) PRINT*, modname//'Le champ <vcov> est absent'
778      CALL get_field("temp",temp,found)
779      IF (.NOT. found) PRINT*, modname//'Le champ <temp> est absent'
780      CALL get_field("omega2",omega2,found)
781      IF (.NOT. found) PRINT*, modname//'Le champ <omega2> est absent'
782      plev(1,klev+1)=0.
783      CALL get_field("plev",plev(:,1:klev),found)
784      IF (.NOT. found) PRINT*, modname//'Le champ <Plev> est absent'
785
786      Do iq=1,nqtot
787        CALL get_field("q"//nmq(iq),q(:,:,iq),found)
788        IF (.NOT.found)PRINT*, modname//'Le champ <q'//nmq//'> est absent'
789      EndDo
790
791      CALL close_startphy
792      print*,' close startphy',fichnom,play(1,1),play(1,klev),temp(1,klev)
793!
794      RETURN
795      END
796!
797! $Id: dyn1dredem.F 1279 2010/07/29 A Lahellec$
798!
799!
800      SUBROUTINE dyn1dredem(fichnom,plev,play,phi,phis,presnivs,           &
801     &                          ucov,vcov,temp,q,omega2)
802      USE dimphy
803      USE mod_grid_phy_lmdz
804      USE mod_phys_lmdz_para
805      USE phys_state_var_mod
806      USE iostart
807      USE infotrac
808      use control_mod
809      USE comconst_mod, ONLY: cpp, daysec, dtvr, g, kappa, omeg, rad
810      USE logic_mod, ONLY: fxyhypb, ysinus
811      USE temps_mod, ONLY: annee_ref,day_end,day_ref,itau_dyn,itaufin
812
813      USE dimensions_mod, ONLY: iim, jjm, llm, ndm
814IMPLICIT NONE
815!=======================================================
816! Ecriture du fichier de redemarrage sous format NetCDF
817!=======================================================
818!   Declarations:
819!   -------------
820
821!!INCLUDE "control.h"
822
823!   Arguments:
824!   ----------
825      CHARACTER*(*) fichnom
826!Al1 plev tronque pour .nc mais plev(klev+1):=0
827      real :: plev(klon,klev),play (klon,klev),phi(klon,klev)
828      real :: presnivs(klon,klev)
829      real :: ucov(klon,klev),vcov(klon,klev),temp(klon,klev)
830      real :: q(klon,klev,nqtot)
831      real :: omega2(klon,klev),rho(klon,klev+1)
832!      real :: ug(klev),vg(klev),fcoriolis
833      real :: phis(klon)
834
835!   Variables locales pour NetCDF:
836!   ------------------------------
837      INTEGER nid
838      INTEGER ierr
839      INTEGER iq,l
840      INTEGER length
841      PARAMETER (length = 100)
842      REAL tab_cntrl(length) ! tableau des parametres du run
843      character*4 nmq(nqtot)
844      character*20 modname
845      character*80 abort_message
846!
847      INTEGER pass
848
849      CALL open_restartphy(fichnom)
850      print*,'redm1 ',fichnom,klon,klev,nqtot
851!!      nmq(1)="vap"
852!!      nmq(2)="cond"
853!!      nmq(3)="tra1"
854!!      nmq(4)="tra2"
855      DO iq = 1,nqtot
856        nmq(iq) = trim(tracers(iq)%name)
857      ENDDO
858
859!     modname = 'dyn1dredem'
860!     ierr = nf90_open(fichnom, nf90_write, nid)
861!     IF (ierr .NE. nf90_noerr) THEN
862!        abort_message="Pb. d ouverture "//fichnom
863!        CALL abort_gcm('Modele 1D',abort_message,1)
864!     ENDIF
865
866      DO l=1,length
867       tab_cntrl(l) = 0.
868      ENDDO
869       tab_cntrl(1)  = FLOAT(iim)
870       tab_cntrl(2)  = FLOAT(jjm)
871       tab_cntrl(3)  = FLOAT(llm)
872       tab_cntrl(4)  = FLOAT(day_ref)
873       tab_cntrl(5)  = FLOAT(annee_ref)
874       tab_cntrl(6)  = rad
875       tab_cntrl(7)  = omeg
876       tab_cntrl(8)  = g
877       tab_cntrl(9)  = cpp
878       tab_cntrl(10) = kappa
879       tab_cntrl(11) = daysec
880       tab_cntrl(12) = dtvr
881!       tab_cntrl(13) = etot0
882!       tab_cntrl(14) = ptot0
883!       tab_cntrl(15) = ztot0
884!       tab_cntrl(16) = stot0
885!       tab_cntrl(17) = ang0
886!       tab_cntrl(18) = pa
887!       tab_cntrl(19) = preff
888!
889!    .....    parametres  pour le zoom      ......
890
891!       tab_cntrl(20)  = clon
892!       tab_cntrl(21)  = clat
893!       tab_cntrl(22)  = grossismx
894!       tab_cntrl(23)  = grossismy
895!
896      IF ( fxyhypb )   THEN
897       tab_cntrl(24) = 1.
898!       tab_cntrl(25) = dzoomx
899!       tab_cntrl(26) = dzoomy
900       tab_cntrl(27) = 0.
901!       tab_cntrl(28) = taux
902!       tab_cntrl(29) = tauy
903      ELSE
904       tab_cntrl(24) = 0.
905!       tab_cntrl(25) = dzoomx
906!       tab_cntrl(26) = dzoomy
907       tab_cntrl(27) = 0.
908       tab_cntrl(28) = 0.
909       tab_cntrl(29) = 0.
910       IF( ysinus )  tab_cntrl(27) = 1.
911      ENDIF
912!Al1 iday_end -> day_end
913       tab_cntrl(30) = FLOAT(day_end)
914       tab_cntrl(31) = FLOAT(itau_dyn + itaufin)
915!
916      DO pass=1,2
917      CALL put_var(pass,"controle","Param. de controle Dyn1D",tab_cntrl)
918!
919
920!  Ecriture/extension de la coordonnee temps
921
922
923!  Ecriture des champs
924!
925      CALL put_field(pass,"plev","p interfaces sauf la nulle",plev)
926      CALL put_field(pass,"play","",play)
927      CALL put_field(pass,"phi","geopotentielle",phi)
928      CALL put_field(pass,"phis","geopotentiell de surface",phis)
929      CALL put_field(pass,"presnivs","",presnivs)
930      CALL put_field(pass,"ucov","",ucov)
931      CALL put_field(pass,"vcov","",vcov)
932      CALL put_field(pass,"temp","",temp)
933      CALL put_field(pass,"omega2","",omega2)
934
935      Do iq=1,nqtot
936        CALL put_field(pass,"q"//nmq(iq),"eau vap ou condens et traceurs",           &
937     &                                                      q(:,:,iq))
938      EndDo
939    IF (pass==1) CALL enddef_restartphy
940    IF (pass==2) CALL close_restartphy
941
942
943      ENDDO
944
945!
946      RETURN
947      END
948      SUBROUTINE gr_fi_dyn(nfield,ngrid,im,jm,pfi,pdyn)
949      IMPLICIT NONE
950!=======================================================================
951!   passage d'un champ de la grille scalaire a la grille physique
952!=======================================================================
953
954!-----------------------------------------------------------------------
955!   declarations:
956!   -------------
957
958      INTEGER im,jm,ngrid,nfield
959      REAL pdyn(im,jm,nfield)
960      REAL pfi(ngrid,nfield)
961
962      INTEGER i,j,ifield,ig
963
964!-----------------------------------------------------------------------
965!   calcul:
966!   -------
967
968      DO ifield=1,nfield
969!   traitement des poles
970         DO i=1,im
971            pdyn(i,1,ifield)=pfi(1,ifield)
972            pdyn(i,jm,ifield)=pfi(ngrid,ifield)
973         ENDDO
974
975!   traitement des point normaux
976         DO j=2,jm-1
977            ig=2+(j-2)*(im-1)
978            CALL SCOPY(im-1,pfi(ig,ifield),1,pdyn(1,j,ifield),1)
979            pdyn(im,j,ifield)=pdyn(1,j,ifield)
980         ENDDO
981      ENDDO
982
983      RETURN
984      END
985
986
987
988      SUBROUTINE abort_gcm(modname, message, ierr)
989
990      USE IOIPSL
991!
992! Stops the simulation cleanly, closing files and printing various
993! comments
994!
995!  Input: modname = name of calling program
996!         message = stuff to print
997!         ierr    = severity of situation ( = 0 normal )
998
999      character(len=*) modname
1000      integer ierr
1001      character(len=*) message
1002
1003      write(*,*) 'in abort_gcm'
1004      call histclo
1005!     call histclo(2)
1006!     call histclo(3)
1007!     call histclo(4)
1008!     call histclo(5)
1009      write(*,*) 'out of histclo'
1010      write(*,*) 'Stopping in ', modname
1011      write(*,*) 'Reason = ',message
1012      call getin_dump
1013!
1014      if (ierr .eq. 0) then
1015        write(*,*) 'Everything is cool'
1016      else
1017        write(*,*) 'Houston, we have a problem ', ierr
1018      endif
1019      STOP
1020      END
1021      REAL FUNCTION fq_sat(kelvin, millibar)
1022!
1023      IMPLICIT none
1024!======================================================================
1025! Autheur(s): Z.X. Li (LMD/CNRS)
1026! Objet: calculer la vapeur d'eau saturante (formule Centre Euro.)
1027!======================================================================
1028! Arguments:
1029! kelvin---input-R: temperature en Kelvin
1030! millibar--input-R: pression en mb
1031!
1032! fq_sat----output-R: vapeur d'eau saturante en kg/kg
1033!======================================================================
1034!
1035      REAL kelvin, millibar
1036!
1037      REAL r2es
1038      PARAMETER (r2es=611.14 *18.0153/28.9644)
1039!
1040      REAL r3les, r3ies, r3es
1041      PARAMETER (R3LES=17.269)
1042      PARAMETER (R3IES=21.875)
1043!
1044      REAL r4les, r4ies, r4es
1045      PARAMETER (R4LES=35.86)
1046      PARAMETER (R4IES=7.66)
1047!
1048      REAL rtt
1049      PARAMETER (rtt=273.16)
1050!
1051      REAL retv
1052      PARAMETER (retv=28.9644/18.0153 - 1.0)
1053!
1054      REAL zqsat
1055      REAL temp, pres
1056!     ------------------------------------------------------------------
1057!
1058!
1059      temp = kelvin
1060      pres = millibar * 100.0
1061!      write(*,*)'kelvin,millibar=',kelvin,millibar
1062!      write(*,*)'temp,pres=',temp,pres
1063!
1064      IF (temp .LE. rtt) THEN
1065         r3es = r3ies
1066         r4es = r4ies
1067      ELSE
1068         r3es = r3les
1069         r4es = r4les
1070      ENDIF
1071!
1072      zqsat=r2es/pres * EXP ( r3es*(temp-rtt) / (temp-r4es) )
1073      zqsat=MIN(0.5,ZQSAT)
1074      zqsat=zqsat/(1.-retv  *zqsat)
1075!
1076      fq_sat = zqsat
1077!
1078      RETURN
1079      END
1080
1081      SUBROUTINE gr_dyn_fi(nfield,im,jm,ngrid,pdyn,pfi)
1082      IMPLICIT NONE
1083!=======================================================================
1084!   passage d'un champ de la grille scalaire a la grille physique
1085!=======================================================================
1086
1087!-----------------------------------------------------------------------
1088!   declarations:
1089!   -------------
1090
1091      INTEGER im,jm,ngrid,nfield
1092      REAL pdyn(im,jm,nfield)
1093      REAL pfi(ngrid,nfield)
1094
1095      INTEGER j,ifield,ig
1096
1097!-----------------------------------------------------------------------
1098!   calcul:
1099!   -------
1100
1101      IF(ngrid.NE.2+(jm-2)*(im-1).AND.ngrid.NE.1)                          &
1102     &    STOP 'probleme de dim'
1103!   traitement des poles
1104      CALL SCOPY(nfield,pdyn,im*jm,pfi,ngrid)
1105      CALL SCOPY(nfield,pdyn(1,jm,1),im*jm,pfi(ngrid,1),ngrid)
1106
1107!   traitement des point normaux
1108      DO ifield=1,nfield
1109         DO j=2,jm-1
1110            ig=2+(j-2)*(im-1)
1111            CALL SCOPY(im-1,pdyn(1,j,ifield),1,pfi(ig,ifield),1)
1112         ENDDO
1113      ENDDO
1114
1115      RETURN
1116      END
1117
1118      SUBROUTINE disvert0(pa,preff,ap,bp,dpres,presnivs,nivsigs,nivsig)
1119
1120!    Ancienne version disvert dont on a modifie nom pour utiliser
1121!    le disvert de dyn3d (qui permet d'utiliser grille avec ab,bp imposes)
1122!    (MPL 18092012)
1123!
1124!    Auteur :  P. Le Van .
1125!
1126      USE dimensions_mod, ONLY: iim, jjm, llm, ndm
1127USE paramet_mod_h
1128IMPLICIT NONE
1129
1130
1131
1132!
1133!=======================================================================
1134!
1135!
1136!    s = sigma ** kappa   :  coordonnee  verticale
1137!    dsig(l)            : epaisseur de la couche l ds la coord.  s
1138!    sig(l)             : sigma a l'interface des couches l et l-1
1139!    ds(l)              : distance entre les couches l et l-1 en coord.s
1140!
1141!=======================================================================
1142!
1143      REAL pa,preff
1144      REAL ap(llmp1),bp(llmp1),dpres(llm),nivsigs(llm),nivsig(llmp1)
1145      REAL presnivs(llm)
1146!
1147!   declarations:
1148!   -------------
1149!
1150      REAL sig(llm+1),dsig(llm)
1151!
1152      INTEGER l
1153      REAL snorm
1154      REAL alpha,beta,gama,delta,deltaz,h
1155      INTEGER np,ierr
1156      REAL pi,x
1157
1158!-----------------------------------------------------------------------
1159!
1160      pi=2.*ASIN(1.)
1161
1162      OPEN(99,file='sigma.def',status='old',form='formatted',                   &
1163     &   iostat=ierr)
1164
1165!-----------------------------------------------------------------------
1166!   cas 1 on lit les options dans sigma.def:
1167!   ----------------------------------------
1168
1169      IF (ierr.eq.0) THEN
1170
1171      print*,'WARNING!!! on lit les options dans sigma.def'
1172      READ(99,*) deltaz
1173      READ(99,*) h
1174      READ(99,*) beta
1175      READ(99,*) gama
1176      READ(99,*) delta
1177      READ(99,*) np
1178      CLOSE(99)
1179      alpha=deltaz/(llm*h)
1180!
1181
1182       DO 1  l = 1, llm
1183       dsig(l) = (alpha+(1.-alpha)*exp(-beta*(llm-l)))*                    &
1184     &          ( (tanh(gama*l)/tanh(gama*llm))**np +                      &
1185     &            (1.-l/FLOAT(llm))*delta )
1186   1   CONTINUE
1187
1188       sig(1)=1.
1189       DO 101 l=1,llm-1
1190          sig(l+1)=sig(l)*(1.-dsig(l))/(1.+dsig(l))
1191101    CONTINUE
1192       sig(llm+1)=0.
1193
1194       DO 2  l = 1, llm
1195       dsig(l) = sig(l)-sig(l+1)
1196   2   CONTINUE
1197!
1198
1199      ELSE
1200!-----------------------------------------------------------------------
1201!   cas 2 ancienne discretisation (LMD5...):
1202!   ----------------------------------------
1203
1204      PRINT*,'WARNING!!! Ancienne discretisation verticale'
1205
1206      h=7.
1207      snorm  = 0.
1208      DO l = 1, llm
1209         x = 2.*asin(1.) * (FLOAT(l)-0.5) / float(llm+1)
1210         dsig(l) = 1.0 + 7.0 * SIN(x)**2
1211         snorm = snorm + dsig(l)
1212      ENDDO
1213      snorm = 1./snorm
1214      DO l = 1, llm
1215         dsig(l) = dsig(l)*snorm
1216      ENDDO
1217      sig(llm+1) = 0.
1218      DO l = llm, 1, -1
1219         sig(l) = sig(l+1) + dsig(l)
1220      ENDDO
1221
1222      ENDIF
1223
1224
1225      DO l=1,llm
1226        nivsigs(l) = FLOAT(l)
1227      ENDDO
1228
1229      DO l=1,llmp1
1230        nivsig(l)= FLOAT(l)
1231      ENDDO
1232
1233!
1234!    ....  Calculs  de ap(l) et de bp(l)  ....
1235!    .........................................
1236!
1237!
1238!   .....  pa et preff sont lus  sur les fichiers start par lectba  .....
1239!
1240
1241      bp(llmp1) =   0.
1242
1243      DO l = 1, llm
1244!c
1245!cc    ap(l) = 0.
1246!cc    bp(l) = sig(l)
1247
1248      bp(l) = EXP( 1. -1./( sig(l)*sig(l)) )
1249      ap(l) = pa * ( sig(l) - bp(l) )
1250!
1251      ENDDO
1252      ap(llmp1) = pa * ( sig(llmp1) - bp(llmp1) )
1253
1254      PRINT *,' BP '
1255      PRINT *,  bp
1256      PRINT *,' AP '
1257      PRINT *,  ap
1258
1259      DO l = 1, llm
1260       dpres(l) = bp(l) - bp(l+1)
1261       presnivs(l) = 0.5 *( ap(l)+bp(l)*preff + ap(l+1)+bp(l+1)*preff )
1262      ENDDO
1263
1264      PRINT *,' PRESNIVS '
1265      PRINT *,presnivs
1266
1267      RETURN
1268      END
1269
1270!!======================================================================
1271!       SUBROUTINE read_tsurf1d(knon,sst_out)
1272!
1273!! This subroutine specifies the surface temperature to be used in 1D simulations
1274!
1275!      USE dimphy, ONLY : klon
1276!
1277!      INTEGER, INTENT(IN)                  :: knon     ! nomber of points on compressed grid
1278!      REAL, DIMENSION(klon), INTENT(OUT)   :: sst_out  ! tsurf used to force the single-column model
1279!
1280!       INTEGER :: i
1281!! COMMON defined in lmdz1d.F:
1282!       real ts_cur
1283!       common /sst_forcing/ts_cur
1284
1285!       DO i = 1, knon
1286!        sst_out(i) = ts_cur
1287!       ENDDO
1288!
1289!      END SUBROUTINE read_tsurf1d
1290!
1291!===============================================================
1292      subroutine advect_vert(llm,w,dt,q,plev)
1293!===============================================================
1294!   Schema amont pour l'advection verticale en 1D
1295!   w est la vitesse verticale dp/dt en Pa/s
1296!   Traitement en volumes finis
1297!   d / dt ( zm q ) = delta_z ( omega q )
1298!   d / dt ( zm ) = delta_z ( omega )
1299!   avec zm = delta_z ( p )
1300!   si * designe la valeur au pas de temps t+dt
1301!   zm*(l) q*(l) - zm(l) q(l) = w(l+1) q(l+1) - w(l) q(l)
1302!   zm*(l) -zm(l) = w(l+1) - w(l)
1303!   avec w=omega * dt
1304!---------------------------------------------------------------
1305      implicit none
1306! arguments
1307      integer llm
1308      real w(llm+1),q(llm),plev(llm+1),dt
1309
1310! local
1311      integer l
1312      real zwq(llm+1),zm(llm+1),zw(llm+1)
1313      real qold
1314
1315!---------------------------------------------------------------
1316
1317      do l=1,llm
1318         zw(l)=dt*w(l)
1319         zm(l)=plev(l)-plev(l+1)
1320         zwq(l)=q(l)*zw(l)
1321      enddo
1322      zwq(llm+1)=0.
1323      zw(llm+1)=0.
1324
1325      do l=1,llm
1326         qold=q(l)
1327         q(l)=(q(l)*zm(l)+zwq(l+1)-zwq(l))/(zm(l)+zw(l+1)-zw(l))
1328         print*,'ADV Q ',zm(l),zw(l),zwq(l),qold,q(l)
1329      enddo
1330
1331
1332      return
1333      end
1334
1335!===============================================================
1336
1337
1338       SUBROUTINE advect_va(llm,omega,d_t_va,d_q_va,d_u_va,d_v_va,              &
1339     &                q,temp,u,v,play)
1340!itlmd
1341!----------------------------------------------------------------------
1342!   Calcul de l'advection verticale (ascendance et subsidence) de
1343!   temperature et d'humidite. Hypothese : ce qui rentre de l'exterieur
1344!   a les memes caracteristiques que l'air de la colonne 1D (WTG) ou
1345!   sans WTG rajouter une advection horizontale
1346!----------------------------------------------------------------------
1347        USE yomcst_mod_h
1348implicit none
1349
1350!        argument
1351        integer llm
1352        real  omega(llm+1),d_t_va(llm), d_q_va(llm,3)
1353        real  d_u_va(llm), d_v_va(llm)
1354        real  q(llm,3),temp(llm)
1355        real  u(llm),v(llm)
1356        real  play(llm)
1357! interne
1358        integer l
1359        real alpha,omgdown,omgup
1360
1361      do l= 1,llm
1362       if(l.eq.1) then
1363!si omgup pour la couche 1, alors tendance nulle
1364        omgdown=max(omega(2),0.0)
1365        alpha = rkappa*temp(l)*(1.+q(l,1)*rv/rd)/(play(l)*(1.+q(l,1)))
1366        d_t_va(l)= alpha*(omgdown)-omgdown*(temp(l)-temp(l+1))             &
1367     &       /(play(l)-play(l+1))
1368
1369        d_q_va(l,:)= -omgdown*(q(l,:)-q(l+1,:))/(play(l)-play(l+1))
1370
1371        d_u_va(l)= -omgdown*(u(l)-u(l+1))/(play(l)-play(l+1))
1372        d_v_va(l)= -omgdown*(v(l)-v(l+1))/(play(l)-play(l+1))
1373
1374
1375       elseif(l.eq.llm) then
1376        omgup=min(omega(l),0.0)
1377        alpha = rkappa*temp(l)*(1.+q(l,1)*rv/rd)/(play(l)*(1.+q(l,1)))
1378        d_t_va(l)= alpha*(omgup)-                                          &
1379
1380!bug?     &              omgup*(temp(l-1)-temp(l))/(play(l-1)-plev(l))
1381     &              omgup*(temp(l-1)-temp(l))/(play(l-1)-play(l))
1382        d_q_va(l,:)= -omgup*(q(l-1,:)-q(l,:))/(play(l-1)-play(l))
1383        d_u_va(l)= -omgup*(u(l-1)-u(l))/(play(l-1)-play(l))
1384        d_v_va(l)= -omgup*(v(l-1)-v(l))/(play(l-1)-play(l))
1385
1386       else
1387        omgup=min(omega(l),0.0)
1388        omgdown=max(omega(l+1),0.0)
1389        alpha = rkappa*temp(l)*(1.+q(l,1)*rv/rd)/(play(l)*(1.+q(l,1)))
1390        d_t_va(l)= alpha*(omgup+omgdown)-omgdown*(temp(l)-temp(l+1))       &
1391     &              /(play(l)-play(l+1))-                                  &
1392!bug?     &              omgup*(temp(l-1)-temp(l))/(play(l-1)-plev(l))
1393     &              omgup*(temp(l-1)-temp(l))/(play(l-1)-play(l))
1394!      print*, '  ??? '
1395
1396        d_q_va(l,:)= -omgdown*(q(l,:)-q(l+1,:))                            &
1397     &              /(play(l)-play(l+1))-                                  &
1398     &              omgup*(q(l-1,:)-q(l,:))/(play(l-1)-play(l))
1399        d_u_va(l)= -omgdown*(u(l)-u(l+1))                                  &
1400     &              /(play(l)-play(l+1))-                                  &
1401     &              omgup*(u(l-1)-u(l))/(play(l-1)-play(l))
1402        d_v_va(l)= -omgdown*(v(l)-v(l+1))                                  &
1403     &              /(play(l)-play(l+1))-                                  &
1404     &              omgup*(v(l-1)-v(l))/(play(l-1)-play(l))
1405
1406      endif
1407
1408      enddo
1409!fin itlmd
1410        return
1411        end
1412!       SUBROUTINE lstendH(llm,omega,d_t_va,d_q_va,d_u_va,d_v_va,
1413       SUBROUTINE lstendH(llm,nqtot,omega,d_t_va,d_q_va,                        &
1414     &                q,temp,u,v,play)
1415!itlmd
1416!----------------------------------------------------------------------
1417!   Calcul de l'advection verticale (ascendance et subsidence) de
1418!   temperature et d'humidite. Hypothese : ce qui rentre de l'exterieur
1419!   a les memes caracteristiques que l'air de la colonne 1D (WTG) ou
1420!   sans WTG rajouter une advection horizontale
1421!----------------------------------------------------------------------
1422        USE yomcst_mod_h
1423implicit none
1424
1425!        argument
1426        integer llm,nqtot
1427        real  omega(llm+1),d_t_va(llm), d_q_va(llm,nqtot)
1428!        real  d_u_va(llm), d_v_va(llm)
1429        real  q(llm,nqtot),temp(llm)
1430        real  u(llm),v(llm)
1431        real  play(llm)
1432        real cor(llm)
1433!        real dph(llm),dudp(llm),dvdp(llm),dqdp(llm),dtdp(llm)
1434        real dph(llm),dqdp(llm),dtdp(llm)
1435! interne
1436        integer k
1437        real omdn,omup
1438
1439!        dudp=0.
1440!        dvdp=0.
1441        dqdp=0.
1442        dtdp=0.
1443!        d_u_va=0.
1444!        d_v_va=0.
1445
1446      cor(:) = rkappa*temp*(1.+q(:,1)*rv/rd)/(play*(1.+q(:,1)))
1447
1448
1449      do k=2,llm-1
1450
1451       dph  (k-1) = (play()- play(k-1  ))
1452!       dudp (k-1) = (u   ()- u   (k-1  ))/dph(k-1)
1453!       dvdp (k-1) = (v   ()- v   (k-1  ))/dph(k-1)
1454       dqdp (k-1) = (q   (k,1)- q   (k-1,1))/dph(k-1)
1455       dtdp (k-1) = (temp()- temp(k-1  ))/dph(k-1)
1456
1457      enddo
1458
1459!      dudp (  llm  ) = dudp ( llm-1 )
1460!      dvdp (  llm  ) = dvdp ( llm-1 )
1461      dqdp (  llm  ) = dqdp ( llm-1 )
1462      dtdp (  llm  ) = dtdp ( llm-1 )
1463
1464      do k=2,llm-1
1465      omdn=max(0.0,omega(k+1))
1466      omup=min(0.0,omega( k ))
1467
1468!      d_u_va(k)  = -omdn*dudp(k)-omup*dudp(k-1)
1469!      d_v_va(k)  = -omdn*dvdp(k)-omup*dvdp(k-1)
1470      d_q_va(k,1)= -omdn*dqdp(k)-omup*dqdp(k-1)
1471      d_t_va(k)  = -omdn*dtdp(k)-omup*dtdp(k-1)+(omup+omdn)*cor(k)
1472      enddo
1473
1474      omdn=max(0.0,omega( 2 ))
1475      omup=min(0.0,omega(llm))
1476!      d_u_va( 1 )   = -omdn*dudp( 1 )
1477!      d_u_va(llm)   = -omup*dudp(llm)
1478!      d_v_va( 1 )   = -omdn*dvdp( 1 )
1479!      d_v_va(llm)   = -omup*dvdp(llm)
1480      d_q_va( 1 ,1) = -omdn*dqdp( 1 )
1481      d_q_va(llm,1) = -omup*dqdp(llm)
1482      d_t_va( 1 )   = -omdn*dtdp( 1 )+omdn*cor( 1 )
1483      d_t_va(llm)   = -omup*dtdp(llm)!+omup*cor(llm)
1484
1485!      if(abs(rlat(1))>10.) then
1486!     Calculate the tendency due agestrophic motions
1487!      du_age = fcoriolis*(v-vg)
1488!      dv_age = fcoriolis*(ug-u)
1489!      endif
1490
1491!       call writefield_phy('d_t_va',d_t_va,llm)
1492
1493          return
1494         end
1495
1496!======================================================================
1497
1498!  Subroutines for nudging
1499
1500      Subroutine Nudge_RHT_init (paprs,pplay,t,q,t_targ,rh_targ)
1501! ========================================================
1502  USE dimphy
1503
1504  USE yomcst_mod_h
1505  USE yoethf_mod_h
1506implicit none
1507
1508! ========================================================
1509      REAL paprs(klon,klevp1)
1510      REAL pplay(klon,klev)
1511!
1512!      Variables d'etat
1513      REAL t(klon,klev)
1514      REAL q(klon,klev)
1515!
1516!   Profiles cible
1517      REAL t_targ(klon,klev)
1518      REAL rh_targ(klon,klev)
1519!
1520   INTEGER k,i
1521   REAL zx_qs
1522
1523! Declaration des constantes et des fonctions thermodynamiques
1524!
1525!
1526!  ----------------------------------------
1527!  Statement functions
1528include "FCTTRE.h"
1529!  ----------------------------------------
1530!
1531        DO k = 1,klev
1532         DO i = 1,klon
1533           t_targ(i,k) = t(i,k)
1534           IF (t(i,k).LT.RTT) THEN
1535              zx_qs = qsats(t(i,k))/(pplay(i,k))
1536           ELSE
1537              zx_qs = qsatl(t(i,k))/(pplay(i,k))
1538           ENDIF
1539           rh_targ(i,k) = q(i,k)/zx_qs
1540         ENDDO
1541        ENDDO
1542      print *, 't_targ',t_targ
1543      print *, 'rh_targ',rh_targ
1544!
1545!
1546      RETURN
1547      END
1548
1549      Subroutine Nudge_UV_init (paprs,pplay,u,v,u_targ,v_targ)
1550! ========================================================
1551  USE dimphy
1552
1553  implicit none
1554
1555! ========================================================
1556      REAL paprs(klon,klevp1)
1557      REAL pplay(klon,klev)
1558!
1559!      Variables d'etat
1560      REAL u(klon,klev)
1561      REAL v(klon,klev)
1562!
1563!   Profiles cible
1564      REAL u_targ(klon,klev)
1565      REAL v_targ(klon,klev)
1566!
1567   INTEGER k,i
1568!
1569        DO k = 1,klev
1570         DO i = 1,klon
1571           u_targ(i,k) = u(i,k)
1572           v_targ(i,k) = v(i,k)
1573         ENDDO
1574        ENDDO
1575      print *, 'u_targ',u_targ
1576      print *, 'v_targ',v_targ
1577!
1578!
1579      RETURN
1580      END
1581
1582      Subroutine Nudge_RHT (dtime,paprs,pplay,t_targ,rh_targ,t,q,          &
1583     &                      d_t,d_q)
1584! ========================================================
1585  USE dimphy
1586
1587  USE yomcst_mod_h
1588  USE yoethf_mod_h
1589implicit none
1590
1591! ========================================================
1592      REAL dtime
1593      REAL paprs(klon,klevp1)
1594      REAL pplay(klon,klev)
1595!
1596!      Variables d'etat
1597      REAL t(klon,klev)
1598      REAL q(klon,klev)
1599!
1600! Tendances
1601      REAL d_t(klon,klev)
1602      REAL d_q(klon,klev)
1603!
1604!   Profiles cible
1605      REAL t_targ(klon,klev)
1606      REAL rh_targ(klon,klev)
1607!
1608!   Temps de relaxation
1609      REAL tau
1610!c      DATA tau /3600./
1611!!      DATA tau /5400./
1612      DATA tau /1800./
1613!
1614   INTEGER k,i
1615   REAL zx_qs, rh, tnew, d_rh, rhnew
1616
1617! Declaration des constantes et des fonctions thermodynamiques
1618!
1619
1620!
1621!  ----------------------------------------
1622!  Statement functions
1623include "FCTTRE.h"
1624!  ----------------------------------------
1625!
1626        print *,'dtime, tau ',dtime,tau
1627        print *, 't_targ',t_targ
1628        print *, 'rh_targ',rh_targ
1629        print *,'temp ',t
1630        print *,'hum ',q
1631!
1632        DO k = 1,klev
1633         DO i = 1,klon
1634           IF (paprs(i,1)-pplay(i,k) .GT. 10000.) THEN
1635            IF (t(i,k).LT.RTT) THEN
1636               zx_qs = qsats(t(i,k))/(pplay(i,k))
1637            ELSE
1638               zx_qs = qsatl(t(i,k))/(pplay(i,k))
1639            ENDIF
1640            rh = q(i,k)/zx_qs
1641!
1642            d_t(i,k) = d_t(i,k) + 1./tau*(t_targ(i,k)-t(i,k))
1643            d_rh = 1./tau*(rh_targ(i,k)-rh)
1644!
1645            tnew = t(i,k)+d_t(i,k)*dtime
1646!jyg<
1647!   Formule pour q :
1648!                         d_q = (1/tau) [rh_targ*qsat(T_new) - q]
1649!
1650!  Cette formule remplace d_q = (1/tau) [rh_targ - rh] qsat(T_new)
1651!   qui n'etait pas correcte.
1652!
1653            IF (tnew.LT.RTT) THEN
1654               zx_qs = qsats(tnew)/(pplay(i,k))
1655            ELSE
1656               zx_qs = qsatl(tnew)/(pplay(i,k))
1657            ENDIF
1658!!            d_q(i,k) = d_q(i,k) + d_rh*zx_qs
1659            d_q(i,k) = d_q(i,k) + (1./tau)*(rh_targ(i,k)*zx_qs - q(i,k))
1660            rhnew = (q(i,k)+d_q(i,k)*dtime)/zx_qs
1661!
1662            print *,' k,d_t,rh,d_rh,rhnew,d_q ',    &
1663                      k,d_t(i,k),rh,d_rh,rhnew,d_q(i,k)
1664           ENDIF
1665!
1666         ENDDO
1667        ENDDO
1668!
1669      RETURN
1670      END
1671
1672      Subroutine Nudge_UV (dtime,paprs,pplay,u_targ,v_targ,u,v,          &
1673     &                      d_u,d_v)
1674! ========================================================
1675  USE dimphy
1676
1677  implicit none
1678
1679! ========================================================
1680      REAL dtime
1681      REAL paprs(klon,klevp1)
1682      REAL pplay(klon,klev)
1683!
1684!      Variables d'etat
1685      REAL u(klon,klev)
1686      REAL v(klon,klev)
1687!
1688! Tendances
1689      REAL d_u(klon,klev)
1690      REAL d_v(klon,klev)
1691!
1692!   Profiles cible
1693      REAL u_targ(klon,klev)
1694      REAL v_targ(klon,klev)
1695!
1696!   Temps de relaxation
1697      REAL tau
1698!c      DATA tau /3600./
1699!      DATA tau /5400./
1700       DATA tau /43200./
1701!
1702   INTEGER k,i
1703
1704!
1705        !print *,'dtime, tau ',dtime,tau
1706        !print *, 'u_targ',u_targ
1707        !print *, 'v_targ',v_targ
1708        !print *,'zonal velocity ',u
1709        !print *,'meridional velocity ',v
1710        DO k = 1,klev
1711         DO i = 1,klon
1712!CR: nudging everywhere
1713!           IF (paprs(i,1)-pplay(i,k) .GT. 10000.) THEN
1714!
1715            d_u(i,k) = d_u(i,k) + 1./tau*(u_targ(i,k)-u(i,k))
1716            d_v(i,k) = d_v(i,k) + 1./tau*(v_targ(i,k)-v(i,k))
1717!
1718!           print *,' k,u,d_u,v,d_v ',    &
1719!                     k,u(i,k),d_u(i,k),v(i,k),d_v(i,k)
1720!           ENDIF
1721!
1722         ENDDO
1723        ENDDO
1724!
1725      RETURN
1726      END
1727
1728!=====================================================================
1729       SUBROUTINE interp2_case_vertical(play,nlev_cas,plev_prof_cas                                    &
1730     &         ,t_prof_cas,th_prof_cas,thv_prof_cas,thl_prof_cas                                       &
1731     &         ,qv_prof_cas,ql_prof_cas,qi_prof_cas,u_prof_cas,v_prof_cas                              &
1732     &         ,ug_prof_cas,vg_prof_cas,vitw_prof_cas,omega_prof_cas                                   &
1733     &         ,du_prof_cas,hu_prof_cas,vu_prof_cas,dv_prof_cas,hv_prof_cas,vv_prof_cas                &
1734     &         ,dt_prof_cas,ht_prof_cas,vt_prof_cas,dtrad_prof_cas,dq_prof_cas,hq_prof_cas,vq_prof_cas &
1735     &         ,dth_prof_cas,hth_prof_cas,vth_prof_cas                                                 &
1736!
1737     &         ,t_mod_cas,theta_mod_cas,thv_mod_cas,thl_mod_cas                                        &
1738     &         ,qv_mod_cas,ql_mod_cas,qi_mod_cas,u_mod_cas,v_mod_cas                                   &
1739     &         ,ug_mod_cas,vg_mod_cas,w_mod_cas,omega_mod_cas                                          &
1740     &         ,du_mod_cas,hu_mod_cas,vu_mod_cas,dv_mod_cas,hv_mod_cas,vv_mod_cas                      &
1741     &         ,dt_mod_cas,ht_mod_cas,vt_mod_cas,dtrad_mod_cas,dq_mod_cas,hq_mod_cas,vq_mod_cas        &
1742     &         ,dth_mod_cas,hth_mod_cas,vth_mod_cas,mxcalc)
1743
1744       USE dimensions_mod, ONLY: iim, jjm, llm, ndm
1745USE yomcst_mod_h
1746implicit none
1747
1748
1749
1750
1751!-------------------------------------------------------------------------
1752! Vertical interpolation of generic case forcing data onto mod_casel levels
1753!-------------------------------------------------------------------------
1754 
1755       integer nlevmax
1756       parameter (nlevmax=41)
1757       integer nlev_cas,mxcalc
1758!       real play(llm), plev_prof(nlevmax) 
1759!       real t_prof(nlevmax),q_prof(nlevmax)
1760!       real u_prof(nlevmax),v_prof(nlevmax), w_prof(nlevmax)
1761!       real ht_prof(nlevmax),vt_prof(nlevmax)
1762!       real hq_prof(nlevmax),vq_prof(nlevmax)
1763 
1764       real play(llm), plev_prof_cas(nlev_cas) 
1765       real t_prof_cas(nlev_cas),th_prof_cas(nlev_cas),thv_prof_cas(nlev_cas),thl_prof_cas(nlev_cas)
1766       real qv_prof_cas(nlev_cas),ql_prof_cas(nlev_cas),qi_prof_cas(nlev_cas)
1767       real u_prof_cas(nlev_cas),v_prof_cas(nlev_cas)
1768       real ug_prof_cas(nlev_cas),vg_prof_cas(nlev_cas), vitw_prof_cas(nlev_cas),omega_prof_cas(nlev_cas)
1769       real du_prof_cas(nlev_cas),hu_prof_cas(nlev_cas),vu_prof_cas(nlev_cas)
1770       real dv_prof_cas(nlev_cas),hv_prof_cas(nlev_cas),vv_prof_cas(nlev_cas)
1771       real dt_prof_cas(nlev_cas),ht_prof_cas(nlev_cas),vt_prof_cas(nlev_cas),dtrad_prof_cas(nlev_cas)
1772       real dth_prof_cas(nlev_cas),hth_prof_cas(nlev_cas),vth_prof_cas(nlev_cas)
1773       real dq_prof_cas(nlev_cas),hq_prof_cas(nlev_cas),vq_prof_cas(nlev_cas)
1774 
1775       real t_mod_cas(llm),theta_mod_cas(llm),thv_mod_cas(llm),thl_mod_cas(llm)
1776       real qv_mod_cas(llm),ql_mod_cas(llm),qi_mod_cas(llm)
1777       real u_mod_cas(llm),v_mod_cas(llm)
1778       real ug_mod_cas(llm),vg_mod_cas(llm), w_mod_cas(llm),omega_mod_cas(llm)
1779       real du_mod_cas(llm),hu_mod_cas(llm),vu_mod_cas(llm)
1780       real dv_mod_cas(llm),hv_mod_cas(llm),vv_mod_cas(llm)
1781       real dt_mod_cas(llm),ht_mod_cas(llm),vt_mod_cas(llm),dtrad_mod_cas(llm)
1782       real dth_mod_cas(llm),hth_mod_cas(llm),vth_mod_cas(llm)
1783       real dq_mod_cas(llm),hq_mod_cas(llm),vq_mod_cas(llm)
1784 
1785       integer l,k,k1,k2
1786       real frac,frac1,frac2,fact
1787 
1788!       do l = 1, llm
1789!       print *,'debut interp2, play=',l,play(l)
1790!       enddo
1791!      do l = 1, nlev_cas
1792!      print *,'debut interp2, plev_prof_cas=',l,play(l),plev_prof_cas(l)
1793!      enddo
1794
1795       do l = 1, llm
1796
1797        if (play(l).ge.plev_prof_cas(nlev_cas)) then
1798 
1799        mxcalc=l
1800!        print *,'debut interp2, mxcalc=',mxcalc
1801         k1=0
1802         k2=0
1803
1804         if (play(l).le.plev_prof_cas(1)) then
1805
1806         do k = 1, nlev_cas-1
1807          if (play(l).le.plev_prof_cas(k).and. play(l).gt.plev_prof_cas(k+1)) then
1808            k1=k
1809            k2=k+1
1810          endif
1811         enddo
1812
1813         if (k1.eq.0 .or. k2.eq.0) then
1814          write(*,*) 'PB! k1, k2 = ',k1,k2
1815          write(*,*) 'l,play(l) = ',l,play(l)/100
1816         do k = 1, nlev_cas-1
1817          write(*,*) 'k,plev_prof_cas(k) = ',k,plev_prof_cas(k)/100
1818         enddo
1819         endif
1820
1821         frac = (plev_prof_cas(k2)-play(l))/(plev_prof_cas(k2)-plev_prof_cas(k1))
1822         t_mod_cas(l)= t_prof_cas(k2) - frac*(t_prof_cas(k2)-t_prof_cas(k1))
1823         theta_mod_cas(l)= th_prof_cas(k2) - frac*(th_prof_cas(k2)-th_prof_cas(k1))
1824         if(theta_mod_cas(l).NE.0) t_mod_cas(l)= theta_mod_cas(l)*(play(l)/100000.)**(RD/RCPD)
1825         thv_mod_cas(l)= thv_prof_cas(k2) - frac*(thv_prof_cas(k2)-thv_prof_cas(k1))
1826         thl_mod_cas(l)= thl_prof_cas(k2) - frac*(thl_prof_cas(k2)-thl_prof_cas(k1))
1827         qv_mod_cas(l)= qv_prof_cas(k2) - frac*(qv_prof_cas(k2)-qv_prof_cas(k1))
1828         ql_mod_cas(l)= ql_prof_cas(k2) - frac*(ql_prof_cas(k2)-ql_prof_cas(k1))
1829         qi_mod_cas(l)= qi_prof_cas(k2) - frac*(qi_prof_cas(k2)-qi_prof_cas(k1))
1830         u_mod_cas(l)= u_prof_cas(k2) - frac*(u_prof_cas(k2)-u_prof_cas(k1))
1831         v_mod_cas(l)= v_prof_cas(k2) - frac*(v_prof_cas(k2)-v_prof_cas(k1))
1832         ug_mod_cas(l)= ug_prof_cas(k2) - frac*(ug_prof_cas(k2)-ug_prof_cas(k1))
1833         vg_mod_cas(l)= vg_prof_cas(k2) - frac*(vg_prof_cas(k2)-vg_prof_cas(k1))
1834         w_mod_cas(l)= vitw_prof_cas(k2) - frac*(vitw_prof_cas(k2)-vitw_prof_cas(k1))
1835         omega_mod_cas(l)= omega_prof_cas(k2) - frac*(omega_prof_cas(k2)-omega_prof_cas(k1))
1836         du_mod_cas(l)= du_prof_cas(k2) - frac*(du_prof_cas(k2)-du_prof_cas(k1))
1837         hu_mod_cas(l)= hu_prof_cas(k2) - frac*(hu_prof_cas(k2)-hu_prof_cas(k1))
1838         vu_mod_cas(l)= vu_prof_cas(k2) - frac*(vu_prof_cas(k2)-vu_prof_cas(k1))
1839         dv_mod_cas(l)= dv_prof_cas(k2) - frac*(dv_prof_cas(k2)-dv_prof_cas(k1))
1840         hv_mod_cas(l)= hv_prof_cas(k2) - frac*(hv_prof_cas(k2)-hv_prof_cas(k1))
1841         vv_mod_cas(l)= vv_prof_cas(k2) - frac*(vv_prof_cas(k2)-vv_prof_cas(k1))
1842         dt_mod_cas(l)= dt_prof_cas(k2) - frac*(dt_prof_cas(k2)-dt_prof_cas(k1))
1843         ht_mod_cas(l)= ht_prof_cas(k2) - frac*(ht_prof_cas(k2)-ht_prof_cas(k1))
1844         vt_mod_cas(l)= vt_prof_cas(k2) - frac*(vt_prof_cas(k2)-vt_prof_cas(k1))
1845         dth_mod_cas(l)= dth_prof_cas(k2) - frac*(dth_prof_cas(k2)-dth_prof_cas(k1))
1846         hth_mod_cas(l)= hth_prof_cas(k2) - frac*(hth_prof_cas(k2)-hth_prof_cas(k1))
1847         vth_mod_cas(l)= vth_prof_cas(k2) - frac*(vth_prof_cas(k2)-vth_prof_cas(k1))
1848         dq_mod_cas(l)= dq_prof_cas(k2) - frac*(dq_prof_cas(k2)-dq_prof_cas(k1))
1849         hq_mod_cas(l)= hq_prof_cas(k2) - frac*(hq_prof_cas(k2)-hq_prof_cas(k1))
1850         vq_mod_cas(l)= vq_prof_cas(k2) - frac*(vq_prof_cas(k2)-vq_prof_cas(k1))
1851         dtrad_mod_cas(l)= dtrad_prof_cas(k2) - frac*(dtrad_prof_cas(k2)-dtrad_prof_cas(k1))
1852     
1853         else !play>plev_prof_cas(1)
1854
1855         k1=1
1856         k2=2
1857         print *,'interp2_vert, k1,k2=',plev_prof_cas(k1),plev_prof_cas(k2)
1858         frac1 = (play(l)-plev_prof_cas(k2))/(plev_prof_cas(k1)-plev_prof_cas(k2))
1859         frac2 = (play(l)-plev_prof_cas(k1))/(plev_prof_cas(k1)-plev_prof_cas(k2))
1860         t_mod_cas(l)= frac1*t_prof_cas(k1) - frac2*t_prof_cas(k2)
1861         theta_mod_cas(l)= frac1*th_prof_cas(k1) - frac2*th_prof_cas(k2)
1862         if(theta_mod_cas(l).NE.0) t_mod_cas(l)= theta_mod_cas(l)*(play(l)/100000.)**(RD/RCPD)
1863         thv_mod_cas(l)= frac1*thv_prof_cas(k1) - frac2*thv_prof_cas(k2)
1864         thl_mod_cas(l)= frac1*thl_prof_cas(k1) - frac2*thl_prof_cas(k2)
1865         qv_mod_cas(l)= frac1*qv_prof_cas(k1) - frac2*qv_prof_cas(k2)
1866         ql_mod_cas(l)= frac1*ql_prof_cas(k1) - frac2*ql_prof_cas(k2)
1867         qi_mod_cas(l)= frac1*qi_prof_cas(k1) - frac2*qi_prof_cas(k2)
1868         u_mod_cas(l)= frac1*u_prof_cas(k1) - frac2*u_prof_cas(k2)
1869         v_mod_cas(l)= frac1*v_prof_cas(k1) - frac2*v_prof_cas(k2)
1870         ug_mod_cas(l)= frac1*ug_prof_cas(k1) - frac2*ug_prof_cas(k2)
1871         vg_mod_cas(l)= frac1*vg_prof_cas(k1) - frac2*vg_prof_cas(k2)
1872         w_mod_cas(l)= frac1*vitw_prof_cas(k1) - frac2*vitw_prof_cas(k2)
1873         omega_mod_cas(l)= frac1*omega_prof_cas(k1) - frac2*omega_prof_cas(k2)
1874         du_mod_cas(l)= frac1*du_prof_cas(k1) - frac2*du_prof_cas(k2)
1875         hu_mod_cas(l)= frac1*hu_prof_cas(k1) - frac2*hu_prof_cas(k2)
1876         vu_mod_cas(l)= frac1*vu_prof_cas(k1) - frac2*vu_prof_cas(k2)
1877         dv_mod_cas(l)= frac1*dv_prof_cas(k1) - frac2*dv_prof_cas(k2)
1878         hv_mod_cas(l)= frac1*hv_prof_cas(k1) - frac2*hv_prof_cas(k2)
1879         vv_mod_cas(l)= frac1*vv_prof_cas(k1) - frac2*vv_prof_cas(k2)
1880         dt_mod_cas(l)= frac1*dt_prof_cas(k1) - frac2*dt_prof_cas(k2)
1881         ht_mod_cas(l)= frac1*ht_prof_cas(k1) - frac2*ht_prof_cas(k2)
1882         vt_mod_cas(l)= frac1*vt_prof_cas(k1) - frac2*vt_prof_cas(k2)
1883         dth_mod_cas(l)= frac1*dth_prof_cas(k1) - frac2*dth_prof_cas(k2)
1884         hth_mod_cas(l)= frac1*hth_prof_cas(k1) - frac2*hth_prof_cas(k2)
1885         vth_mod_cas(l)= frac1*vth_prof_cas(k1) - frac2*vth_prof_cas(k2)
1886         dq_mod_cas(l)= frac1*dq_prof_cas(k1) - frac2*dq_prof_cas(k2)
1887         hq_mod_cas(l)= frac1*hq_prof_cas(k1) - frac2*hq_prof_cas(k2)
1888         vq_mod_cas(l)= frac1*vq_prof_cas(k1) - frac2*vq_prof_cas(k2)
1889         dtrad_mod_cas(l)= frac1*dtrad_prof_cas(k1) - frac2*dtrad_prof_cas(k2)
1890
1891         endif ! play.le.plev_prof_cas(1)
1892
1893        else ! above max altitude of forcing file
1894 
1895!jyg
1896         fact=20.*(plev_prof_cas(nlev_cas)-play(l))/plev_prof_cas(nlev_cas) !jyg
1897         fact = max(fact,0.)                                           !jyg
1898         fact = exp(-fact)                                             !jyg
1899         t_mod_cas(l)= t_prof_cas(nlev_cas)                            !jyg
1900         theta_mod_cas(l)= th_prof_cas(nlev_cas)                       !jyg
1901         thv_mod_cas(l)= thv_prof_cas(nlev_cas)                        !jyg
1902         thl_mod_cas(l)= thl_prof_cas(nlev_cas)                        !jyg
1903         qv_mod_cas(l)= qv_prof_cas(nlev_cas)*fact                     !jyg
1904         ql_mod_cas(l)= ql_prof_cas(nlev_cas)*fact                     !jyg
1905         qi_mod_cas(l)= qi_prof_cas(nlev_cas)*fact                     !jyg
1906         u_mod_cas(l)= u_prof_cas(nlev_cas)*fact                       !jyg
1907         v_mod_cas(l)= v_prof_cas(nlev_cas)*fact                       !jyg
1908         ug_mod_cas(l)= ug_prof_cas(nlev_cas)*fact                     !jyg
1909         vg_mod_cas(l)= vg_prof_cas(nlev_cas)*fact                     !jyg
1910         w_mod_cas(l)= 0.0                                             !jyg
1911         omega_mod_cas(l)= 0.0                                         !jyg
1912         du_mod_cas(l)= du_prof_cas(nlev_cas)*fact
1913         hu_mod_cas(l)= hu_prof_cas(nlev_cas)*fact                     !jyg
1914         vu_mod_cas(l)= vu_prof_cas(nlev_cas)*fact                     !jyg
1915         dv_mod_cas(l)= dv_prof_cas(nlev_cas)*fact
1916         hv_mod_cas(l)= hv_prof_cas(nlev_cas)*fact                     !jyg
1917         vv_mod_cas(l)= vv_prof_cas(nlev_cas)*fact                     !jyg
1918         dt_mod_cas(l)= dt_prof_cas(nlev_cas) 
1919         ht_mod_cas(l)= ht_prof_cas(nlev_cas)                          !jyg
1920         vt_mod_cas(l)= vt_prof_cas(nlev_cas)                          !jyg
1921         dth_mod_cas(l)= dth_prof_cas(nlev_cas) 
1922         hth_mod_cas(l)= hth_prof_cas(nlev_cas)                        !jyg
1923         vth_mod_cas(l)= vth_prof_cas(nlev_cas)                        !jyg
1924         dq_mod_cas(l)= dq_prof_cas(nlev_cas)*fact
1925         hq_mod_cas(l)= hq_prof_cas(nlev_cas)*fact                     !jyg
1926         vq_mod_cas(l)= vq_prof_cas(nlev_cas)*fact                     !jyg
1927         dtrad_mod_cas(l)= dtrad_prof_cas(nlev_cas)*fact               !jyg
1928 
1929        endif ! play
1930 
1931       enddo ! l
1932
1933          return
1934          end
1935!***************************************************************************** 
1936
1937
1938
1939
Note: See TracBrowser for help on using the repository browser.