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

Last change on this file since 5270 was 5270, checked in by abarral, 2 weeks ago

Replace F77 netcdf library by F90 netcdf library

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